[jhc] compiler errors/bugs with transformers

Korcan Hussein korcan_h at hotmail.com
Sat Jan 8 12:35:11 CET 2011


Hello, I have built the latest version of transformers package (so no multi-parameter type-classes) with the latest darcs version of jhc. When I "run" my monad transformer stack in main (and escape back into IO) I get an error message, I've attached a simplified example which reproduces the bug, I get the message:

jhc: getType: EPi (x34075924::ELit (Jhc.Prim.Int::EPi (_::ESort *) (ESort *))) (ELit ((#2#) (ELit (Jhc.Prim.World__::ESort #)) (ELit (Jhc at .Absurd.*::ESort *))::ESort #))

If I use a records with foreign pointers for StateT/ReaderT and use get/ask I get 100s of error messages starting with:

Typechecking...
Compiling...
Collected Compilation...
-- typeAnalyzeMethods

>>> Exception thrown

>>> Before typeAnalyze-Main-AfterMethod
theMain :: Jhc.Prim.World__ → Jhc.Prim.World__
theMain = λv1∷Jhc.Prim.World__. Jhc.IO.runMain () Main.main v1

Instance at .iJhc.Num.toInteger.Data.Word.Word32 :: Data.Word.Word32 → Integer
Instance at .iJhc.Num.toInteger.Data.Word.Word32 = λv1∷Data.Word.Word32.
    case v1 of
        Word32# (v3∷bits32) →
        case W at .fInstance@.iJhc.Num.toInteger.Data.Word.Word32 v3 of
            v4∷bits<max> → Integer# v4;;

Instance at .iForeign.Storable.poke.Graphics.UI.SDL.Color.Color :: Jhc.Addr.Ptr Graphics.UI.SDL.Color.Color → Graphics.UI.SDL.Color.Color → Jhc.Prim.IO ()
Instance at .iForeign.Storable.poke.Graphics.UI.SDL.Color.Color = λv1∷Jhc.Addr.Ptr Graphics.UI.SDL.Color.Color.
                                                               λv2∷Graphics.UI.SDL.Color.Color.
                                                               λv3∷Jhc.Prim.World__.
    case v2 of
        Graphics.UI.SDL.Color.Color (v5∷Data.Word.Word8) (v6∷Data.Word.Word8) (v7∷Data.Word.Word8) →
        W at .fInstance@.iForeign.Storable.poke.Graphics.UI.SDL.Color.Color v1 v5 v6 v7 v3;

Jhc.Monad.=<< :: ∀f0∷* → *.∀a.∀b. (a → f0 b) → f0 a → f0 b
Jhc.Monad.=<< = Λf0∷* → *.Λa.Λb.λJhc.Monad.97_f∷a → f0 b.λJhc.Monad.98_x∷f0 a.
    Jhc.Monad.>>= f0 a b Jhc.Monad.98_x Jhc.Monad.97_f

Foreign.C.String.peekCAString :: Jhc.Addr.Ptr Foreign.C.Types.CChar → Jhc.Prim.IO String
Foreign.C.String.peekCAString = λv1∷Jhc.Addr.Ptr Foreign.C.Types.CChar.
                                λv2∷Jhc.Prim.World__.
    case v1 of
        Jhc.Addr.Ptr (v4∷bits<ptr>) → W at .fForeign.C.String.peekCAString v4 v2;

Jhc.IO.runMain :: ∀a. Jhc.Prim.IO a → Jhc.Prim.World__ → Jhc.Prim.World__
Jhc.IO.runMain = Λa.λJhc.IO.74_main∷Jhc.Prim.IO a.λJhc.IO.75_w∷Jhc.Prim.World__.
    case Jhc.IO.74_main Jhc.IO.75_w of (# v2∷Jhc.Prim.World__, v3∷a #) → v2;
...
....
...

 		 	   		  
-------------- next part --------------
A non-text attachment was scrubbed...
Name: Main.hs
Type: application/octet-stream
Size: 406 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/jhc/attachments/20110108/baaf507a/attachment.obj>


More information about the jhc mailing list