FDs and confluence

2006-04-10 Thread Ross Paterson
(see the FunctionalDependencies page for background omitted here)

One of the problems with the relaxed coverage condition implemented
by GHC and Hugs is a loss of confluence.  Here is a slightly cut-down
version of Ex. 18 from the FD-CHR paper:

class B a b | a - b
class C a b c | a - b

instance B a b = C [a] b Bool

Starting from a constraint set C [a] b Bool, C [a] c d, we have two
possible reductions:

1) C [a] b Bool, C [a] c d
= c = b, C [a] b Bool, C [a] b d   (use FD on C)
= c = b, B a b, C [a] b d  (reduce instance)

2) C [a] b Bool, C [a] c d
= C a b, C [a] c d (reduce instance)

The proposed solution was to tighten the restrictions on instances to
forbid those like the above one for C.  However there may be another
way out.

The consistency condition implies that there cannot be another
instance C [t1] t2 t3: a substitution unifying a and t1 need not
unify b and t2.  Thus we could either

1) consider the two constraint sets equivalent, since they describe
   the same set of ground instances, or

2) enhance the instance improvement rule: in the above example, we
   must have d = Bool in both cases, so both reduce to

c = b, d = Bool, B a b

   More precisely, given a dependency X - Y and an instance C t, if
   tY is not covered by tX, then for any constraint C s with sX = S tX
   for some substitution S, we can unify s with S t.

   We would need a restriction on instances to guarantee termination:
   each argument of the instance must either be covered by tX or be
   a single variable.  That is less restrictive (and simpler) than
   the previous proposal, however.

Underlying this is an imbalance between the two restrictions on instances.
In the original version, neither took any account of the context of the
instance declaration.  The implementations change this for the coverage
condition but not the consistency condition.  Indeed the original form of
the consistency condition is necessary for the instance improvement rule.

___
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


FDs and confluence

2006-04-10 Thread Martin Sulzmann
Ross Paterson writes:
  (see the FunctionalDependencies page for background omitted here)
  
  One of the problems with the relaxed coverage condition implemented
  by GHC and Hugs is a loss of confluence.  Here is a slightly cut-down
  version of Ex. 18 from the FD-CHR paper:
  
   class B a b | a - b
   class C a b c | a - b
  
   instance B a b = C [a] b Bool
  
  Starting from a constraint set C [a] b Bool, C [a] c d, we have two
  possible reductions:
  
  1) C [a] b Bool, C [a] c d
   = c = b, C [a] b Bool, C [a] b d   (use FD on C)
   = c = b, B a b, C [a] b d  (reduce instance)
  
  2) C [a] b Bool, C [a] c d
   = C a b, C [a] c d (reduce instance)
   ^
should be  B a b


  The proposed solution was to tighten the restrictions on instances to
  forbid those like the above one for C.  However there may be another
  way out.
  
  The consistency condition implies that there cannot be another
  instance C [t1] t2 t3: a substitution unifying a and t1 need not
  unify b and t2.  Thus we could either
  
  1) consider the two constraint sets equivalent, since they describe
 the same set of ground instances, or
  

That's troublesome for (complete) type inference.
Two constraint stores are equivalent if they are equivalent
for any satisfying ground instance? How to check that?

  2) enhance the instance improvement rule: in the above example, we
 must have d = Bool in both cases, so both reduce to
  
   c = b, d = Bool, B a b
  
 More precisely, given a dependency X - Y and an instance C t, if
 tY is not covered by tX, then for any constraint C s with sX = S tX
 for some substitution S, we can unify s with S t.
  

I'm not following you here, you're saying?

rule C [a] b d == d=Bool

Are you sure that you're not introducing further critical pairs?

 We would need a restriction on instances to guarantee termination:
 each argument of the instance must either be covered by tX or be
 a single variable.  That is less restrictive (and simpler) than
 the previous proposal, however.
  
  Underlying this is an imbalance between the two restrictions on instances.
  In the original version, neither took any account of the context of the
  instance declaration.  The implementations change this for the coverage
  condition but not the consistency condition.  Indeed the original form of
  the consistency condition is necessary for the instance improvement rule.
  

Maybe, you found a simple solution (that would be great)
but I'not 100% convinced yet.


The problem you're addressing only arises for non-full FDs.
Aren't such cases very rare in practice?

Martin


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


RE: Signals + minimal proposal

2006-04-10 Thread Simon Marlow
On 09 April 2006 16:02, Marcin 'Qrczak' Kowalczyk wrote:

 Simon Marlow [EMAIL PROTECTED] writes:
 
 That sounds hard to program with - surely you want to stop the
 program in order to clean up?  Otherwise the program is going to
 continue working, generating more exit handlers, and we might never
 get to exit. 
 
 Here is how I've done it in Kogut:
 
 An equivalent of Haskell's exitWith simply throws a predefined
 exception. When an unhandled exception reaches the toplevel, this
 exception is treated specially and is not printed with a stack trace.
 Exceptions caused by system signals are special too.
 
 There is a central list of registered exit handlers. On program exit
 each handler is run once. Handlers registered during this cleanup are
 run too. Any exceptions thrown from handlers are caught and ignored.
 This happens after printing a stack trace from an unhandled exception,
 just before shutting down the runtime and exiting.
 
 One of exit handlers cancels all other threads (except those which
 has been garbage collected) and waits until they finish. New threads
 started during this cleanup are canceled too.

Can a thread be GC'd without being sent an exception first?

How does cancelling a thread differ from sending it an exception?

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


Re: FDs and confluence

2006-04-10 Thread Ross Paterson
On Mon, Apr 10, 2006 at 02:39:18PM +0100, Claus Reinke wrote:
 instance B a b = C [a] b Bool
 
 Starting from a constraint set C [a] b Bool, C [a] c d,
 
 there is no implication that d=Bool
 (you could add: 'instance B a b = C [a] b Char' without violating
 FD consistency).

These instances (alpha-renamed):

instance B a1 b1 = C [a1] b1 Bool
instance B a2 b2 = C [a2] b2 Char

violate the consistency condition: a substitution that unifies a1 and
a2 need not unify b1 and b2, because the consistency condition makes
no mention of the contexts.  (If it did, the instance improvement rule
would be invalid.)

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


Re: MPTCs and functional dependencies

2006-04-10 Thread Henrik Nilsson

Hi all,

Manuel Chakravarty wrote:
  My conclusion is that we should not include FDs or ATs into the
  standard at the moment.  Standardising FDs as a stopgap measure may
  easily put us into the same situation that we are having with
  records at the moment.
  Nobody is really happy with it, but we don't dare to change it
  either.

Martin Sulzmann

 The situation here is clearly different. Whatever comes next
 (after FDs) will be a conservative extension. So, standardising
 FDs is a good thing because they have proven to be a useful (somewhat
 essential for MPTCs) feature. Hence, I will go with Simon:
 H' should have MPTC + FDs, but not ATs.

I basically agree with Simon PJ and Martin:

MPTCs are necessary for H', and MPTCs pretty much necessitates
at least some limited form of FD/AT.

Thus I view FD/AT as so important, that I think it is a secondary
concern if it ends up being a stop gap measure.

Moreover, it seems to me that FD/AT declarations in practical
applications amounts to very little code. Thus, the likely work
impact if FD/AT is completely replaced with some other mechanism
providing the same functionality should be very limited.

This is unlike records, say, where record notation is likely to be
used pretty much throughout an application.

Also, the alternative of NOT having FD/AT would seem to lead
to rather convoluted solutions in many cases, so the work of
adapting non FD/AT MPTC code to an hypotetical H'' setting
where an FD/AT replacement is available, is potentially quite
big.

But of couse, the above discussion on likely change
impact is just my gut feeling.

My key argument is that MPTCs and thus some form  of FDs/ATs
are really important in practice.

All the best,

/Henrik

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]


This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

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


RE: FDs and confluence

2006-04-10 Thread Simon Peyton-Jones
Interesting!  It'd be great if you've found a simpler more uniform rule.
(Which you seem to be getting rather good at.)Let's see if you can
convince Martin, first, and then articulate the proposed rules.  I'll
look fwd to that.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Ross Paterson
| Sent: 10 April 2006 09:53
| To: haskell-prime@haskell.org
| Subject: FDs and confluence
| 
| (see the FunctionalDependencies page for background omitted here)
| 
| One of the problems with the relaxed coverage condition implemented
| by GHC and Hugs is a loss of confluence.  Here is a slightly cut-down
| version of Ex. 18 from the FD-CHR paper:
| 
|   class B a b | a - b
|   class C a b c | a - b
| 
|   instance B a b = C [a] b Bool
| 
| Starting from a constraint set C [a] b Bool, C [a] c d, we have two
| possible reductions:
| 
| 1) C [a] b Bool, C [a] c d
|   = c = b, C [a] b Bool, C [a] b d   (use FD on C)
|   = c = b, B a b, C [a] b d  (reduce instance)
| 
| 2) C [a] b Bool, C [a] c d
|   = C a b, C [a] c d (reduce instance)
| 
| The proposed solution was to tighten the restrictions on instances to
| forbid those like the above one for C.  However there may be another
| way out.
| 
| The consistency condition implies that there cannot be another
| instance C [t1] t2 t3: a substitution unifying a and t1 need not
| unify b and t2.  Thus we could either
| 
| 1) consider the two constraint sets equivalent, since they describe
|the same set of ground instances, or
| 
| 2) enhance the instance improvement rule: in the above example, we
|must have d = Bool in both cases, so both reduce to
| 
|   c = b, d = Bool, B a b
| 
|More precisely, given a dependency X - Y and an instance C t, if
|tY is not covered by tX, then for any constraint C s with sX = S tX
|for some substitution S, we can unify s with S t.
| 
|We would need a restriction on instances to guarantee termination:
|each argument of the instance must either be covered by tX or be
|a single variable.  That is less restrictive (and simpler) than
|the previous proposal, however.
| 
| Underlying this is an imbalance between the two restrictions on
instances.
| In the original version, neither took any account of the context of
the
| instance declaration.  The implementations change this for the
coverage
| condition but not the consistency condition.  Indeed the original form
of
| the consistency condition is necessary for the instance improvement
rule.
| 
| ___
| 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: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-10 Thread John Meacham
On Mon, Apr 10, 2006 at 02:58:20PM +0100, Simon Marlow wrote:
 Suppose I want to do some action with a temporary file:
 
