Re: deeqSeq proposal

2006-07-05 Thread Wolfgang Jeltsch
Am Freitag, 7. April 2006 00:40 schrieb Andy Adams-Moran:
> Lennart Augustsson wrote:
> > Andy Adams-Moran wrote:
> >>> The only thing you can do with non-functions is put them in the sin
> >>> bin:
> >>>
> >>>   deepSeq :: a -> IO ()
> >>
> >> unsafeDeepSeq?
> >>
> >> I guess we don't want to expand the unsafe* vocabulary for Haskell'
> >> though ...
> >
> > What's wrong with
> > deepSeeqIO :: a -> IO ()
> > ?
> > Then you can use unsafePerformIO if you want
> > deepSeq :: a -> b -> b
>
> Yes, quite right!  In the case of deepSeqIO, we do know precisely what
> the safety condition is (as opposed to generic uses of unsafePerformIO
> and its cousins), so maybe we want to call that out somehow.
>
> A

And maybe we should switch from seq to seqIO :: a -> IO ()?

Best wishes,
Wolfgang
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org//mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-13 Thread Jan-Willem Maessen


On Apr 12, 2006, at 4:25 PM, John Meacham wrote:


On Wed, Apr 12, 2006 at 09:21:10AM -0400, Jan-Willem Maessen wrote:

Though, to be fair, an awful lot of Prelude code didn't work in pH
unless it was re-written to vary slightly from the specification.  So
the assumption of laziness was more deeply embedded than the spec was
willing to acknowledge.


out of curiosity what sort of things had to be rewritten? I have been
toying with the idea of relaxing sharing to help some optimizations  
and

was curious what I was in for.


Well, the differences really had to do with termination under an  
eager strategy.


But beyond obvious problems such as defining things in terms of take  
+ iterate (numericEnumFrom[Then]To is an obvious example), we ran  
into terrible performance problems with Read instances.  Programs  
would spend minutes running read, then a few fractions of a second  
computing.  We ended up doing a lot of tweaking, none of which was  
ever quite correct.  Ditching ReadS in terms of ReadP would do an  
enormous amount of good here, I think---it would at least put all the  
re-coding in one centralized place, which is what we ended up having  
to do anyhow.


Finally, there are a bunch of Haskell idioms which don't work in pH.   
The most obvious examples are numbering a list:

   zip [0..] xs
and where-binding a value which is unused in one clause:

f x
  | p x = ... r ...
  | q x = ... r ...
  | otherwise = ... no r ...
  where r = something very expensive

I suppose you could view this as a "sharing problem": the expression  
r is shared down two of the branches and not down the other.  But I  
don't think that's what you meant.


A lot of these can be solved by a certain amount of code motion---but  
note that this code motion changes the termination properties of the  
program as it was written.  In pH that was naughty.


-Jan



John

--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-13 Thread Lennart Augustsson

Jan-Willem Maessen wrote:


On Apr 11, 2006, at 5:37 PM, Lennart Augustsson wrote:


Yes, I realize than dynamic idempotence is not the same as
cycle detection.  I still worry. :)

I think expectance is in the eye of the beholder.  The reason
that (the pure subset of) pH was a proper implementation of
Haskell was because we were not over-specifying the semantics
originally.  I would hate to do that now.


Though, to be fair, an awful lot of Prelude code didn't work in pH 
unless it was re-written to vary slightly from the specification.  So 
the assumption of laziness was more deeply embedded than the spec was 
willing to acknowledge.


-Jan-Willem Maessen


Well, if the pH scheduler had been fair I think the Prelude functions
would have been semantically correct (but maybe not efficient).

-- Lennart

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-12 Thread Roman Leshchinskiy
On Tue, 2006-04-11 at 09:53 +0100, Simon Peyton-Jones wrote: 
> Whether it should be in a class is a rather separate discussion.  In a
> way we already sold out when we allowed seq to escape from the
> type-class world.  Perhaps deepSeq is worse (because it traverses data
> structures) but not obviously. 

I think it is much worse because it completely breaks encapsulation if
it is not in a class. For instance, is it safe to apply deepSeq to the
result of Data.Map.empty? To 'Data.Array.array (0,10) []'? The
documentation does not say, and for good reasons - whether an abstract
data type uses bottoms in its representation shouldn't be of any concern
to the clients. Bottoms become detectable, however, if the default
behaviour of deepSeq cannot be overridden. 

Roman



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 09:21:10AM -0400, Jan-Willem Maessen wrote:
> Though, to be fair, an awful lot of Prelude code didn't work in pH  
> unless it was re-written to vary slightly from the specification.  So  
> the assumption of laziness was more deeply embedded than the spec was  
> willing to acknowledge.

out of curiosity what sort of things had to be rewritten? I have been
toying with the idea of relaxing sharing to help some optimizations and
was curious what I was in for.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-12 Thread Jan-Willem Maessen


On Apr 11, 2006, at 5:37 PM, Lennart Augustsson wrote:


Yes, I realize than dynamic idempotence is not the same as
cycle detection.  I still worry. :)

I think expectance is in the eye of the beholder.  The reason
that (the pure subset of) pH was a proper implementation of
Haskell was because we were not over-specifying the semantics
originally.  I would hate to do that now.


Though, to be fair, an awful lot of Prelude code didn't work in pH  
unless it was re-written to vary slightly from the specification.  So  
the assumption of laziness was more deeply embedded than the spec was  
willing to acknowledge.


-Jan-Willem Maessen



-- Lennart

Simon Peyton-Jones wrote:
| Well, my worry was partly about the suggested version of deepSeq  
that

| would not diverge on circular structures (since circular structures
| are just one way to implement "infinite" data structures).
Dynamic idempotence is not the same as detecting circular structures.
Deepseqing a circular structure should definitely diverge, as it  
would
as if it was infinite.  Idempotence changes the operational  
behaviour,

but not the denotational behaviour.  So that part of the worry is ok.
But since the dynamic-idempotence operational behaviour is (as I
understand the proposal) the whole point, it's true that the
implementation would be constrained.  In the same kind of way that we
expect call-by-need rather than call-by-name.  S


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-11 Thread Lennart Augustsson

Yes, I realize than dynamic idempotence is not the same as
cycle detection.  I still worry. :)

I think expectance is in the eye of the beholder.  The reason
that (the pure subset of) pH was a proper implementation of
Haskell was because we were not over-specifying the semantics
originally.  I would hate to do that now.

-- Lennart

Simon Peyton-Jones wrote:

| Well, my worry was partly about the suggested version of deepSeq that
| would not diverge on circular structures (since circular structures
| are just one way to implement "infinite" data structures).

Dynamic idempotence is not the same as detecting circular structures.
Deepseqing a circular structure should definitely diverge, as it would
as if it was infinite.  Idempotence changes the operational behaviour,
but not the denotational behaviour.  So that part of the worry is ok.

But since the dynamic-idempotence operational behaviour is (as I
understand the proposal) the whole point, it's true that the
implementation would be constrained.  In the same kind of way that we
expect call-by-need rather than call-by-name.  


S



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-11 Thread Simon Peyton-Jones
| Well, my worry was partly about the suggested version of deepSeq that
| would not diverge on circular structures (since circular structures
| are just one way to implement "infinite" data structures).

Dynamic idempotence is not the same as detecting circular structures.
Deepseqing a circular structure should definitely diverge, as it would
as if it was infinite.  Idempotence changes the operational behaviour,
but not the denotational behaviour.  So that part of the worry is ok.

