Well, normally - you can't (unless there is some equivalent to the
constructor exported).
But there is a trick. You can use generic classes:
{-# OPTIONS_GHC -fglasgow-exts -XGenerics -package lang #-}
import Generics
class Binary' a where
put' :: a -> Put
get' :: Get a
put' {| Unit |} Unit = return ()
get' {| Unit |} = return Unit
put' {| a :+: b |} (Inl x) = putWord8 0 >> put' x
put' {| a :+: b |} (Inr y) = putWord8 1 >> put' y
get' {| a :+: b |} =
do w <- getWord8
case w of
0 -> liftM Left get'
_ -> liftM Right get'
put' {| a :*: b |} (x :*: y) = put' x >> put' y
get' {| a :*: b |} =
do x <- get'
y <- get'
return $ x :*: y
instance Binary' Int32 where
put' = put
get' = get
instance Binary' StdGen
instance Binary StdGen where
put = put'
get = get'
Last time I've checked it worked fine. A friend of mine have used it to
create "instance Eq Chan", if I remember correctly.
Grigory Sarnitskiy wrote:
In System.Random StdGen is defined as
data StdGen = StdGen Int32 Int32
but its constructor StdGen is not exported. How to make StdGen to be an
instance of Binary? The following won't work:
instance Data.Binary.Binary StdGen where
put (StdGen aa ab) = do
Data.Binary.put aa
Data.Binary.put ab
get = do
aa <- get
ab <- get
return (StdGen aa ab)
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe