Re: Defaults for superclass methods

2006-04-13 Thread Dave Menendez
John Meacham writes:

> On Tue, Apr 11, 2006 at 11:35:09AM +0100, Simon Marlow wrote:
> > On 11 April 2006 11:08, Ross Paterson wrote:
> > 
> > > On Tue, Apr 11, 2006 at 11:03:22AM +0100, Simon Marlow wrote:
> > >> This is a rather useful extension, and as far as I can tell it
> > >> doesn't have a ticket yet: 
> > >> 
> > >>
http://www.haskell.org//pipermail/libraries/2005-March/003494.html
> > >> 
> > >> should I create a ticket?  Is there any reason it might be hard
> > >> to implement?
> > > 
> > > There are a range of proposals, but none of them are implemented.
> > > Wouldn't that rule them out for Haskell'?
> > 
> > If it's not clear which is the right way to go, then yes I guess
> > that does rule it out.  Could you summarise the proposals?  If
> > there was a clear winner, and it was easy enough to implement,
> > perhaps we can knock up a prototype in time.
> 
> As I recall, this was brought up a few times during the class alias
> discussion and there were good technical reasons why it would be
> tricky to define a sane semantics for it. as in, it's harder than it
> first looks.

The tricky part is dealing with multiple subclasses.

For example,

class Functor f where
fmap :: (a -> b) -> f a -> f b

class Functor f => Monad f where
...
fmap = liftM

class Functor f => Comonad f where
...
fmap = liftW

newtype Id a = Id a

instance Functor Id
instance Monad Id
instance Comonad Id

Which default gets used for fmap?
-- 
David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws
  |of thermodynamics!"
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FDs and confluence

2006-04-13 Thread Ross Paterson
On Thu, Apr 13, 2006 at 05:10:36PM -0700, Iavor Diatchki wrote:
> > > I understand the reduction steps.  Are you saying that the problem is
> > > that the two sets are not syntactically equal?   To me this does not
> > > seem important: we just end up with two different ways to say the same
> > > thing (i.e., they are logically equivalent).
> >
> > If c were mentioned in another constraint, they would not be equivalent.
> 
> How so?  A concrete example would really be useful.  I think that the
> constraint 'C [a] b d' and 'C [a] c d' are equivalent and I don't see
> how the rest of the context can affect this (of course I have been
> wrong in the past :-).

They are equivalent, but C [a] b d, Num c and C [a] c d, Num c are not.

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


Re: FDs and confluence

2006-04-13 Thread Iavor Diatchki
Hello,

> > I understand the reduction steps.  Are you saying that the problem is
> > that the two sets are not syntactically equal?   To me this does not
> > seem important: we just end up with two different ways to say the same
> > thing (i.e., they are logically equivalent).
>
> If c were mentioned in another constraint, they would not be equivalent.

How so?  A concrete example would really be useful.  I think that the
constraint 'C [a] b d' and 'C [a] c d' are equivalent and I don't see
how the rest of the context can affect this (of course I have been
wrong in the past :-).  The one way to see that is (like I already
said) --- assume the one and prove the other and vice versa.

Another way to see that is as follows:   All the instances of 'C' that
have '[a]' in their first argument must have the same type in the
second argument otherwise the functional dependecy of 'C' will be
violated. Thus 'b' and 'c' above happen to be just different names for
the same thing.

Yet another slightly different way to think of this is that a
functional dependency is a function on types (e.g., associated type
synonyms give us a way to name this function). So lets say that the
functional dependecy on 'C' is called 'F'.  Than we can see that both
'C [a] b d' and 'C [a] c d' are really the same thing, namely 'C [a]
(F [a]) d'.

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


Re: collecting requirements for FDs

2006-04-13 Thread Claus Reinke



What other libraries should Haskell' support, and what are their
requirements?


useful initiative! will your collection be available anywhere?

may I suggest that you (a) ask on the main Haskell and library lists
for better coverage (I would have thought that the alternative Num
prelude suggestions might have some use cases), and (b) collect 
non-use cases as well (eg, where current implementations are 
buggy/incomplete/do different things, or where other reasons have 
prevented Haskellers from using FDs so far)? I think trying to clean

up the latter will be more effective than wading through dozens of
variations of the same working examples - you're looking for 
counter-examples to the current design, aren't you?


and just in case you haven't got these on your list already, here are 
some examples from earlier discussions on this mailing list:


- ticket #92 has module Data.Records attached to it.
   http://hackage.haskell.org/trac/haskell-prime/ticket/92
   I'd like to be able to use that in Haskell'. the library is useful in 
   itself (I've used its record selection and concatenation parts when 
   encoding attribute grammars), and I also suggested it as a good 
   testcase for Haskell' providing a sufficient (but cleaned-up) subset 
   of currently available features. but it is also an example of code that


   - works with GHC, but not with Hugs; one of those problems 
   I reported on hugs-bugs:

   http://www.haskell.org//pipermail/hugs-bugs/2006-February/001560.html

   and went through a few of the Hugs/GHC differences here 
   on this mailing list:

   http://www.haskell.org//pipermail/haskell-prime/2006-February/000577.html
   
   and used the Select example to motivate the need for relaxed

   coverage in termination checking:
   http://www.haskell.org//pipermail/haskell-prime/2006-February/000825.html

   I have since come to doubt that GHC really solves the issue,
   it just happens that its strategy of delaying problems until they may
   no longer matter works for this example; but one can construct other 
   examples that expose the problem in spite of this delayed complaining 
   trick. see my own attempts to show FD problems here:

   http://www.haskell.org//pipermail/haskell-prime/2006-February/000781.html

   or Oleg's recent example on haskell-cafe:
   http://www.haskell.org//pipermail/haskell-cafe/2006-April/015372.html
   
   while I didn't quite agree with his interpretation (see my answer

   to his message), he did manage to construct an example in which
   GHC accepts a type/program in violation of an FD.

   - requires complex workarounds, thanks to current restrictions,
   where the same could be expressed simply and directly without;
   (compare the code for Remove in Data.Record.hs: the one in 
comments vs the one I had to use to make GHC happy)


- things like a simple type equality predicate at the type class level
   run into problems with both GHC and Hugs. reported to both
   GHC and Hugs bugs lists as:
   http://www.haskell.org//pipermail/hugs-bugs/2006-February/001564.html

- the FD-visibility limitations strike not only at the instance level. 
   here is a simplified example of a problem I ran into when trying 
   to encode ATS in FDs (a variable in a superclass constraint that

   doesn't occur in the class head, but is determined by an FD on
   the superclass constraint):
   http://hackage.haskell.org/trac/ghc/ticket/714

- the HList library and associated paper also use and investigate
   the peculiarities of FDs, and variations on the TypeEq theme
   (it has both unpractical/portable and practical versions that 
make essential use of some limitations in GHC's type class

implementation to work around other of its limitations; it
demonstrates wonderfully why the current story needs to
be cleaned up!):
   http://homepages.cwi.nl/~ralf/HList/

hope that's the kind of thing you are looking for?-)

cheers,
claus

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


Re: Defaults for superclass methods

2006-04-13 Thread Ashley Yakeley

Simon Marlow wrote:


If it's not clear which is the right way to go, then yes I guess that
does rule it out.  Could you summarise the proposals?  If there was a
clear winner, and it was easy enough to implement, perhaps we can knock
up a prototype in time.

The reason being I just hit a case where this would be useful, while
trying to find a nice way to express extensible exceptions.


If we're going to do this, we should make Functor a superclass of Monad. 
This is a well-known and annoying wart in the standard libraries that 
has not been fixed only because there's no superclass default mechanism.


--
Ashley Yakeley, Seattle WA
WWED? http://www.cs.utexas.edu/users/EWD/

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://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: FDs and confluence

2006-04-13 Thread Ross Paterson
On Thu, Apr 13, 2006 at 12:07:53PM -0700, Iavor Diatchki wrote:
> On 4/12/06, Claus Reinke <[EMAIL PROTECTED]> wrote:
> > that's why Ross chose a fresh variable in FD range position:
> > in the old translation, the class-based FD improvement rule no
> > longer applies after reduction because there's only one C constraint
> > left, and the instance-based FD improvement rule will only instantiate
> > the 'b' or 'c' in the constraint with a fresh 'b_123', 'b_124', ..,
> > unrelated to 'b', 'c', or any previously generated variables in the
> > constraint store.
> 
> I understand the reduction steps.  Are you saying that the problem is
> that the two sets are not syntactically equal?   To me this does not
> seem important: we just end up with two different ways to say the same
> thing (i.e., they are logically equivalent).

If c were mentioned in another constraint, they would not be equivalent.

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


Haskell prime wiki

2006-04-13 Thread Iavor Diatchki
Hello,
The wiki page says that we should alert the committee about
inaccuracies etc of pages, so here are some comments about the page on
FDs
(http://hackage.haskell.org/trac/haskell-prime/wiki/FunctionalDependencies)

1) The example for non-termination can be simplified to:
f = \x y ->  (x .*. [y]) `asTypeOf` y

2) The example for 'non-confluence' has a typo (bullet 2 should have a
'c' not a 'b',  as it is the the two are syntactically equal :-))

3) In the section on references it seems relevant to add a reference
to "Simplifying and Improving Qualified Types" by Mark Jones, because
it provides important background on the topic.

Hope this helps
-Iavor
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FDs and confluence

2006-04-13 Thread Iavor Diatchki
Hello,

On 4/12/06, Claus Reinke <[EMAIL PROTECTED]> wrote:
> that's why Ross chose a fresh variable in FD range position:
> in the old translation, the class-based FD improvement rule no
> longer applies after reduction because there's only one C constraint
> left, and the instance-based FD improvement rule will only instantiate
> the 'b' or 'c' in the constraint with a fresh 'b_123', 'b_124', ..,
> unrelated to 'b', 'c', or any previously generated variables in the
> constraint store.

I understand the reduction steps.  Are you saying that the problem is
that the two sets are not syntactically equal?   To me this does not
seem important: we just end up with two different ways to say the same
thing (i.e., they are logically equivalent).  I think there would
really be a problem if we could do some reduction and end up with two
non-equivalent constraint sets, then I think we would have lost
confluence.  But can this happen?

> another way to interpret your message: to show equivalence of
> the two constraint sets, you need to show that one implies the
> other, or that both are equivalent to a common constraint set -
I just used this notion of equivalance, becaue it is what we usually
use in logic.  Do you think we should use something else?

> you cannot use constraints from one set to help discharging
> constraints in the other.
I don't understand this, why not?  If I want to prove that 'p iff q' I
assume 'p' to prove 'q', and vice versa.  Clearly I can use 'p' while
proving 'q'.  We must be talking about different things :-)

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


Concurrency, FFI status

2006-04-13 Thread Simon Marlow
I have now summarised the concurrency proposal status, here:

 
http://hackage.haskell.org/cgi-bin/haskell-prime/trac.cgi/wiki/Concurren
cy

I have tried to summarise the various points that have arisen during the
discussion.  If anyone feels they have been mis-paraphrased, or I have
forgotten something, please feel free to edit, or send me some text for
inclusion.  I don't want to include long gobs of text in here, though:
just summarise the main points, and if necessary link to relevant
mailing list posts.

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


RE: FFI, safe vs unsafe

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

> John Meacham <[EMAIL PROTECTED]> writes:
> 
>> Checking thread local state for _every_ foregin call is definitly
>> not an option either. (but for specificially annotated ones it is
>> fine.)
> 
> BTW, does Haskell support foreign code calling Haskell in a thread
> which the Haskell runtime has not seen before? Does it work in GHC?

Yes, yes.

> If so, does it show the same ThreadId from that point until OS
> thread's death (like in Kogut), or a new ThreadId for each callback
> (like in Python)?

A new ThreadId, but that's not a conscious design decision, just a
symptom of the fact that we don't re-use old threads.

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


Re: preemptive vs cooperative: attempt at formalization

2006-04-13 Thread David Roundy
On Wed, Apr 12, 2006 at 05:50:40PM +0100, Malcolm Wallace wrote:
> The argument John was making is that this is a useful distinguishing
> point to tell whether your concurrent implementation is cooperative or
> preemptive.  My argument is that, even if you can distinguish them in
> this way, it is not a useful distinction to make.  Your program is
> simply wrong.  If you have a sequential program whose value is _|_, your
> program is bad.  If you execute it in parallel with other programs, that
> does not make it any less bad.  One scheduler reveals the wrongness by
> hanging, another hides the wrongness by letting other things happen.  So
> what?  It would be perverse to say that the preemptive scheduler is
> semantically "better" in this situation.

I understood John's criterion in terms of a limiting case that can be
exactly specified regarding latency.  As I see it, the point of preemptive
systems is to have a lower latency than cooperative systems, and this is
also what distinguishes the two.  But the trouble is that preemptive
systems can't have a fixed latency guarantee, and shouldn't be expected to.
So he's pointing out that at a minimum, a preemptive system should always
have a latency less than infinity, while a cooperative system always *can*
have an infinite latency.  While you're right that the limiting case is bad
code, the point isn't to handle that case well, the point is to emphasize
the close-to-limiting case, when a pure function might run for longer than
your desired latency.  His spec does this in a rigorous, but achievable
manner (i.e. a useful spec).
-- 
David Roundy
http://www.darcs.net
___
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: preemptive vs cooperative: attempt at formalization

2006-04-13 Thread Simon Marlow
On 13 April 2006 11:41, Malcolm Wallace wrote:

> "Simon Marlow" <[EMAIL PROTECTED]> wrote:
> 
>>> Well, the expression "ones" on its own is non-terminating.
>> 
>> under what definition of non-termination?  Non-termination has meant
>> the same as _|_ in a call-by-name semantics as far as I'm concerned,
>> and "ones" is most definitely not == _|_.
> 
> Ok, fair enough, if we accept that "ones" is terminating, because it
> reaches a WHNF, then tell me what is the value of "print ones"?  For a
> terminating computation, x, "print x" would have a real value of type
> IO (), even though that value is abstract and you cannot name it.  But
> surely the value of "print ones" is _|_, because it never terminates?

"print ones" always has the value "print ones", i.e. it's already in
WHNF(*).

You could additionally give a semantics for running IO actions that
includes a concept of _|_ (see my other message), but we shouldn't
confuse this with the pure denotational semantics of Haskell.

Cheers,
Simon

(*) if print is an IO primitive, that is.  In practice it probably
evaluates to "hPutStr stdout (show ones)".
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: preemptive vs cooperative: attempt at formalization

2006-04-13 Thread Simon Marlow
On 13 April 2006 10:53, John Meacham wrote:

> On Thu, Apr 13, 2006 at 09:46:03AM +0100, Simon Marlow wrote:
>> You seem to be assuming more about cooperative scheduling than eg.
>> Hugs provides.  I can easily write a thread that starves the rest of
>> the system without using any _|_s.  eg.
>> 
>>   let loop = do x <- readIORef r; writeIORef r (x+1); loop in loop
> 
> this is a non-productive non-cooperative loop, as in _|_.

Ok, I'm confused because I'm thinking in terms of operational semantics
for IO.

Maybe a way to describe this is to give a meaning to an value of type IO
as a lazy sequence of yields and effects, with some way of "evaluating"
an IO action in the context of the world state, to get the next yield or
effect together with a continuation and the new world state.  Running an
IO action may give _|_ instead of the next yield or effect; ok.

Still, I think the operational semantics interpretation works fine too.

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


Re: preemptive vs cooperative: attempt at formalization

2006-04-13 Thread Malcolm Wallace
"Simon Marlow" <[EMAIL PROTECTED]> wrote:

> > Well, the expression "ones" on its own is non-terminating.
> 
> under what definition of non-termination?  Non-termination has meant
> the same as _|_ in a call-by-name semantics as far as I'm concerned,
> and "ones" is most definitely not == _|_.

Ok, fair enough, if we accept that "ones" is terminating, because it
reaches a WHNF, then tell me what is the value of "print ones"?  For a
terminating computation, x, "print x" would have a real value of type
IO (), even though that value is abstract and you cannot name it.  But
surely the value of "print ones" is _|_, because it never terminates?

[ Hmm, maybe you would want to say that there _are_ WHNFs inside the
  value of "print ones", we just can't see them.  Abstractly, there is
  reduction going on like:
 print ones
==>  putChar '1' >> print ones
==>  putChar '1' >> putChar '1' >> print ones
==>  putChar '1' >> putChar '1' >> putChar '1' >> print ones
  and each of those sequenced putChar actions is like a WHNF that is
  being consumed by the RTS driver.
]

> > This infinite computation produces an infinite output.
> 
> Depends entirely on whether putStrLn yields at regular intervals while
> it is evaluating its argument.  If we are to allow cooperative
> scheduling, then the spec needs to say whether it does or not (and
> similarly for any IO operation you want to implicitly yield).

Indeed, I was assuming that I/O implied a yield, but this assumption
should definitely be made explicit.  I propose that a cooperative
scheduler ought to yield at all primitive I/O actions, where primitive
means things like hPutChar, or takeMVar, which are implemented at a
lower level than Haskell.

> You seem to be assuming more about cooperative scheduling than eg.
> Hugs provides.  I can easily write a thread that starves the rest of
> the system without using any _|_s.  eg.
> 
>   let loop = do x <- readIORef r; writeIORef r (x+1); loop in loop

I wasn't originally aware that Hugs scheduler only yields on MVar
operations.  That seems too restrictive.  I believe the "all I/O
primitives" rule would guarantee progress in the absence of _|_.
Unless you can think of another counter-example?

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


Re: preemptive vs cooperative: attempt at formalization

2006-04-13 Thread John Meacham
On Thu, Apr 13, 2006 at 02:53:01AM -0700, John Meacham wrote:
> this is a non-productive non-cooperative loop, as in _|_. since IORefs

I mean 

this is a non-productive non-terminating loop, as in _|_. since IORefs

John

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


Re: preemptive vs cooperative: attempt at formalization

2006-04-13 Thread John Meacham
On Thu, Apr 13, 2006 at 09:46:03AM +0100, Simon Marlow wrote:
> You seem to be assuming more about cooperative scheduling than eg. Hugs
> provides.  I can easily write a thread that starves the rest of the
> system without using any _|_s.  eg.
> 
>   let loop = do x <- readIORef r; writeIORef r (x+1); loop in loop

this is a non-productive non-cooperative loop, as in _|_. since IORefs
can't be shared unless protected by an MVar there is no way to observe
the side effect of this routine. MVar routines since they are
potentially blocking (and moreso because we have the MVar fairness
guarentee),  must be yield points.

> I must be missing something.  The progress guarantee we have on the wiki
> makes complete sense, but the fairness guarantee that John proposed
> seems much stronger.

it was not my intent to be any stronger, but rather just be a
reformulation.

John

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


Concurrency, FFI status

2006-04-13 Thread Simon Marlow
This is just a "heads up" that I'm currently collating the current state
of the discussion re: concurrency and the FFI, with a view to
enumerating all the current issues with rationale on the wiki.  It's
getting to a state where I can't keep it all in my head at one time, and
I think this will help us to move forward, and give others a chance to
identify issues they would like to comment on.

So just in case anyone else was considering large changes to the
concurrency page on the wiki, please hold for a while.  I should have it
up by the end of the day.

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


Re: FFI, safe vs unsafe

2006-04-13 Thread Marcin 'Qrczak' Kowalczyk
John Meacham <[EMAIL PROTECTED]> writes:

> Checking thread local state for _every_ foregin call is definitly
> not an option either. (but for specificially annotated ones it is
> fine.)

