
On Fri, Nov 04, 2011 at 08:52:36AM -0500, aditya siram wrote:
Perhaps this is what you're looking for: {-# LANGUAGE ExistentialQuantification #-} import Data.Binary import Data.ByteString.Lazy as B ( readFile, writeFile ) import Codec.Compression.GZip ( compress, decompress )
data Thing = forall a. (Binary a, Show a, Eq a) => Thing a
instance Binary Thing where get = get put (Thing a) = put a
instance Show Thing where show (Thing a) = show a
readThing :: FilePath -> IO Thing readThing f = return . decode . decompress =<< B.readFile f
writeThing :: FilePath -> Thing -> IO () writeThing f = B.writeFile f . compress . encode
doSomething :: Thing -> m Thing doSomething = undefined
main = do a <- readThing "file1.txt" a' <- doSomething a writeThing "file2.txt" a'
It compiles on my machine (GHC 7.2.1) but I haven't tested it. It uses the
This will not work. The problem is that once you have a Thing you cannot do anything with it, because you have no information about what type is inside. In other words you cannot implement 'doSomething' to do anything interesting at all. I am actually surprised that 'readThing' type checks -- I am not sure what type it thinks the read thing has, or how it can guarantee that it satisfies the given constraints. I tried adding a Typeable constraint to Thing and using 'cast' to recover the type, but that doesn't really work either. You would really have to do something like changing the Binary instance for Thing so that it also serializes/deserializes a TypeRep along with the value, and then does some sort of unsafe cast after reading. You may want to take a look at how xmonad handles this problem -- it allows arbitrary user-extensible state and layouts, which it needs to serialize and deserialize when restarting itself. -Brent