bracket
newTempFile
(\f - removeTempFile f)
(\f - doSomethingWith f)
 
 Under your scheme, this code doesn't get to remove its temporary file on
 exit, unless I explicitly add an exit handler that throws an exception
 to the current thread.
 
 I think code like the above should just work.  Furthermore, I think it
 should be an invariant that a thread is never discarded or killed, only
 sent an exception.  Otherwise, how else can I acquire a resource and
 guarantee to release it when either an exception is raised, the program
 exits, or the computation completes?

you ask the system to send you an exception on exit.

 
 According to your definition of exitWith above, I can't both raise an
 exception *and* exit in the same thread.  If I register an onExit
 handler that throws an exception to the current thread, things go wrong
 if the current thread also calls exitWith.  Also, you couldn't call
 exitWith while holding an MVar, if the handlers need access to the same
 MVar.

hrm? nothing goes wrong. it is the same as calling 'throw' in the
current thread.

I don't see how it is unsafe, it is always unsafe to call a routine that
needs an MVar you already have held open. you don't call exitWith by
accident. There is always 'forkIO exitFailure' in any case. 

 You didn't show WithTemporaryExitHandler, which complicates things quite
 a bit.

it is uneeded, only a utility routine, I just didn't want to show the
bookkeeping in the handler list to allow deletion of elements as it
wasn't important to the scheme. any thread that wants to do bracket
style cleanup just asks to be thrown an Exit exception and uses the
standard 'bracket' etc.. routines.

 Also, your implementation has a race condition - a thread might add
 another exit handler after the swapMVar.

that is why it is in a swapMVar loop, processing batch's of handlers. at
some point, you just gotta accept that another thread didn't get its
handler in on time, after all, if things were scheduled differently it
might not have gotten there. mainly I wanted to make sure no handlers
registered from within other handlers got lost, as those should run to
completion being synchronously regiseterd from the handlers point of
view.

 I think we can probably agree on one thing: exitWith should raise an
 exception:
 
   exitWith e = throw (ExitException e)

I disagree :)

throwTo and throw should raise exceptions, exit should quit the program.
though, perhaps we just need another function in the middle.

AFAICT, what you are proposing is the same as mine but with

forkIO being implemented as 

forkIO action = forkIO' action' where 
action' = do
myThreadId = onExit . throwTo PleaseExit
action

I just want to have control as to whether that throw me an exception
exit handler gets added and not have the implementation wait on my
thread to clean up before it can exit if it has nothing special to clean
up and might be deep in foreign calls.

perhaps if there were just a flag on each thread saying whether they
wanted to recieve exit message? though. I still don't like the idea of
exitWith throwing anything, just feels really dirty. though, if there
were a 'runExitHandlers' routine, what I want can be simulated by
'runExitHandlers  exitWith_ foo'


 This isn't inconsistent with your proposal, and I think it's
 unambiguously better.  The top-level exception handler catches
 ExitException and performs the required steps (running handlers, calling
 exit_).  As you said, you need a top-level exception handler anyway,
 this is just a small change to your proposal, moving the exit actions to
 the top-level exception handler.

but that means you have to wait until the thread with that top level
exception handler becomes runnable. which could take arbitrary time if
it is in a foreign call. I'd rather stuff be taken care of on the
current thread (since we know we are runnable since we just ran
exitWith), or on some new exit only thread. as if exitwith behaved as if
it were called (forkIO $ exitWith)

it just seems odd for your global system exit code to be hidden deep at
the base of a certain threads stack somewhere. I don't mind so much
exceptions being thrown everywhere to give things a chance to clean up,
so much as the requirement we wait for it to fall off the distinguished
'main thread' before the program can actually quit.

by default fork 
  3. simple rules. expressable in pure haskell.
  4. can quit immediatly on a SIGINT since the exitWith routine runs on
  whatever thread called exit, rather than throwing responsibility back
  to the other threads which might be stuck in a foreign call. (unless
  you explicitly ask it to)
 
 Don't understand this one - it certainly doesn't help with SIGINT in
 GHC.

when the signal occurs ghc sends a byte down a pipe, listening thread
reads that and calls 

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 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 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
explicit in grin, we just go through and modify each call site
accordingly.


John




--

Re: collecting requirements for FDs

2006-04-10 Thread Jim Apple
On 4/10/06, Ross Paterson [EMAIL PROTECTED] wrote:
 What other libraries should Haskell' support, and what are their
 requirements?

http://hackage.haskell.org/trac/ghc/wiki/CollectionClassFramework

There are two range arguments here, IIUC.

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