BTW, does Haskell support foreign code calling Haskell in a thread
which the Haskell runtime has not seen before? Does it work in GHC?

If so, does it show the same ThreadId from that point until OS
thread's death (like in Kogut), or a new ThreadId for each callback
(like in Python)?

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: preemptive vs cooperative: attempt at formalization

2006-04-13 Thread Simon Marlow
On 12 April 2006 17:51, Malcolm Wallace wrote:

> "Simon Marlow" <[EMAIL PROTECTED]> wrote:
> 
>>> By infinite loop, you mean both non-terminating, and non-productive.
>>> A non-terminating but productive pure computation (e.g. ones =
>>> 1:ones) is not necessarily a problem.
>> 
>> That's slightly odd terminology.  ones = 1:ones  is definitely
>> terminating.  (length ones) is not, though.
> 
> Well, the expression "ones" on its own is non-terminating.

under what definition of non-termination?  Non-termination has meant the
same as _|_ in a call-by-name semantics as far as I'm concerned, and
"ones" is most definitely not == _|_.

> So if you
> say "putStrLn (show ones)", it doesn't just sit there doing nothing.
> This infinite computation produces an infinite output.  So the fact
> that it is non-terminating is irrelevant.  I may very well want a
> thread to do exactly that, and even with a cooperative scheduler this
> is perfectly OK.  Other threads will still run just fine.

Depends entirely on whether putStrLn yields at regular intervals while
it is evaluating its argument.  If we are to allow cooperative
scheduling, then the spec needs to say whether it does or not (and
similarly for any IO operation you want to implicitly yield).

> The only time when other threads will *not* run under cooperative
> scheduling is when the non-terminating pure computation is *also*
> unproductive (like your "length ones").

You seem to be assuming more about cooperative scheduling than eg. Hugs
provides.  I can easily write a thread that starves the rest of the
system without using any _|_s.  eg.

  let loop = do x <- readIORef r; writeIORef r (x+1); loop in loop

I must be missing something.  The progress guarantee we have on the wiki
makes complete sense, but the fairness guarantee that John proposed
seems much stronger.

I had in mind defining something based on an operational semantics such
as in [1].  The cooperative guarantee would be something like "if any
transition can be made, then the system will choose one to make", with
an extra condition about pure terms that evaluate to _|_, and a
guarantee that certain operations like yield choose the next transition
from another thread.  Preemtpive would remove the _|_ condition, the
yield condition, and add a fairness property.

Cheers,
Simon

[1] Asynchronous Exceptions in Haskell,
http://www.haskell.org/~simonmar/papers/async.pdf
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FDs and confluence

2006-04-13 Thread Tom Schrijvers

On Thu, 13 Apr 2006, Claus Reinke wrote:

(btw, in a real implementation, I wouldn't expect the memo constraints to 
enter the constraint store at all - they are just a CHR-based way to express 
a memo table, hence the name; as, in fact, I explained before even starting 
that alternative translation thread..).


Sure, you can have any particular dedicated data structure to realize part 
of the constraint store. CHR implementations already use lists, trees, 
hashtables, global variables, ...


If some Haskell' implementations want a dedicated CHR implementation for 
their type inference, there is already quite some expertise in efficient 
implementation and optimized compilation of CHR and I would be 
interested as a CHR implementor.


Cheers,

Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: FDs and confluence

2006-04-13 Thread Simon Peyton-Jones
| there are interesting problems in FDs, but it seems that the
confluence
| problems were merely problems of the old translation, not anything
| inherent in FDs! I really had hoped we had put that phantom to rest.

Claus

You're doing a lot of work here, which is great.  Why not write a paper?
Even for people (like me) who are relatively familiar with FDs, it's
hard to follow a long email thread.  For others, who might well be
interested, it's even harder.  The phantom is not resting yet!   (On the
other hand, email can be a good way of developing the ideas, which is
what you have been doing.)

A good way forward might be to write a paper building on our recent JFP
submission, and proposing whatever changes and improvements you have
developed.  That would make your work accessible to a much wider
audience.  

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