[Template-haskell]
RE: [ ghc-Bugs-820778 ] Malformed Predicate w/ Template Haskell
Simon Peyton-Jones
simonpj at microsoft.com
Thu Oct 30 10:39:09 EST 2003
TH maestros
This bug turns out to be simply that Template Haskell is only set up for
Haskell 98, whereas Jon Cast wants to manipulate multi-parameter type
clases.
Should we add multi-param type classes to THSyntax? Does anyone feel
like doing it? It's a fairly routine matter, but it does mean changing
the data type. (Another reason to use bracket syntax!)
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: 09 October 2003 18:51
| To: noreply at sourceforge.net
| Subject: [ ghc-Bugs-820778 ] Malformed Predicate w/ Template Haskell
|
| Bugs item #820778, was opened at 2003-10-09 12:51
| 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=820778&grou
p_id=8032
|
| Category: Compiler (Type checker)
| Group: 6.0.1
| Status: Open
| Resolution: None
| Priority: 5
| Submitted By: Jon Cast (jcast)
| Assigned to: Nobody/Anonymous (nobody)
| Summary: Malformed Predicate w/ Template Haskell
|
| Initial Comment:
| The following two modules:
|
| --- Cut ---
|
| module ScratchTemplates where
|
| import Language.Haskell.THSyntax
|
| newtype Interaction a = Interaction a deriving Show
|
| ret = Interaction
|
| instance Monad Interaction where
| return = Interaction
| Interaction x >>= f = f x
|
| instance Functor Interaction where
| fmap f x = x >>= return . f
|
| interactionT t = tcon (TconName "Interaction") `tapp` t
|
| class Flatten a b | a -> b where
| flatten :: a -> b
|
| flattenT :: TypQ -> TypQ -> TypQ
| flattenT t t' = tvar "Flatten" `tapp` t `tapp` t
|
| baseType t = sequence [
| inst (return []) (flattenT t t)
| [val (pvar "flatten") (normal (var "id")) []],
| inst (return []) (flattenT (interactionT t)
| (interactionT t))
| [val (pvar "flatten") (normal (var "id")) []]]
|
| instance Flatten a b =>
| Flatten (Interaction (Interaction a))
| (Interaction b) where
| flatten a = a >>= id >>= return . flatten
|
| module Main where
|
| import Monad
| import ScratchTemplates
| import Language.Haskell.THSyntax
|
| $(baseType (tcon (Tuple 0)))
|
| instance Flatten String String where
| flatten a = a
|
| instance Flatten (Interaction String) (Interaction
| String) where
| flatten a = a
|
| instance Flatten b c => Combine String b (String, c) where
| combine a b = liftM2 (,) a (fmap flatten b)
|
| instance Flatten Int Int where
| flatten a = a
|
| class Combine a b c | a b -> c where
| combine :: Interaction a -> Interaction b ->
| Interaction c
|
| instance Combine () b b where
| combine a b = b
|
| instance Flatten b c => Combine Int b (Int, c) where
| combine a b = do
| x <- a
| y <- fmap flatten b
| return (x, y)
|
| instance (Flatten b c, Combine a c d) =>
| Flatten (Interaction a, Interaction b)
| (Interaction d) where
| flatten (a, b) = combine a (fmap flatten b)
|
| main = main
|
| --- Cut here ---
|
| loaded into ghci -fglasgow-exts produce the following
| error message:
|
| Compiling ScratchTemplates ( ScratchTemplates.hs,
| interpreted )
| Compiling Main ( scratch.hs, interpreted )
| ghc-6.0.1: panic! (the `impossible' happened, GHC
| version 6.0.1):
| Malformed predicate
|
| Please report it as a compiler bug to
| glasgow-haskell-bugs at haskell.org,
| or http://sourceforge.net/projects/ghc/.
|
|
| ----------------------------------------------------------------------
|
| You can respond by visiting:
|
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=820778&grou
p_id=8032
| _______________________________________________
| Glasgow-haskell-bugs mailing list
| Glasgow-haskell-bugs at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
More information about the template-haskell
mailing list