But since the dynamic-idempotence operational behaviour is (as I
understand the proposal) the whole point, it's true that the
implementation would be constrained.  In the same kind of way that we
expect call-by-need rather than call-by-name.  

S
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-11 Thread Lennart Augustsson

Simon Peyton-Jones wrote:

| Any function that is not defineable in (pure) Haskell should be viewed
| with utmost suspicion.  The seq function is one of these.  At least
| seq has simple denotational semantics, which can't be said for
deepSeq.
| 
| I say, put deepSeq in a type class (which is what I've done when I

need
| it).

The whole *point* is that deepSeq is (dynamically) idempotent: deepSeq
(deepSeq x) = deepSeq x.  Its denotational behaviour is perfectly
definable in Haskell, but its operational behaviour is not.  That is
both attractive (because it means you feel less anxious about wasting
work with deepSeq) and repellent (because it constrains the
implementation, as John points out).

Whether it should be in a class is a rather separate discussion.  In a
way we already sold out when we allowed seq to escape from the
type-class world.  Perhaps deepSeq is worse (because it traverses data
structures) but not obviously. 


Well, my worry was partly about the suggested version of deepSeq that
would not diverge on circular structures (since circular structures
are just one way to implement "infinite" data structures).

I think deepSeq is only worse than seq if we insist that it should
have some semantics that constrains implementations (like that the
second time you apply deepSeq it should be "fast").

I think it was a mistake to let seq out of the type class bag, but
that's already done.

-- Lennart

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-11 Thread Simon Peyton-Jones
| instance Eval (a -> b) where
| 

You could say the same of instance Num Int, because Int is a primitive
type.  But yes, seq on functions is not lambda-definable, and that is
indeed a qualitivative difference between seq and deepSeq I agree.

It's not worth making a meal of this.  All I'm saying is that there are
two distinct decisions
1. Add seqFun :: (a->b) -> c -> c
2. Given (1), one could provide seq via a type-class, or without.  H98
chooses the latter

For deepSeq, (1) doesn't arise, but the same choice arises for (2), and
with the same arguments for and against.  See in particular John
Hughes's impassioned pleas for not changing type signatures "all the way
up" when adding a 'seq'.

I don't think we disagree here.  But equally I don't there's a clear
"right" answer.

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 12:15:57PM +0100, Simon Peyton-Jones wrote:
> | well, there is a difference there in that 'seq' is unimplementable in
> | haskell, so the design comitee had freedom to implement it however
> they
> | wanted. 
>   
>   class Eval a where
> seq :: a -> b -> b
> 
>   instance Eval (a,b) where
>  seq (_,_) b = b
> 
>   instance Eval [a] where
>  seq [] b = b
>  seq (_:_) b = b

instance Eval (a -> b) where


?

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-11 Thread Simon Peyton-Jones
| well, there is a difference there in that 'seq' is unimplementable in
| haskell, so the design comitee had freedom to implement it however
they
| wanted. 

class Eval a where
  seq :: a -> b -> b

instance Eval (a,b) where
   seq (_,_) b = b

instance Eval [a] where
   seq [] b = b
   seq (_:_) b = b

etc

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 09:53:54AM +0100, Simon Peyton-Jones wrote:
> Whether it should be in a class is a rather separate discussion.  In a
> way we already sold out when we allowed seq to escape from the
> type-class world.  Perhaps deepSeq is worse (because it traverses data
> structures) but not obviously. 

well, there is a difference there in that 'seq' is unimplementable in
haskell, so the design comitee had freedom to implement it however they
wanted. however, now that we have seq, a deepSeq is perfectly
implementable* in haskell using a typeclass, which is a strong argument
for making it have one. 

* dynamic idempotent issues aside. 

in any case, if it were to be in the standard, I'd put it in a typeclass
and give a haskell translation with a note that implemenations are free
to implement optimized versions under the hood as long as the observable
effect is the same but you can't count on anything better than the plain
old recursive seq definition.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-11 Thread Simon Peyton-Jones
| Any function that is not defineable in (pure) Haskell should be viewed
| with utmost suspicion.  The seq function is one of these.  At least
| seq has simple denotational semantics, which can't be said for
deepSeq.
| 
| I say, put deepSeq in a type class (which is what I've done when I
need
| it).

The whole *point* is that deepSeq is (dynamically) idempotent: deepSeq
(deepSeq x) = deepSeq x.  Its denotational behaviour is perfectly
definable in Haskell, but its operational behaviour is not.  That is
both attractive (because it means you feel less anxious about wasting
work with deepSeq) and repellent (because it constrains the
implementation, as John points out).

Whether it should be in a class is a rather separate discussion.  In a
way we already sold out when we allowed seq to escape from the
type-class world.  Perhaps deepSeq is worse (because it traverses data
structures) but not obviously. 

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-11 Thread Simon Marlow
On 10 April 2006 22:41, Andy Gill wrote:

> Why can't we just steal a bit in the (GHC)
> info table,
> rather than mess with LSB of pointers, or have two info tables?

Because you need one bit per constructor *instance*.  eg. there are two
variants of Just: the normal one, and the deepSeq'd one.  So I either
put the bit in the constructor instance itself, or I need one info table
for each variant, or I need to distinguish based on the address of the
closure.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-10 Thread John Meacham
On Mon, Apr 10, 2006 at 02:40:44PM -0700, Andy Gill wrote:
> >it is unlikely it will even be possible to implement in jhc without
> >radical changes to its internals. there is just no where to attach
> >a bit
> >to, and even if there were, there is no generic way to evaluate
> >something to WHNF, or even a concept of WHNF in final grin. (grin code
> >can look inside unevaluated closures, hopefully making the thunk
> >non-updatable)
>
> I do not understand.
>
> - (A) I'm calling for a recursive descent function that does seq. I
> could
> write it in Haskell, for any specific type.  How is seq implemented jhs?

it is true, if you can express it in core, then jhc can implement it.
but there is no way to express 'the bit you want to steal' in core.
indeed there is no where to steal a bit from. there isn't a thunk type
at runtime in jhc. so implementing deepSeq in the traditinal way is
fine, optimizing it in the way you describe is not.

> - (B) Once we have this recursive function, I'm advocating for an
> optimization
> which will make it cheap. Why can't we just steal a bit in the (GHC)
> info table,
> rather than mess with LSB of pointers, or have two info tables?
>
> Yes, in grin this information would need to be used at compile time
>  but the resulting code would be considerably faster. A deepSeq is
> a gift to the compiler from the programmer.

actually, it may be slower in jhc. reducing to normal form is not
necessarily a win in jhc, and if you do do it, you want to evaluate a
function as _early_ as possible, as in, as close to its definition
point. 'evals' are inlined to have a branch for every possible way a
value could come about, since you could deepseq pretty much any type of
object, you would end up with huge expanded evals, but worse, it would
cause all these thunks to be updatable when they didn't need to be.

imagine a use of a thunk, rather than evaluate it to WHNF, jhc will just
pull the components right out of the unevaluated thunk, if at some point
in the past it might have been deepsequed, you suddenly need a case
statement to determine whether it has been evaluated or not. knowing
something has not been evaluated is just as valuable as knowing it has
definitely been.

for a quick example, imagine you have this function and it is not
optimized away in core for some reason or another.

> mktup x y = (y,x)

> foo x = case x of (x,y) -> bar x y
> main = let ... in foo (mktup a b)

now we convert to grin

> fmktup x y = do
> return (CTuple y x)
>
> ffoo x = do
> y <- eval x
> update x y
> (CTuple a b) <- y
> bar a b
>
> main = do
> ...
> x <- Store (Fmktup a b)
> ffoo x

