Me again...

given test.hs:

> 10:27am moussor:Prelude/ cat test.hs
> module Prelude where
> 
> data Ordering = LT | GT | EQ

we compile:

> 10:29am moussor:Prelude/ ~/mou/ghc-cvs/ghc/compiler/ghc-inplace 
>-fno-implicit-prelude -fext-core -fno-code test.hs
> 10:29am moussor:Prelude/ ~/mou/ghc-cvs/ghc/compiler/ghc-inplace --version
> The Glorious Glasgow Haskell Compilation System, version 5.05

(This is a cvs head from a few weeks ago)

then the beginning of the generated core is:

> 10:29am moussor:Prelude/ head test.hcr
> %module Prelude
>   %data Prelude.Ordering =
>     {Prelude.LT;
>      Prelude.GT;
>      Prelude.EQ};
>   Prelude.LT :: Prelude.Ordering = Prelude.zdwLT;
>   Prelude.GT :: Prelude.Ordering = Prelude.zdwGT;
>   Prelude.EQ :: Prelude.Ordering = Prelude.zdwEQ;

Except these last three lines are backwards.  They should read:

>   Prelude.zdwLT :: Prelude.Ordering = Prelude.LT;

and so on.

 - Hal

--
Hal Daume III

 "Computer science is no more about computers    | [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to