Release plans

Doaitse Swierstra doaitse at cs.uu.nl
Tue Apr 17 06:50:48 EDT 2007


Just to show what kind of problems we are currently facing. The  
following type checks in our EHC compiler and in Hugs, but not in the  
GHC:

module Test where

data T s = forall x. T (s -> (x -> s) -> (x, s, Int))

run :: (forall s . T s) -> Int
run ts  = case ts of
             T g -> let (x,_, b) =  g x id
                    in b


Doaitse Swierstra


On Apr 17, 2007, at 12:41 AM, Stefan O'Rear wrote:

> On Mon, Apr 16, 2007 at 03:54:56PM +0100, Simon Marlow wrote:
>> - left-to-right impredicative instantiation: runST $ foo
>
> This concerns me.  With each ad-hoc extension of the type system, I
> worry that soon the GHC type system will become so byzantine and
> ill-specified that the type checker can only be cloned, not
> substantially improved on.  I personally have a type checker idea I am
> working on, but I doubt I will ever be able to implement features such
> as this, because the type checking abstraction is now leaking badly.
> Once the Hindley-Damas-Milner algorithm is exposed, I fear programmers
> will rely on it and progress in Haskell typechecker implementation
> will be effectively halted.  (Yes, I know I'm a bit late in
> complaining...)
>
>> - list fusion
>
> Nitpick - you did mean stream fusion, right?
>
>> We think the above feature set makes for a pretty strong 6.8 release.
>>
>> What do you think of this plan?  Are there features/bug-fixes that  
>> you
>> really want to see in 6.8?
>
> Good code generation for loops.  I understand they are rare in
> practice, but it's kinda disheartening to write memset() and see in
> the asm loop 11 memory references, 9 to the stack (numbers from
> unreliable memory).
>
> I don't mind the plan, either.
>
> Stefan
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



More information about the Glasgow-haskell-users mailing list