[Haskell-cafe] How to derive instance for type without exported
constructor?
Grigory Sarnitskiy
sargrigory at ya.ru
Fri Sep 4 13:07:18 EDT 2009
Well, I've managed to produce a solution, quite ugly and unefficient. Still it works (and I really need it). StdGen serialization occurs only once during computation that lasts several hours, so the speed is not vital for me. Here is my solution:
module Main where
import System.Random
import Data.Binary
import Data.Int
data StdGen' = StdGen' Int32 Int32 deriving (Show)
gen2gen' :: StdGen -> StdGen'
gen2gen' gen = let
[g1, g2] = words $ show $ gen
g1' = read g1 :: Int32
g2' = read g2 :: Int32
in StdGen' g1' g2'
gen'2gen :: StdGen' -> StdGen
gen'2gen (StdGen' g1' g2') = let
gen = read $ show g1' ++ ' ':(show g2') :: StdGen
in gen
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)
instance Data.Binary.Binary StdGen where
put gen = put $ gen2gen' gen
get = do
gen' <- get
return (gen'2gen gen')
More information about the Haskell-Cafe
mailing list