| Safe Haskell | None |
|---|
Data.RefSerialize
Description
Read, Show and Data.Binary do not check for repeated references to the same address. As a result, the data is duplicated when serialized. This is a waste of space in the filesystem and also a waste of serialization time. but the worst consequence is that, when the serialized data is read, it allocates multiple copies for the same object when referenced multiple times. Because multiple referenced data is very typical in a pure language such is Haskell, this means that the resulting data loose the beatiful economy of space and processing time that referential transparency permits.
This package leverages Show, Read and Data.Binary instances while it permits textual as well as binary serialization keeping internal references.
Here comes a brief tutorial:
runW applies showp, the serialization parser of the instance Int for the RefSerialize class
Data.RefSerialize>let x= 5 :: Int
Data.RefSerialize>runW $ showp x
5
every instance of Read and Show is an instance of RefSerialize. for how to construct showp and readp parsers, see the demo.hs
rshowp is derived from showp, it labels the serialized data with a variable name
Data.RefSerialize>runW $ rshowp x
v8 where {v8= 5; }
Data.RefSerialize>runW $ rshowp [2::Int,3::Int]
v6 where {v6= [ v9, v10]; v9= 2; v10= 3; }
while showp does a normal show serialization
Data.RefSerialize>runW $ showp [x,x]
[5, 5]
rshowp variables are serialized memory references: no piece of data that point to the same addrees is serialized but one time
Data.RefSerialize>runW $ rshowp [x,x]
v9 where {v6= 5; v9= [ v6, v6]; }
this happens recursively
Data.RefSerialize>let xs= [x,x] in str = runW $ rshowp [xs,xs]
Data.RefSerialize>str
v8 where {v8= [ v10, v10]; v9= 5; v10= [ v9, v9]; }
the rshowp serialized data is read with rreadp. The showp serialized data is read by readp
Data.RefSerialize>let xss= runR rreadp str :: [[Int]]
Data.RefSerialize>print xss
[[5,5],[5,5]]
this is the deserialized data
the deserialized data keep the references!! pointers are restored! That is the whole point!
Data.RefSerialize>varName xss !! 0 == varName xss !! 1
True
rShow= runW rshowp
rRead= runR rreadp
Data.RefSerialize>rShow x
v11 where {v11= 5; }
In the definition of a referencing parser non referencing parsers can be used and viceversa. Use a referencing parser
when the piece of data is being referenced many times inside the serialized data.
by default the referencing parser is constructed by:
rshowp= insertVar showp
rreadp= readVar readp
but this can be redefined. See for example the instance of [] in RefSerialize.hs
This is an example of a showp parser for a simple data structure.
data S= S Int Int deriving ( Show, Eq)
instance Serialize S where
showp (S x y)= do
-- insertString S
rshowp x -- rshowp parsers can be inside showp parser
rshowp y
readp = do
symbol S -- I included a (almost) complete Parsec for deserialization
x <- rreadp
y <- rreadp
return $ S x y
there is a mix between referencing and no referencing parser here:
Data.RefSerialize>putStrLn $ runW $ showp $ S x x
S v23 v23 where {v23= 5; }- module Data.RefSerialize.Parser
- class Serialize c where
- type Context = HashTable Int (StableName MFun, MFun, ShowF)
- newContext :: IO Context
- rshowp :: Serialize c => c -> ST ()
- rreadp :: Serialize c => ST c
- showps :: Serialize a => a -> ST ByteString
- showpText :: Show a => a -> ST ()
- readpText :: Read a => ST a
- takep :: Int -> ST ByteString
- showpBinary :: Binary a => a -> ST ()
- readpBinary :: Binary a => ST a
- insertString :: ByteString -> ST ()
- insertChar :: Char -> ST ()
- rShow :: Serialize c => c -> ByteString
- rRead :: Serialize c => ByteString -> c
- insertVar :: (a -> ST ()) -> a -> ST ()
- readVar :: Serialize c => ST c -> ST c
- varName :: a -> [Char]
- runR :: ST a -> ByteString -> a
- runRC :: (Context, ByteString) -> ST a -> ByteString -> a
- runW :: ST () -> ByteString
- readHexp :: (Num a, Integral a) => ST a
- showHexp :: (Num a, Integral a, Show a) => a -> ST ()
- getContext :: ST (Context, ByteString)
Documentation
module Data.RefSerialize.Parser
Methods
Arguments
| :: ST c | read the content of a expression, must be user defined |
Instances
| Serialize String | |
| (Show a, Read a) => Serialize a | defualt instances |
| Serialize a => Serialize [a] | |
| Serialize a => Serialize (Maybe a) | |
| (Serialize a, Serialize b) => Serialize (Either a b) | |
| (Serialize a, Serialize b) => Serialize (a, b) | |
| (Serialize a, Ord a, Serialize b) => Serialize (Map a b) | |
| (Serialize a, Serialize b, Serialize c) => Serialize (a, b, c) | |
| (Serialize a, Serialize b, Serialize c, Serialize d) => Serialize (a, b, c, d) |
showps :: Serialize a => a -> ST ByteStringSource
output the string of the serialized variable
showpText :: Show a => a -> ST ()Source
if a is an instance of Show, showpText can be used as the showp method the drawback is that the data inside is not inspected for common references so it is recommended to create your own readp method for your complex data structures
readpText :: Read a => ST aSource
if a is an instance of Read, readpText can be used as the readp method the drawback is that the data inside is not inspected for common references so it is recommended to create your own readp method for your complex data structures
takep :: Int -> ST ByteStringSource
showpBinary :: Binary a => a -> ST ()Source
serialize a variable which has a Binary instance
readpBinary :: Binary a => ST aSource
deserialize a variable serialized by showpBinary
insertString :: ByteString -> ST ()Source
Write a String in the serialized output with an added whitespace. Deserializable with symbol
insertChar :: Char -> ST ()Source
Write a char in the serialized output (no spaces)
rShow :: Serialize c => c -> ByteStringSource
use the rshowp parser to serialize the object
rShow c= runW $ rshowp c
rRead :: Serialize c => ByteString -> cSource
deserialize trough the rreadp parser
rRead str= runR rreadp $ str
insertVar :: (a -> ST ()) -> a -> ST ()Source
insert a variable at this position. The expression value is inserted in the where section if it is not already
created. If the address of this object being parsed correspond with an address already parsed and
it is in the where section, then the same variable name is used
runW showp (1::Int) -> 1
runW (insertVar showp) (1::Int) -> v1 where { v1=1}
runW (insertVar showp) [(1::Int) ,1] -> [v1.v1] where { v1=1}
This is useful when the object is referenced many times
readVar :: Serialize c => ST c -> ST cSource
deserialize a variable serialized with insertVar. Memory references are restored
runR :: ST a -> ByteString -> aSource
deserialize the string with the parser
runRC :: (Context, ByteString) -> ST a -> ByteString -> aSource
read an expression with the variables definedd in a context passed as parameter.
runW :: ST () -> ByteStringSource
serialize x with the parser
getContext :: ST (Context, ByteString)Source
return the serialized list of variable values
useful for delayed deserialzation of expresions, in case of dynamic variables were deserialization
is done when needed, once the type is known with runRC