things starting with capital letters are tags, parenthesized things are
nodes on the heap.


now, we do eval-expansion in ffoo, points to analysis determines a
suspended Fmktup may be passed into ffoo.

> ffoo x = do
> x' <- fetch x
> y <- case x' of
> (Fmktup a b) ->
> fmktup a b
> update x y
> (CTuple a b) <- y
> bar a b

now, the case-of-case code motion (the y scrutinization is treated as a
simple case pulls the code into ffoo


> ffoo x = do
> x' <- fetch x
> case x' of
> (Fmktup a b) ->
> y <- fmktup a b
> update x y
> (CTuple a b) <- y
> bar a b

now, points-to analysis showed that nothing scrutinized this memory
location looking for a CTuple, therefor the update is uneeded.

also, fmktup is trivial so it is inlined

> ffoo x = do
> x' <- fetch x
> case x' of
> (Fmktup a b) ->
> y <- Return (CTuple b a)  -- inlined fmktup
> (CTuple a b) <- y
> bar a b

wrich trivially simplifise too

> ffoo x = do
> x' <- fetch x
> case x' of
> (Fmktup a b) ->
> bar b a
>
> ffoo x = do
> (Fmktup a b) <- fetch x
> bar b a

notice, there is no longer a concept of WHNF, Fmktup effectivly has
become the head normal form of that call due to standard optimization,
this type of transformation might happen to some suspended versions of
mktup, but not others, there is no way to tell from the heap location
itself whether it should be evaluated into WHNF or if uses are going to
pull its arguments right out of its closure or not.

deepseqing this case would only hurt performance as it would mean we couldn't
get rid of the 'update' or 'check if it is already a tuple' case. of
course, if mktup were some expensive call, then the opposite might be
true. in any case, deepseq is not always a win.

the above ffoo actually has another optimization waiting, arity raising,
since it knows x is always a pointer to a Fmktup, it pulls the arguments
out and passes 'a and b' to ffoo directly. since all function calls are
exp

Re: deeqSeq proposal

2006-04-10 Thread Lennart Augustsson

You're assuming some particular representation where there are
bits to steal.  I don't like this at all.  I think tying deepSeq
to some particular implementation techniques is a reall *BAD* idea.

Any function that is not defineable in (pure) Haskell should be viewed
with utmost suspicion.  The seq function is one of these.  At least
seq has simple denotational semantics, which can't be said for deepSeq.

I say, put deepSeq in a type class (which is what I've done when I need
it).

-- Lennart


Andy Gill wrote:


On Apr 10, 2006, at 2:25 AM, John Meacham wrote:


On Mon, Apr 10, 2006 at 10:10:18AM +0100, Simon Marlow wrote:

It's not *completely* straightforward to implement, at least in GHC, and
at least if you want to implement it in a modular way (i.e. without
touching lots of different parts of the system).

The obvious way to "add a bit to a closure" is to use the LSB of the
info pointer, which currently is always 0.  However, that means masking
out this bit every time you want to get the info pointer of a closure,
which means lots of changes to the runtime.  The price seems pretty
high.

An alternative is to have two info tables for every constructor, one
normal one and one "deepSeq'd", and the normal one probably needs to
point to the deepSeq'd version.  This doesn't require masking out any
bits, but it does increase code size (one extra info table + entry code
for every constructor, except possibly those that don't contain any
pointer fields), and one extra field in a constructor's info table.
Plus associated cache pollution.

Yet another alternative is to store fully evaluated data in a segregated
part of the heap.  The garbage collector could do this - indeed we
already do something similar, in that data that has no pointer fields is
kept separate.  Checking the "deepSeq" bit on a closure is then more
complicated - but this has the advantage that only the GC and storage
manager are affected.

None of these solutions is as simple and self-contained as I'd like :-(


it is unlikely it will even be possible to implement in jhc without
radical changes to its internals. there is just no where to attach a bit
to, and even if there were, there is no generic way to evaluate
something to WHNF, or even a concept of WHNF in final grin. (grin code
can look inside unevaluated closures, hopefully making the thunk
non-updatable)


I do not understand.

- (A) I'm calling for a recursive descent function that does seq. I could
write it in Haskell, for any specific type.  How is seq implemented jhs?

- (B) Once we have this recursive function, I'm advocating for an 
optimization
which will make it cheap. Why can't we just steal a bit in the (GHC) 
info table,

rather than mess with LSB of pointers, or have two info tables?

Yes, in grin this information would need to be used at compile time
 but the resulting code would be considerably faster. A deepSeq is
a gift to the compiler from the programmer.

Andy Gill

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-10 Thread Andy Gill


On Apr 10, 2006, at 2:25 AM, John Meacham wrote:


On Mon, Apr 10, 2006 at 10:10:18AM +0100, Simon Marlow wrote:
It's not *completely* straightforward to implement, at least in  
GHC, and

at least if you want to implement it in a modular way (i.e. without
touching lots of different parts of the system).

The obvious way to "add a bit to a closure" is to use the LSB of the
info pointer, which currently is always 0.  However, that means  
masking
out this bit every time you want to get the info pointer of a  
closure,

which means lots of changes to the runtime.  The price seems pretty
high.

An alternative is to have two info tables for every constructor, one
normal one and one "deepSeq'd", and the normal one probably needs to
point to the deepSeq'd version.  This doesn't require masking out any
bits, but it does increase code size (one extra info table + entry  
code

for every constructor, except possibly those that don't contain any
pointer fields), and one extra field in a constructor's info table.
Plus associated cache pollution.

Yet another alternative is to store fully evaluated data in a  
segregated

part of the heap.  The garbage collector could do this - indeed we
already do something similar, in that data that has no pointer  
fields is

kept separate.  Checking the "deepSeq" bit on a closure is then more
complicated - but this has the advantage that only the GC and storage
manager are affected.

None of these solutions is as simple and self-contained as I'd  
like :-(


it is unlikely it will even be possible to implement in jhc without
radical changes to its internals. there is just no where to attach  
a bit

to, and even if there were, there is no generic way to evaluate
something to WHNF, or even a concept of WHNF in final grin. (grin code
can look inside unevaluated closures, hopefully making the thunk
non-updatable)


I do not understand.

- (A) I'm calling for a recursive descent function that does seq. I  
could

write it in Haskell, for any specific type.  How is seq implemented jhs?

- (B) Once we have this recursive function, I'm advocating for an  
optimization
which will make it cheap. Why can't we just steal a bit in the (GHC)  
info table,

rather than mess with LSB of pointers, or have two info tables?

Yes, in grin this information would need to be used at compile time
 but the resulting code would be considerably faster. A deepSeq is
a gift to the compiler from the programmer.

Andy Gill

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-10 Thread John Meacham
On Mon, Apr 10, 2006 at 10:10:18AM +0100, Simon Marlow wrote:
> It's not *completely* straightforward to implement, at least in GHC, and
> at least if you want to implement it in a modular way (i.e. without
> touching lots of different parts of the system).
> 
> The obvious way to "add a bit to a closure" is to use the LSB of the
> info pointer, which currently is always 0.  However, that means masking
> out this bit every time you want to get the info pointer of a closure,
> which means lots of changes to the runtime.  The price seems pretty
> high.
> 
> An alternative is to have two info tables for every constructor, one
> normal one and one "deepSeq'd", and the normal one probably needs to
> point to the deepSeq'd version.  This doesn't require masking out any
> bits, but it does increase code size (one extra info table + entry code
> for every constructor, except possibly those that don't contain any
> pointer fields), and one extra field in a constructor's info table.
> Plus associated cache pollution.
> 
> Yet another alternative is to store fully evaluated data in a segregated
> part of the heap.  The garbage collector could do this - indeed we
> already do something similar, in that data that has no pointer fields is
> kept separate.  Checking the "deepSeq" bit on a closure is then more
> complicated - but this has the advantage that only the GC and storage
> manager are affected.
> 
> None of these solutions is as simple and self-contained as I'd like :-(

it is unlikely it will even be possible to implement in jhc without
radical changes to its internals. there is just no where to attach a bit
to, and even if there were, there is no generic way to evaluate
something to WHNF, or even a concept of WHNF in final grin. (grin code
can look inside unevaluated closures, hopefully making the thunk
non-updatable)

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-10 Thread Simon Marlow
On 07 April 2006 22:38, Andy Gill wrote:

> On Apr 7, 2006, at 3:59 AM, Rene de Visser wrote:
> 
>> Hello,
>> 
>> As deepSeq has a non local effect, I think it requires a non-local
>> source transformation to implement it. One option would be for the
>> compiler to create a second deepSeq version of every function
>> definition. 
>> 
>> e.g.
>> 
>> If the user defines a function f
>> 
>> f x = g h x
>> 
>> then the compile creates an additional function !!f
>> 
>> !!f x = temp `seq` temp
>>  where temp = !!g !!h x
>> 
>> which uses the compiler generated functions !!g and !!h.
>> 
>> It looks like library writers are increasingly doing this manually.
>> Creating a strict and non strict version of a number of the
>> functions provided. This would automate that.
>> 
>> Rene.
>> 
> 
> It depend on the semantics of deepSeq. If deepSeq just performs seq
> on all constructors recursively, then
> that can be implemented as a runtime primitive. If deepSeq is making
> all embedded partial applications
> strict, then yes this might be a non-local effect.
> 
> What are the semantics of !!(\ x -> ...)?
> 
> I am calling for the version of deepSeq/strict that evaluates all
> thunks, but does not strictify the arguments
> to partial application, because
>   - I believe this is straightforward to implement

It's not *completely* straightforward to implement, at least in GHC, and
at least if you want to implement it in a modular way (i.e. without
touching lots of different parts of the system).

The obvious way to "add a bit to a closure" is to use the LSB of the
info pointer, which currently is always 0.  However, that means masking
out this bit every time you want to get the info pointer of a closure,
which means lots of changes to the runtime.  The price seems pretty
high.

An alternative is to have two info tables for every constructor, one
normal one and one "deepSeq'd", and the normal one probably needs to
point to the deepSeq'd version.  This doesn't require masking out any
bits, but it does increase code size (one extra info table + entry code
for every constructor, except possibly those that don't contain any
pointer fields), and one extra field in a constructor's info table.
Plus associated cache pollution.

Yet another alternative is to store fully evaluated data in a segregated
part of the heap.  The garbage collector could do this - indeed we
already do something similar, in that data that has no pointer fields is
kept separate.  Checking the "deepSeq" bit on a closure is then more
complicated - but this has the advantage that only the GC and storage
manager are affected.

None of these solutions is as simple and self-contained as I'd like :-(

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-07 Thread Andy Gill


On Apr 7, 2006, at 3:59 AM, Rene de Visser wrote:


Hello,

As deepSeq has a non local effect, I think it requires a non-local  
source transformation to implement it. One option would be for the  
compiler to create a second deepSeq version of every function  
definition.


e.g.

If the user defines a function f

f x = g h x

then the compile creates an additional function !!f

!!f x = temp `seq` temp
 where temp = !!g !!h x

which uses the compiler generated functions !!g and !!h.

It looks like library writers are increasingly doing this manually.  
Creating a strict and non strict version of a number of the  
functions provided. This would automate that.


Rene.



It depend on the semantics of deepSeq. If deepSeq just performs seq  
on all constructors recursively, then
that can be implemented as a runtime primitive. If deepSeq is making  
all embedded partial applications

strict, then yes this might be a non-local effect.

What are the semantics of !!(\ x -> ...)?

I am calling for the version of deepSeq/strict that evaluates all  
thunks, but does not strictify the arguments

to partial application, because
 - I believe this is straightforward to implement
 - It does not change the semantics (any more than seq)
 - I will address the problems we are trying to solve by ad-hoc  
means at Galois.


Andy





___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-07 Thread Rene de Visser

Hello,

As deepSeq has a non local effect, I think it requires a non-local source 
transformation to implement it. One option would be for the compiler to 
create a second deepSeq version of every function definition.


e.g.

If the user defines a function f

f x = g h x

then the compile creates an additional function !!f

!!f x = temp `seq` temp
 where temp = !!g !!h x

which uses the compiler generated functions !!g and !!h.

It looks like library writers are increasingly doing this manually. Creating 
a strict and non strict version of a number of the functions provided. This 
would automate that.


Rene.


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-06 Thread Andy Adams-Moran
Lennart Augustsson wrote:
> Andy Adams-Moran wrote:
>>> The only thing you can do with non-functions is put them in the sin bin:
>>>
>>>   deepSeq :: a -> IO ()
>>
>> unsafeDeepSeq?
>>
>> I guess we don't want to expand the unsafe* vocabulary for Haskell'
>> though ...
> 
> What's wrong with
> deepSeeqIO :: a -> IO ()
> ?
> Then you can use unsafePerformIO if you want
> deepSeq :: a -> b -> b

Yes, quite right!  In the case of deepSeqIO, we do know precisely what
the safety condition is (as opposed to generic uses of unsafePerformIO
and its cousins), so maybe we want to call that out somehow.

A

-- 
Andy Adams-Moran Phone: 503.626.6616, x113
Galois Connections Inc.  Fax: 503.350.0833
12725 SW Millikan Way, Suite #290http://www.galois.com
Beaverton, OR 97005 [EMAIL PROTECTED]
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-06 Thread Lennart Augustsson

Andy Adams-Moran wrote:

The only thing you can do with non-functions is put them in the sin bin:

  deepSeq :: a -> IO ()


unsafeDeepSeq?

I guess we don't want to expand the unsafe* vocabulary for Haskell'
though ...


What's wrong with
deepSeeqIO :: a -> IO ()
?
Then you can use unsafePerformIO if you want
deepSeq :: a -> b -> b

-- Lennart
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-06 Thread John Meacham
On Thu, Apr 06, 2006 at 12:06:53AM -0700, Andy Gill wrote:
> Because deepSeq's cost to evaluate a list that will eventually be  
> required is linear.
> The maximum number of deepSeq calls (and recursive calls) you can do  
> over any
> structure is simply the number of nodes.
> 
> Consider:
> 
>   foldr (\ a as -> deepSeq (a : as)) [] $ some list
> 
> With the bit ==> one deepSeq per cons, then we hit the 'is-pre- 
> deepSeqd' bit.
> Without the bit ==> O(n^2)

Ah, I see, I was thinking of something else.

unfortunatly, this scheme or any scheme with changes to the run-time
representation will be impossible in jhc. there is no concept of WHNF
or thunks, let alone a generic way to evaluate them at run time in GRIN.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-06 Thread Fergus Henderson
On 05-Apr-2006, Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote:
> Andy Gill wrote:
> >- [various reasons for deepSeq]
> You left out the one that most interests me: ensuring that there are no 
> exceptions hiding inside a data structure.

Yes, that's important for fault isolation... see below.

On 03-Apr-2006, Andy Gill <[EMAIL PROTECTED]> wrote:
>
> - Fergus Henderson used deeqSeq in our Cryptol to FPGA compiler, between
> each pass, to make sure that we could assess which pass was taking
> what time.

Actually that wasn't the only reason why we needed deepSeq.

The other reason, at least as important, was fault isolation.  Like most
compilers, the Cryptol to FPGA compiler consists of a number of of
separate compilation phases.  When a problem in our compiler such as
an exception, heap or stack exhaustion, or an infinite loop occurs,
it is very helpful to be able to know in which phase that error occurred.

With lazy evaluation, this is tricky, since the execution of
all the different phases will be interleaved.  Any debugging
messages produced by "trace" from the different stages also
get interleaved.

The Cryptol to FPGA compiler will (in verbose mode) print out a message
when it starts each compilation stage.  We use deepSeq to ensure that each
stage has been fully evaluated before proceeding on to the next stage.
This allows us to isolate faults to a particular compilation stage.

I also used hyperSeq in previous Haskell programs before I joined Galois.
I've found the need for this to be quite common...

-- 
Fergus J. Henderson |  "I have always known that the pursuit
Galois Connections, Inc.|  of excellence is a lethal habit"
Phone: +1 503 626 6616  | -- the last words of T. S. Garp.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-06 Thread Andy Adams-Moran
Simon Marlow wrote:
> On 04 April 2006 19:53, Andy Adams-Moran wrote:
> 
>> Andy Gill wrote:
>>> let xs' () = 1 : 2 :  xs' ()
>>> let xs2 = xs'
>>>
>>> let xs = 1 : 2 : xs
>>>
>>> So deepSeq xs2 ==> _|_, but deepSeq xs ==> xs
> 
> Yes, and hence deepSeq isn't monotonic.  That's bad.

Yes, quite right.  In the standard denotational semantics, we can't even
express deepSeq (the fact that it's not monotonic is a consequence, or a
cause, depending on your PoV :-).  If the semantics of Haskell was
sensitive to sharing, and could distinguish between terms depending upon
their level of sharing (probably not a desirable feature of a Haskell
semantics), then deepSeq would be expressible and probably legit.

The above example points to the fact that we don't won't to allow
speculative use of deepSeq.  However, if the program is hyperstrict in a
term (i.e., demands all parts of the term, like all of the cases wherre
Andy wants to use it), then it's safe to use deepSeq ahead of demand.

Thus deepSeq begins to sound a little like unsafePerformIO: it's okay to
use when you satisfy certain pre-conditions.  At least we're able to
/specify/ the pre-conditions for deepSeq :-)

> The only thing you can do with non-functions is put them in the sin bin:
> 
>   deepSeq :: a -> IO ()

unsafeDeepSeq?

I guess we don't want to expand the unsafe* vocabulary for Haskell'
though ...

A

-- 
Andy Adams-Moran Phone: 503.626.6616, x113
Galois Connections Inc.  Fax: 503.350.0833
12725 SW Millikan Way, Suite #290http://www.galois.com
Beaverton, OR 97005 [EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-06 Thread Simon Marlow
On 05 April 2006 21:02, Ben Rudiak-Gould wrote:

> Andy Gill wrote:
>> - [various reasons for deepSeq]
> 
> You left out the one that most interests me: ensuring that there are
> no exceptions hiding inside a data structure.
> 
>> deepSeq :: a -> b -> b
> 
> This ties demand for the (fully evaluated) normal form of an
> expression to demand for the WHNF of a different expression, which is
> a bit weird. I think it's cleaner for the primitive to be your
> "strict", which ties demand for the normal form of an expression to
> demand for the WHNF of the same expression. In fact I'd argue that
> "deepSeq" should not be provided at all (though of course it can be
> defined by the user). The analogy with seq is a bit
> misleading---deepSeq is a lot less symmetric than seq. The
> expressions (x `deepSeq` y `deepSeq` z) and (strict x `seq` strict y
> `seq` z) are equivalent, but only the latter makes it clear that z
> doesn't get fully evaluated. 

Agreed - that pinpoints something that seemed a little strange to me
too.  strict should be the primitive; or maybe strict renamed to
deepSeq.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-06 Thread Andy Gill


On Apr 5, 2006, at 4:51 PM, John Meacham wrote:


On Wed, Apr 05, 2006 at 10:34:09AM -0500, Spencer Janssen wrote:

How about an implementation that sets the deepSeq'd bit *after* each
field has been successfully deepSeq'd?  deepSeq'ing a cyclic  
structure

would behave just like an infinite structure.


what would be the point of having a bit then?


Because deepSeq's cost to evaluate a list that will eventually be  
required is linear.
The maximum number of deepSeq calls (and recursive calls) you can do  
over any

structure is simply the number of nodes.

Consider:

  foldr (\ a as -> deepSeq (a : as)) [] $ some list

With the bit ==> one deepSeq per cons, then we hit the 'is-pre- 
deepSeqd' bit.

Without the bit ==> O(n^2)


in any case, we should talk about the meaning of deepseqing something,
not its implementation.

depth limited recursive seq seems like the best route to me.

John

--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-05 Thread John Meacham
On Wed, Apr 05, 2006 at 10:34:09AM -0500, Spencer Janssen wrote:
> How about an implementation that sets the deepSeq'd bit *after* each
> field has been successfully deepSeq'd?  deepSeq'ing a cyclic structure
> would behave just like an infinite structure.

what would be the point of having a bit then?

in any case, we should talk about the meaning of deepseqing something,
not its implementation.

depth limited recursive seq seems like the best route to me.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-05 Thread Ben Rudiak-Gould

Andy Gill wrote:

- [various reasons for deepSeq]


You left out the one that most interests me: ensuring that there are no 
exceptions hiding inside a data structure.



deepSeq :: a -> b -> b


This ties demand for the (fully evaluated) normal form of an expression to 
demand for the WHNF of a different expression, which is a bit weird. I think 
it's cleaner for the primitive to be your "strict", which ties demand for 
the normal form of an expression to demand for the WHNF of the same 
expression. In fact I'd argue that "deepSeq" should not be provided at all 
(though of course it can be defined by the user). The analogy with seq is a 
bit misleading---deepSeq is a lot less symmetric than seq. The expressions 
(x `deepSeq` y `deepSeq` z) and (strict x `seq` strict y `seq` z) are 
equivalent, but only the latter makes it clear that z doesn't get fully 
evaluated.


-- Ben

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-05 Thread Simon Peyton-Jones
| >> let xs' () = 1 : 2 :  xs' ()
| >> let xs2 = xs'
| >>
| >> let xs = 1 : 2 : xs
| >>
| >> So deepSeq xs2 ==> _|_, but deepSeq xs ==> xs

No, no.  deepSeq of either should be _|_.  

That's easy to achieve, even with the "marking" idea.  Simply do a
depth-first walk, but mark the node *after* traversing all its children,
not before. That way, if there's a cycle you'll diverge, as you should!
But you still get the effect that   
deepSeq (deepSeq x) = deepSeq x
(dynamically).

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-05 Thread Spencer Janssen
How about an implementation that sets the deepSeq'd bit *after* each
field has been successfully deepSeq'd?  deepSeq'ing a cyclic structure
would behave just like an infinite structure.


Spencer Janssen

On 4/4/06, Simon Marlow <[EMAIL PROTECTED]> wrote:
> On 30 March 2006 23:12, Andy Gill wrote:
>
> > Implementation:
> >
> > deepSeq (RAW_CONS  ... fields ) =
> >  if  == True
> >  then return  /* hey, we've already deepSeq'd this */
> >  else set  to True.
> >   deepSeq (field_1)
> >   ...
> >   deepSeq (field_n)
> > deepSEQ (REF/MVAR...) = return
>
> So deepSeq doesn't return _|_ when passed a cyclic structure?  This is a
> bad idea, because it lets you distinguish cyclic structures from
> infinite ones.  deepSeq has to behave like a function, regardless of its
> implementation.
>
> Cheers,
> Simon
> ___
> Haskell-prime mailing list
> Haskell-prime@haskell.org
> http://haskell.org/mailman/listinfo/haskell-prime
>
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-05 Thread Nils Anders Danielsson
On Tue, 04 Apr 2006, Andy Gill <[EMAIL PROTECTED]> wrote:

> let xs' () = 1 : 2 :  xs' ()
> let xs2 = xs'
>
> let xs = 1 : 2 : xs
>
> So deepSeq xs2 ==> _|_, but deepSeq xs ==> xs
>
> I appeal to the "morally correct reasoning"  argument .. If the program
> terminates, then it is still correct.

To avoid confusion I'd like to note that this has nothing to do with
the kind of moral correctness that I and some others wrote about
recently. (I guess that this is the downside of choosing a phrase like
that. :)

-- 
/NAD

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-05 Thread Simon Marlow
On 04 April 2006 19:53, Andy Adams-Moran wrote:

> Andy Gill wrote:
>> let xs' () = 1 : 2 :  xs' ()
>> let xs2 = xs'
>> 
>> let xs = 1 : 2 : xs
>> 
>> So deepSeq xs2 ==> _|_, but deepSeq xs ==> xs

Yes, and hence deepSeq isn't monotonic.  That's bad.

>> I appeal to the "morally correct reasoning"  argument .. If the
>> program terminates, then it is still correct. The deepSeq is an
>> assertion about the ability to represent the result in finite space.
> 
> I'm not convinced Simon's argument holds, as I don't think you can use
> deepSeq to write a Haskell function that will distinguish cyclic
> structures from infinite ones. If we can't do that, then we haven't
> really added any new semantic observational capability to the theory,
> so I think the "morally correct reasoning" argument holds.
> 
> Simon?

I think we should be able to rely on a bit more than "moral correctness"
:-)  Imagine writing a denotational semantics for deepSeq: you can't
without talking about representations, and we don't want to talk about
representations in denotational semantics, or in the Haskell language
definition.

The only thing you can do with non-functions is put them in the sin bin:

  deepSeq :: a -> IO ()

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread John Meacham
On Tue, Apr 04, 2006 at 02:53:36PM -0700, Andy Gill wrote:
> >Another issue is that being able to detect cyclic structures would  
> >make
> >it impossible to express deepSeq as a Haskell -> Haskell translation.
> >which is no good.
> 
> I am trying to understand this requirement. For the sake of what must
> all primitives be expressible as a Haskell -> Haskell translation?

Mainly it is an excellent proof that no undue burden is being placed on
any implementation, current or future. It also gives a way to reason
about its behavior and is a way to ensure you don't accidentally miss
defining any behavior or break referential transparency or any of the
other properties haskell programmers expect.

not that it has to be implemented via the translation of course. things
like DeepSeq and Typeable will most likely have optimized versions on
various compilers which is why I'd like to see the restriction that the
only way to create instances for these two classes is via the "deriving"
mechanism of the compiler. for the record, jhc can do a super optimized
Typeable, but not a DeepSeq, so will likely have to use the standard
class definition of DeepSeq (which it can already derive, under a
different name).

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread Andy Gill


On Apr 4, 2006, at 2:18 PM, John Meacham wrote:


On Tue, Apr 04, 2006 at 11:52:55AM -0700, Andy Adams-Moran wrote:
I'm not convinced Simon's argument holds, as I don't think you can  
use

deepSeq to write a Haskell function that will distinguish cyclic
structures from infinite ones. If we can't do that, then we haven't
really added any new semantic observational capability to the  
theory, so

I think the "morally correct reasoning" argument holds.


compiler optimizations don't necessarily preserve cyclic  
structures. in

practice they probably do, but there is no guarentee and we wouldn't
want to start making one.


This goes the heart of the problem. Haskell does not have a space
usage semantics. My job is taking something that is not specified,
and giving a Haskell program that has an understandable space usage  
profile.


As part of this, I want a way of assuring that a data structure is  
fully evaluated -

thunklessness we might call it.  And we already perform transformations
that may or may not change space behavior.

  let xs = [1..n]
  in sum xs / length xs

Inlining xs can give a version that runs in constant space, but the  
given

example will take O(n) space, given typical evaluation order.

another option would be for the DeepSeq class (or whatver) have a  
depth

limited version,

deepSeqSome :: DeepSeq a => Int -> a -> a

which would only traverse a limited depth into a structure.


Interesting idea!

 deepSeq = deepSeq maxInt ?

==> deepSeq *will* terminate on any cyclic structure
==> we can implement the cycle spotting optimization.

The only difference is how long before it might terminate,
not if it will terminate.

Another issue is that being able to detect cyclic structures would  
make

it impossible to express deepSeq as a Haskell -> Haskell translation.
which is no good.


I am trying to understand this requirement. For the sake of what must
all primitives be expressible as a Haskell -> Haskell translation?

Andy Gill

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread John Meacham
On Tue, Apr 04, 2006 at 11:52:55AM -0700, Andy Adams-Moran wrote:
> I'm not convinced Simon's argument holds, as I don't think you can use
> deepSeq to write a Haskell function that will distinguish cyclic
> structures from infinite ones. If we can't do that, then we haven't
> really added any new semantic observational capability to the theory, so
> I think the "morally correct reasoning" argument holds.

compiler optimizations don't necessarily preserve cyclic structures. in
practice they probably do, but there is no guarentee and we wouldn't
want to start making one.

another option would be for the DeepSeq class (or whatver) have a depth
limited version,

deepSeqSome :: DeepSeq a => Int -> a -> a

which would only traverse a limited depth into a structure.


Another issue is that being able to detect cyclic structures would make
it impossible to express deepSeq as a Haskell -> Haskell translation.
which is no good.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread Andy Adams-Moran
Andy Gill wrote:
> 
> On Apr 4, 2006, at 3:47 AM, Simon Marlow wrote:
> 
>> On 30 March 2006 23:12, Andy Gill wrote:
>>
>>> Implementation:
>>>
>>> deepSeq (RAW_CONS  ... fields ) =
>>>  if  == True
>>>  then return  /* hey, we've already deepSeq'd this */
>>>  else set  to True.
>>>   deepSeq (field_1)
>>>   ...
>>>   deepSeq (field_n)
>>> deepSEQ (REF/MVAR...) = return
>>
>> So deepSeq doesn't return _|_ when passed a cyclic structure?  This is a
>> bad idea, because it lets you distinguish cyclic structures from
>> infinite ones.  deepSeq has to behave like a function, regardless of its
>> implementation.
>>
>> Cheers,
>> Simon
> 
> Good observation, though pragmatically I'd rather the deepSeq to
> behave well on loops. Its the thunks I'm trying to remove, not
> the loop itself.
> 
> Allowing loops in the returned value gives the the beauty of laziness
> to construct the cycle, but the assurance that the structure does not
> contain
> thunks. A nice property, and a way to interact with laziness.
> 
> let xs' () = 1 : 2 :  xs' ()
> let xs2 = xs'
> 
> let xs = 1 : 2 : xs
> 
> So deepSeq xs2 ==> _|_, but deepSeq xs ==> xs
> 
> I appeal to the "morally correct reasoning"  argument .. If the program
> terminates, then it is still correct. The deepSeq is an assertion about
> the ability to represent the result in finite space.

I'm not convinced Simon's argument holds, as I don't think you can use
deepSeq to write a Haskell function that will distinguish cyclic
structures from infinite ones. If we can't do that, then we haven't
really added any new semantic observational capability to the theory, so
I think the "morally correct reasoning" argument holds.

Simon?

A

-- 
Andy Adams-Moran Phone: 503.626.6616, x113
Galois Connections Inc.  Fax: 503.350.0833
12725 SW Millikan Way, Suite #290http://www.galois.com
Beaverton, OR 97005 [EMAIL PROTECTED]
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread Andy Gill


On Apr 4, 2006, at 3:47 AM, Simon Marlow wrote:


On 30 March 2006 23:12, Andy Gill wrote:


Implementation:

deepSeq (RAW_CONS  ... fields ) =
 if  == True
 then return  /* hey, we've already deepSeq'd this */
 else set  to True.
  deepSeq (field_1)
  ...
  deepSeq (field_n)
deepSEQ (REF/MVAR...) = return


So deepSeq doesn't return _|_ when passed a cyclic structure?  This  
is a

bad idea, because it lets you distinguish cyclic structures from
infinite ones.  deepSeq has to behave like a function, regardless  
of its

implementation.

Cheers,
Simon


Good observation, though pragmatically I'd rather the deepSeq to
behave well on loops. Its the thunks I'm trying to remove, not
the loop itself.

Allowing loops in the returned value gives the the beauty of laziness
to construct the cycle, but the assurance that the structure does not  
contain

thunks. A nice property, and a way to interact with laziness.

let xs' () = 1 : 2 :  xs' ()
let xs2 = xs'

let xs = 1 : 2 : xs

So deepSeq xs2 ==> _|_, but deepSeq xs ==> xs

I appeal to the "morally correct reasoning"  argument .. If the program
terminates, then it is still correct. The deepSeq is an assertion about
the ability to represent the result in finite space.

You could imagine a timestamp implementation of deepSeq, though,
that would disallow loops, but allow for the caching of previous deepSeq
calls; the property I'm really after.

Andy Gill

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread Taral
On 4/4/06, Simon Marlow <[EMAIL PROTECTED]> wrote:
> So deepSeq doesn't return _|_ when passed a cyclic structure?  This is a
> bad idea, because it lets you distinguish cyclic structures from
> infinite ones.  deepSeq has to behave like a function, regardless of its
> implementation.

Why is this necessary?

--
Taral <[EMAIL PROTECTED]>
"You can't prove anything."
-- Gödel's Incompetence Theorem
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-04 Thread Simon Marlow
On 30 March 2006 23:12, Andy Gill wrote:

> Implementation:
> 
> deepSeq (RAW_CONS  ... fields ) =
>  if  == True
>  then return  /* hey, we've already deepSeq'd this */
>  else set  to True.
>   deepSeq (field_1)
>   ...
>   deepSeq (field_n)
> deepSEQ (REF/MVAR...) = return

So deepSeq doesn't return _|_ when passed a cyclic structure?  This is a
bad idea, because it lets you distinguish cyclic structures from
infinite ones.  deepSeq has to behave like a function, regardless of its
implementation.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-03 Thread Andy Gill



f x xs = let g y = x+y in map !! g xs


I'm imagining that this !! would not evaluate x, in much the same way as

!!(const 42 undefined)

==>

42

The program generating the deepSeq argument is free to use laziness
as much as it wants, just the (non functional parts of the) result
are completely evaluated.

Andy

On Apr 3, 2006, at 4:16 AM, Simon Peyton-Jones wrote:


Interesting idea.

What would you expect to happen here?

f x xs = let g y = x+y in map !! g xs

Here I'm evaluating the function g hyperstrictly before the call to  
map.

Does x, the free variable in g's function closure, get evaluated?

From an implementation point of view, you could imagine that  
hyperstrict

evaluation would pull apart function closures, as well as data
structures.  But I'm not sure you could give that a sensible
denotational semantics.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Andy Gill
| Sent: 30 March 2006 23:12
| To: haskell-prime@haskell.org
| Cc: Laura McKinney
| Subject: deeqSeq proposal
|
| For the reasons talked about in previous posts, I'd like to  
propose a

| deepSeq
| for Haskell'.
|
|   - It provides a mechanism to allow an effective, systematic
| tracking down of
|   a class of space leaks.
|   - It provides a mechanism to simply stomp on a class of space  
leaks.

|   - It avoids the user having to explicitly declare instances for a
| homebrew deepSeq
|for every type in your program.
| - It has a declarative feel; this expression is hyper strict.
| - Is a specification of strictness.
| - It will open up various optimization opportunities, avoiding
| building thunks.
| (I dont talk about this more, but I'm happy to elaborate)
| - It can have an efficient implementation, or a simple (slow)
| implementation.
| (The fast implementation one can be used to stomp space leaks,
| the slow one can help find the same leaks.)
|
| What I would like to propose for Haskell' are four things:
|
| (Essential) Add a deepSeq function into Haskell'
|
| deepSeq :: a -> b -> b
|
|  - Don't really care if its in a class or not; would prefer not
for
| the reasons John Hughes talked about.
|  - This would deepSeq all its children for regular constructors.
|  - deepSeq would not indirect into IO or MVar.
|  - functions would be evaluated to (W?)HNF.
|  - IO, ST are functions under the hood.
|
| (Easy) Add a $!! function, and a strict function
|
| f $!! a = a `deepSeq` f a
| strict a = a `deepSeq` a
|
| (Nice) Add a !! notation, where we have ! in datatypes.
|
| data StrictList a = Cons (!!a) (!!StrictList a) | Nil
|
| (Perhaps) Add a way of making *all* the fields strict/hyperstrict.
|
| data !!StrictList a = ..,
|
| We could also do this for !
|
| --
|
| Implementation:
|
| deepSeq (RAW_CONS  ... fields ) =
|  if  == True
|  then return  /* hey, we've already deepSeq'd this */
|  else set  to True.
|   deepSeq (field_1)
|   ...
|   deepSeq (field_n)
| deepSEQ (REF/MVAR...) = return
|
| So we only deepSeq any specific constructor once! Sorta like lazy
| evaluation :-)
| We'd need to catch exceptions, unset the is_deep_seq'd_bit, so that
any
| subsequent call of deepSeq would also have the option of raising the
| exception.
|
| So,
|
|   - How easy is this to add to the compilers? It looks pretty simple
| to me,
| and would provide huge bang-for-buck for Galois.
|   - Any alternatives to the key concern; stomping on space leaks.
| (This proposal is orthogonal to the seq/Class discussion)
|
| Andy Gill
| Galois
|
| ___
| Haskell-prime mailing list
| Haskell-prime@haskell.org
| http://haskell.org/mailman/listinfo/haskell-prime


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-03 Thread Robert Dockins


On Apr 3, 2006, at 7:16 AM, Simon Peyton-Jones wrote:


Interesting idea.

What would you expect to happen here?

f x xs = let g y = x+y in map !! g xs

Here I'm evaluating the function g hyperstrictly before the call to  
map.

Does x, the free variable in g's function closure, get evaluated?

From an implementation point of view, you could imagine that  
hyperstrict

evaluation would pull apart function closures, as well as data
structures.  But I'm not sure you could give that a sensible
denotational semantics.



Indeed, the semantics would be troublesome.  I'd much prefer to see  
the semantics of hyperstrict (what a great term!) functions defined  
with a nice conjugation property, ie, if 'strict' is a partial  
function (forall a. a -> a) then for g::(b -> c)


strict g === strict . g . strict

Which (I believe) should do what you would expect for multi-argument  
functions; all arguments are evaluated hyperstrict, g is applied, and  
then the result is evaluated hyperstrict.

Easy to specify and reason about.





Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Andy Gill
| Sent: 30 March 2006 23:12
| To: haskell-prime@haskell.org
| Cc: Laura McKinney
| Subject: deeqSeq proposal
|
| For the reasons talked about in previous posts, I'd like to  
propose a

| deepSeq
| for Haskell'.
|
|   - It provides a mechanism to allow an effective, systematic
| tracking down of
|   a class of space leaks.
|   - It provides a mechanism to simply stomp on a class of space  
leaks.

|   - It avoids the user having to explicitly declare instances for a
| homebrew deepSeq
|for every type in your program.
| - It has a declarative feel; this expression is hyper strict.
| - Is a specification of strictness.
| - It will open up various optimization opportunities, avoiding
| building thunks.
| (I dont talk about this more, but I'm happy to elaborate)
| - It can have an efficient implementation, or a simple (slow)
| implementation.
| (The fast implementation one can be used to stomp space leaks,
| the slow one can help find the same leaks.)
|
| What I would like to propose for Haskell' are four things:
|
| (Essential) Add a deepSeq function into Haskell'
|
| deepSeq :: a -> b -> b
|
|  - Don't really care if its in a class or not; would prefer not
for
| the reasons John Hughes talked about.
|  - This would deepSeq all its children for regular constructors.
|  - deepSeq would not indirect into IO or MVar.
|  - functions would be evaluated to (W?)HNF.
|  - IO, ST are functions under the hood.
|
| (Easy) Add a $!! function, and a strict function
|
| f $!! a = a `deepSeq` f a
| strict a = a `deepSeq` a
|
| (Nice) Add a !! notation, where we have ! in datatypes.
|
| data StrictList a = Cons (!!a) (!!StrictList a) | Nil
|
| (Perhaps) Add a way of making *all* the fields strict/hyperstrict.
|
| data !!StrictList a = ..,
|
| We could also do this for !
|
| --
|
| Implementation:
|
| deepSeq (RAW_CONS  ... fields ) =
|  if  == True
|  then return  /* hey, we've already deepSeq'd this */
|  else set  to True.
|   deepSeq (field_1)
|   ...
|   deepSeq (field_n)
| deepSEQ (REF/MVAR...) = return
|
| So we only deepSeq any specific constructor once! Sorta like lazy
| evaluation :-)
| We'd need to catch exceptions, unset the is_deep_seq'd_bit, so that
any
| subsequent call of deepSeq would also have the option of raising the
| exception.
|
| So,
|
|   - How easy is this to add to the compilers? It looks pretty simple
| to me,
| and would provide huge bang-for-buck for Galois.
|   - Any alternatives to the key concern; stomping on space leaks.
| (This proposal is orthogonal to the seq/Class discussion)
|
| Andy Gill
| Galois



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: deeqSeq proposal

2006-04-03 Thread Simon Peyton-Jones
Interesting idea.

What would you expect to happen here?

f x xs = let g y = x+y in map !! g xs

Here I'm evaluating the function g hyperstrictly before the call to map.
Does x, the free variable in g's function closure, get evaluated? 

>From an implementation point of view, you could imagine that hyperstrict
evaluation would pull apart function closures, as well as data
structures.  But I'm not sure you could give that a sensible
denotational semantics.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Andy Gill
| Sent: 30 March 2006 23:12
| To: haskell-prime@haskell.org
| Cc: Laura McKinney
| Subject: deeqSeq proposal
| 
| For the reasons talked about in previous posts, I'd like to propose a
| deepSeq
| for Haskell'.
| 
|   - It provides a mechanism to allow an effective, systematic
| tracking down of
|   a class of space leaks.
|   - It provides a mechanism to simply stomp on a class of space leaks.
|   - It avoids the user having to explicitly declare instances for a
| homebrew deepSeq
|for every type in your program.
| - It has a declarative feel; this expression is hyper strict.
| - Is a specification of strictness.
| - It will open up various optimization opportunities, avoiding
| building thunks.
| (I dont talk about this more, but I'm happy to elaborate)
| - It can have an efficient implementation, or a simple (slow)
| implementation.
| (The fast implementation one can be used to stomp space leaks,
| the slow one can help find the same leaks.)
| 
| What I would like to propose for Haskell' are four things:
| 
| (Essential) Add a deepSeq function into Haskell'
| 
| deepSeq :: a -> b -> b
| 
|  - Don't really care if its in a class or not; would prefer not
for
| the reasons John Hughes talked about.
|  - This would deepSeq all its children for regular constructors.
|  - deepSeq would not indirect into IO or MVar.
|  - functions would be evaluated to (W?)HNF.
|  - IO, ST are functions under the hood.
| 
| (Easy) Add a $!! function, and a strict function
| 
| f $!! a = a `deepSeq` f a
| strict a = a `deepSeq` a
| 
| (Nice) Add a !! notation, where we have ! in datatypes.
| 
| data StrictList a = Cons (!!a) (!!StrictList a) | Nil
| 
| (Perhaps) Add a way of making *all* the fields strict/hyperstrict.
| 
| data !!StrictList a = ..,
| 
| We could also do this for !
| 
| --
| 
| Implementation:
| 
| deepSeq (RAW_CONS  ... fields ) =
|  if  == True
|  then return  /* hey, we've already deepSeq'd this */
|  else set  to True.
|   deepSeq (field_1)
|   ...
|   deepSeq (field_n)
| deepSEQ (REF/MVAR...) = return
| 
| So we only deepSeq any specific constructor once! Sorta like lazy
| evaluation :-)
| We'd need to catch exceptions, unset the is_deep_seq'd_bit, so that
any
| subsequent call of deepSeq would also have the option of raising the
| exception.
| 
| So,
| 
|   - How easy is this to add to the compilers? It looks pretty simple
| to me,
| and would provide huge bang-for-buck for Galois.
|   - Any alternatives to the key concern; stomping on space leaks.
| (This proposal is orthogonal to the seq/Class discussion)
| 
| Andy Gill
| Galois
| 
| ___
| Haskell-prime mailing list
| Haskell-prime@haskell.org
| http://haskell.org/mailman/listinfo/haskell-prime
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-03-30 Thread John Meacham
On Thu, Mar 30, 2006 at 02:12:29PM -0800, Andy Gill wrote:
>  - How easy is this to add to the compilers? It looks pretty simple  
> to me,

jhc already has it by accident, it uses DrIFT for implementing its
deriving methods which has had deepSeq deriving for a while. (though, it
calls it 'rnf' for reduce to normal form)

>and would provide huge bang-for-buck for Galois.

out of curiosity, do you use tools like DrIFT or TH to auto-generate
DeepSeq instances for you?

>  - Any alternatives to the key concern; stomping on space leaks.
>(This proposal is orthogonal to the seq/Class discussion)

One thing, in order to deepSeq arbitrary types, it would mean heap
locations need to be self-describing, which is not true in general for
some haskell implementations. (the tag might have been unboxed away for
instance, or you only have an opaque code pointer representation)

requiring a typeclass DeepSeq a => would solve this problem as the
"shape" of the type will be carried in the typeclass, either as a
method(ghc) or a type parameter (in jhc) or discarded on implementations
that don't need it. (yhc I am guessing?)

So what I'd like to see is for the compiler to be able to auto-derive a
DeepSeq instance so compilers are free to choose the best implementation
method. incidentally, I'd like to see the same thing for Typeable.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime