[Haskell-cafe] GADTs and instances
Tony Hannan
tonyhannan2 at gmail.com
Sat Sep 6 08:43:52 EDT 2008
Hello haskellers,
Anyone know the trick for making a Binary instance of a GADT.
See sample code below followed by the type error reported by ghc version
6.8.3
Thanks,
Tony
----
{-# LANGUAGE GADTs #-}
module GADTTest where
import Data.Binary
import Control.Monad (liftM)
data Query a where
Lookup :: String -> Query (Maybe Int)
Fetch :: [String] -> Query [Int]
instance (Binary a) => Binary (Query a) where
put (Lookup x) = putWord8 0 >> put x
put (Fetch x) = putWord8 1 >> put x
get = getWord8 >>= \tag -> case tag of
0 -> liftM Lookup get
1 -> liftM Fetch get
-----
GADTTest.hs:12:0:
Couldn't match expected type `Maybe Int'
against inferred type `[Int]'
When trying to generalise the type inferred for `get'
Signature type: forall a. (Binary a) => Get (Query a)
Type to generalise: Get (Query a)
In the instance declaration for `Binary (Query a)'
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080906/e6c2ac63/attachment.htm
More information about the Haskell-Cafe
mailing list