Binary library

Jan de Wit jwit@students.cs.uu.nl
Wed, 21 Nov 2001 11:43:12 +0100 (MET)


> > Does Malcolm's Binary library exist for ghc? If not, is there 
> > a standard
> > way (ie using Haskell that works on any compiler) to dump a data
> > structure into a file that another program or part of the same program
> > can then pick up and read (cf "serialize" in Java)? I'm 
> > reluctant to go
> > with a solution that's compiler-specific.
>
> Using Show & Read is the only really portable way to do this,
> unfortunately.  
[snip]

Well, it's not really portable... Try the program at the end of this file,
by first executing hugsMain in hugs, exiting and then running main in
ghc or ghci, and you'll see:

| Cons{hd='a',tl=(Cons{hd='b',tl=Nil})}
| *** Exception: Prelude.read: no parse

So, at least ghc and hugs disagree... My ghc version is 5.02 and my hugs
is February 2000/2001 (both give the same output).

Cheers, 

Jan de Wit

----8<----
module Test where

data List a = Nil | Cons { hd :: a, tl :: List a } 
  deriving (Show,Read,Eq)
    
theList = Cons 'a' (Cons 'b' Nil)

hugsMain = do writeFile "test.txt" (show theList)
              main

main = do s <- readFile "test.txt"
	  let theListFromFile = read s
	  print theList
	  print theListFromFile
	  print $ theList == theListFromFile    
	  writeFile "test.txt" (show theList)