#4949: TH typechecking regression
----------------------------------------+-----------------------------------
Reporter: igloo | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 7.0.2
Component: Compiler (Type checker) | Version: 7.0.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
----------------------------------------+-----------------------------------
Comment(by igloo):
I suspect this from `haskelldb-th` is the same problem:
{{{
{-# LANGUAGE TemplateHaskell, MultiParamTypeClasses,
FunctionalDependencies #-}
module Database.HaskellDB.CodeGen where
import Language.Haskell.TH
import qualified Language.Haskell.TH as TH
infixr 5 #
infix 6 <<
infix 9 !
(<<) :: Attr f a -> e a -> Record (RecCons f (e a) RecNil)
(<<) = undefined
(#) :: Record (RecCons f a RecNil) -> (b -> c) -> (b -> RecCons f a c)
(#) = undefined
data RecCons f a b = RecCons a b deriving (Eq, Ord)
data RecNil = RecNil deriving (Eq, Ord)
type Record r = RecNil -> r
data Attr f a = Attr Attribute
type Attribute = String
class Select f r a | f r -> a where
(!) :: r -> f -> a
mkRecord :: [(TH.Name, [TH.Name])] -> ExpQ
mkRecord = projTable . concatMap (\(table, fields) -> zip (repeat table)
fields)
where
projTable ([]) = [|id|]
projTable ((table, f):rest)
= [|$(varE f) << $(varE table) ! $(varE f) # $(projTable rest)|]
}}}
{{{
Database/HaskellDB/CodeGen.hs:31:40:
No instance for (Select f0 r0 (e0 a0))
arising from a use of `!'
Possible fix:
add an instance declaration for (Select f0 r0 (e0 a0))
In the second argument of `(<<)', namely
`$(varE table) ! $(varE f)'
In the first argument of `(#)', namely
`$(varE f) << $(varE table) ! $(varE f)'
In the Template Haskell quotation
[| $(varE f) << $(varE table) ! $(varE f) # $(projTable rest) |]
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4949#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs