FW: [Template-haskell] FW: [ ghc-Bugs-992200 ] Template crash
onconstructing existential datatype
Simon Peyton-Jones
simonpj at microsoft.com
Fri Aug 20 11:37:52 EDT 2004
...and the third one...
-----Original Message-----
From: template-haskell-bounces at haskell.org
[mailto:template-haskell-bounces at haskell.org] On Behalf Of Simon
Peyton-Jones
Sent: 19 July 2004 17:35
To: template-haskell at haskell.org
Subject: [Template-haskell] FW: [ ghc-Bugs-992200 ] Template crash
onconstructing existential datatype
Dear Template Haskell folk
This SourceForge bug is another example of the bad things that happen
when:
- a TH program constructs a syntactically invalid program
- and then splices it in
The trouble is that Convert.convertToHsExpr :: TH.Exp -> LHsExpr RdrName
is a pure function, and fails "hard" with a panic, whereas it should
really be in the TcM monad, and fail in the way any other type error
fails. It's a user error, and should not show up as a panic.
Would anyone like to fix hsSyn/Convert.lhs so that it lives in the Tc
monad? The call (in TcSplice) is easily changed. It'd probably make
sense to move it from hsSyn/ to typecheck/
I'm thinking about putting types in the syntax tree, so if others can
help out with tidying up like this, it'd be great.
Simon
-----Original Message-----
From: glasgow-haskell-bugs-bounces at haskell.org
[mailto:glasgow-haskell-bugs-bounces at haskell.org] On Behalf Of
SourceForge.net
Sent: 16 July 2004 10:11
To: noreply at sourceforge.net
Subject: [ ghc-Bugs-992200 ] Template crash on constructing existential
datatype
Bugs item #992200, was opened at 2004-07-16 09:11
Message generated for change (Tracker Item Submitted) made by Item
Submitter
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=992200&grou
p_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))
----------------------------------------------------------------------
You can respond by visiting:
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=992200&grou
p_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs at haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
_______________________________________________
template-haskell mailing list
template-haskell at haskell.org
http://www.haskell.org/mailman/listinfo/template-haskell
More information about the template-haskell
mailing list