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-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-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 is_deep_seq'd_bit ... fields ) =
 if is_deep_seq'd_bit == True
 then return  /* hey, we've already deepSeq'd this */
 else set is_deep_seq'd_bit 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 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


deeqSeq proposal

2006-03-30 Thread Andy Gill
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 is_deep_seq'd_bit ... fields ) =
if is_deep_seq'd_bit == True
then return  /* hey, we've already deepSeq'd this */
else set is_deep_seq'd_bit 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


Re: seq as a class method

2006-03-29 Thread Andy Gill

John, et. al.,

I'd rather just use a polymorphic function, but would having some
sort of ... notation in class contexts help?

sort (Eq a,_) = [a] - [a]

Which means that we need at least the Eq a, but perhaps more.
See #86 http://hackage.haskell.org/trac/haskell-prime/wiki/ 
PartialTypeAnnotations


In terms of seq, and deepSeq, here is a space leak problem I often  
need to solve.


Imagine a function

cpuStep :: CPUState - CPUState

where the CPUState is a large structure, for (say) the 68000 register  
file, a

and also contains information about a level-1 cache.

I want to run for 100,000 instructions.

runCPU :: Int -  CPUState - CPUState
runCPU 0 state = state
runCPU n state = runCPU (n-1) (cpuStep state)

My job is to make this run in approximately constant space; a  
reasonable request.


Well, we can add a seq to the modified state:

runCPU n state = state'` `seq` runCPU (n-1) state'
  where
state' = cpuStep state

But the thing still leaks like crazy. *I've seen this again and again.*
Some internal piece of data inside CPUState depends on
the value of another piece of CPUState from the previous
iteration.

At Galois, we often fix this with a deepSeq (actually using NFData).

runCPU n state = state'` `depSeq` runCPU (n-1) state'
  where
state' = cpuStep state

Great, the leak is gone, but now each step takes 100s of times longer!
So we descend into the implementation of cpuStep, turning on-and-off
deepSeq's until we have constant space version. Ugg. Then someone
makes a small change to our implementation of cpuStep, and re-introduces
the leak...

We have used a version of deepSeq that that looked up a table
at runtime, to find what to make strict and what not to make strict.
This made for rapid binary searching to find the problem thunk(s),
but ugly unsafePerformIOs behind the derivings, and non-standard
hacks. But like runtime flags for asserts, we could have runtime
arguments for seq/deepSeq pragmas.

Questions
 - Does anyone have any better suggestions of how to fix this real  
issue?

 - Could a polymorphic deepSeq allow for a implementation that does
   not do repeated walked over pre-evaluated data?

Andy Gill

On Mar 24, 2006, at 5:40 AM, John Hughes wrote:



it seems that there is not yet a ticket about putting seq into a  
type class (again).


In my opinion, having seq available for every type is a serious  
flaw.  One problem is that the law f = \x - f x doesn't hold  
anymore since the equation is false for f = _|_.  There was also a  
discussion on one of the mailing lists some time ago which  
revealed that the Monad instance for IO doesn't satisfy the monad  
laws because of the availability of seq for IO, I think.


In addition, the automatic definition of seq for every type can  
make implementation details visible which were thought of as  
completely hidden.  For example, it might make a difference  
whether one uses data or newtype for a one-alternative-one-field  
datatype, even if the data constructor is hidden.


I therefore propose to declare a class like this:

class Seq a where
seq :: a - b - b


Oh please, no.

This sounds like a good idea in principle, but it was a nightmare  
in practice.


First, the implementation details and the difference between _|_  
and const _|_
make a difference to space behaviour, and one needs a way to  
control that.

Hiding the differences can make space leaks *impossible* to fix.

Secondly, the need to insert and remove Seq contexts from type  
signatures during
space debugging is a major overhead. In my practical experience  
such overheads made
some desirable refactorings impossible to carry out in the time  
available for the

project.

Thirdly, the laws one loses are nearly true anyway, and that's  
very often
enough. See Fast and loose reasoning is morally correct, POPL  
2006. We
don't need to give up anything to make reasoning *as though* such  
laws held

sound, in most cases.

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: Strict Haskell debate

2006-02-17 Thread Andy Gill


On Feb 17, 2006, at 3:30 PM, Ashley Yakeley wrote:


Andy Gill wrote:
I'd like to see a way of enforcing return strictness, that is  
where you

have confidence that what a function is returning is fully evaluated.
Imagine a function hstrict;
 hstrict :: a - a


Is this like deepseq, that strictly evaluates internal structure  
using seq?


yes. it is.




With hstrict you can write functions in the style.
fun f a b c = hstrict $ 
  where
...
...


But surely fun can return the unevaluated thunk (hstrict x)? Since  
hstrict has not yet been called, it can't do its strictifying  
magic, whatever that is.




No. hstrict will always be called before returning. Evaluation does
not return thunks, they get created by lets/where (at the core level),
not by function application/evaluation.

Andy Gill

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