Bugs item #992200, was opened at 2004-07-16 09:11
Message generated for change (Comment added) made by mm_aa
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=992200&group_id=8032

Category: Compiler
Group: 6.2.1
Status: Open
Resolution: None
Priority: 5
Submitted By: Mike Aizatsky (mm_aa)
Assigned to: Nobody/Anonymous (nobody)
Summary: Template crash on constructing existential data type

Initial Comment:
Windows XP

D:\Tools\ghc>ghc-6.2.1\bin\ghc.exe -fglasgow-exts --make foo.hs
Chasing modules from: foo.hs
Compiling Any              ( ./Any.hs, ./Any.o )
Compiling Foo              ( foo.hs, foo.o )
Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package haskell-src ... linking ... done.
ghc.exe: panic! (the `impossible' happened, GHC version 6.2.1):
        Malformed predicate


module Any where

import Language.Haskell.THSyntax

genAny :: DecQ -> Q [Dec]
genAny decl =
    do{
        d <- decl
      ; case d of
            ClassD _ name _ decls -> sequenceQ [genAnyClass 
(name)
decls]
            _ -> error "genAny can be applied to classes only"
    }

genAnyClass :: String -> [Dec] -> DecQ
genAnyClass name decls =
    do{
        returnQ (DataD [forall] anyName [] [constructor] [])
    }
    where
        anyName = "Any" ++ name ++ "1111"
        constructor = NormalC anyName [(NotStrict, VarT "a")]
        forall = ForallT [] [] (VarT "a")


module Foo where

import Any

class MyInterface a where
        foo :: a -> Int
        foo1 :: Int -> a -> Int

$(genAny (reifyDecl MyInterface))


----------------------------------------------------------------------

>Comment By: Mike Aizatsky (mm_aa)
Date: 2004-07-20 13:41

Message:
Logged In: YES 
user_id=76543

Ok. I'll wait for 992199 fix to see how should I construct
the existential data types.

----------------------------------------------------------------------

Comment By: Simon Peyton Jones (simonpj)
Date: 2004-07-19 16:36

Message:
Logged In: YES 
user_id=50165

You're constructing a syntactically invalid data type 
declaration, looking like
  data (forall. a) => T = MkT a

and not surprisingly that does not work.  But the error 
message is terrible, and we'll improve that, so I'm leaving the 
bug open.  It's a user error not a compiler failure.

----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=992200&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to