[Haskell-cafe] GADTs and instances

Ryan Ingram ryani.spam at gmail.com
Sat Sep 6 16:33:42 EDT 2008


The problem is that the caller of "get" is allowed to say what type of
Query they want with this instance, for example:

] get :: Get (Query Int)
because Int is an instance of Binary, and you claim
] instance Binary a => Binary (Query a)
In fact, since the type of each query is unique, the tagging in "put"
doesn't help you.

So there is no way to write a generic Binary instance for Query a.

But don't give up!  Here's a solution in literate haskell...

> {-# LANGUAGE ExistentialQuantification, FlexibleInstances, GADTs #-}
> module Query where
> import Data.Binary
> import Control.Monad (liftM)
>
> data Query a where
>     Lookup :: String -> Query (Maybe Int)
>     Fetch :: [String] -> Query [Int]

One obvious strategy is to use existential types:

> data SomeQuery = forall a. SomeQuery (Query a)

You can then make SomeQuery an instance of Binary using very similar
code to your implementation.  Now, the code that calls "get" needs to
be able to deal with any Query type it gets back inside the SomeQuery.

Another possibility is to drop the tagging altogether and use a helper class:

> class BinaryQuery a where
>     putQ :: Query a -> Put
>     getQ :: Get (Query a)

> instance BinaryQuery a => Binary (Query a) where
>     put = putQ
>     get = getQ

> instance BinaryQuery (Maybe Int) where
>     putQ (Lookup x) = put x
>     getQ = liftM Lookup get

> instance BinaryQuery [Int] where
>     putQ (Fetch xs) = put xs
>     getQ = liftM Fetch get

You can also combine the strategies and use SomeQuery when the stored
value needs a tag:

> instance Binary SomeQuery where
>    put (SomeQuery x@(Lookup _)) = putWord8 0 >> put x
>    put (SomeQuery x@(Fetch _)) = putWord8 1 >> put x
>    get = getWord8 >>= \tag -> case tag of
>                0 -> liftM SomeQuery (get :: Get (Query (Maybe Int)))
>                1 -> liftM SomeQuery (get :: Get (Query [Int]))

The pattern matching in "put" specializes the type of x, allowing the
query-level put to find the correct implementation.  Similarily, in
"get" we choose the correct get based on the input type.

   -- ryan


More information about the Haskell-Cafe mailing list