You're right.

The issue you've mentioned can be fixed easily - import Data.Generics instead of Generics and get rid of -package lang (I've copied them from the documentation without checking, seems like it's a bit outdated).

The real problem is that you can't use "Get a" in generics! And you have the same problem here, because "Get" constructor isn't exported either!

But we can make it work using a continuation trick:

{-# OPTIONS_GHC -fglasgow-exts -XGenerics #-}
module Test where
import Control.Monad
import Data.Binary
import Data.Generics
import Data.Int
import System.Random
class Binary' a where
  put' :: a -> Put
  get' :: (a -> Get StdGen) -> Get StdGen
  put' {| Unit |} Unit = return ()
  get' {| Unit |} f = f Unit
  put' {| a :+: b |} (Inl x) = putWord8 0 >> put' x
  put' {| a :+: b |} (Inr y) = putWord8 1 >> put' y
  get' {| a :+: b |} f =
      do w <- getWord8
         case w of
           0 -> get' $ \x -> f $ Inl x
           _ -> get' $ \y -> f $ Inr y
  put' {| a :*: b |} (x :*: y) = put' x >> put' y
  get' {| a :*: b |} f = get' $ \x -> get' $ \y -> f (x :*: y)
instance Binary' Int32 where
  put' = put
  get' f = get >>= f
instance Binary' StdGen
instance Binary StdGen where
  put = put'
  get = get' return

This time I've checked that it really compiles. Pretty much sure it works.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to