Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
NOTE: to avoid long lists of variables with only one reference, now variables not referenced two or more times are inlined so rshowp serializes the same result than showp in these cases. However, showp is faster. In correspondence, rreadp call readp when there is no variable serialized.
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
- rshowp :: Serialize c => c -> STW ()
- rreadp :: Serialize c => STR c
- showps :: Serialize a => a -> STW ByteString
- rshowps :: Serialize t => t -> STW ByteString
- runR :: STR a -> ByteString -> a
- runW :: STW () -> ByteString
- showpText :: Show a => a -> STW ()
- readpText :: Read a => STR a
- showpBinary :: Binary a => a -> STW ()
- readpBinary :: Binary a => STR a
- insertString :: ByteString -> STW ()
- insertChar :: Char -> STW ()
- rShow :: Serialize c => c -> ByteString
- rRead :: Serialize c => ByteString -> c
- insertVar :: (a -> STW ()) -> a -> STW ()
- addrHash :: Context -> a -> IO (Either Int Int)
- readVar :: Serialize c => STR c -> STR c
- takep :: Int64 -> STR ByteString
- readHexp :: (Num a, Integral a) => STR a
- showHexp :: (Num a, Integral a, Show a) => a -> STW ()
- type Context = BasicHashTable Int (StableName MFun, MFun, [ShowF], Int)
- getRContext :: STR (Context, ByteString)
- getWContext :: STW (Context, ByteString)
- newContext :: IO Context
- showContext :: Context -> Bool -> ByteString
- runRC :: (Context, ByteString) -> STR a -> ByteString -> a
- runWC :: (Context, ByteString) -> STW () -> ByteString
Documentation
module Data.RefSerialize.Parser
class Serialize c where Source #
Serialize String Source # | |
Serialize a => Serialize [a] Source # | |
Serialize a => Serialize (Maybe a) Source # | |
(Serialize a, Serialize b) => Serialize (Either a b) Source # | |
(Serialize a, Serialize b) => Serialize (a, b) Source # | |
(Serialize a, Ord a, Serialize b) => Serialize (Map a b) Source # | |
(Serialize a, Serialize b, Serialize c) => Serialize (a, b, c) Source # | |
(Serialize a, Serialize b, Serialize c, Serialize d) => Serialize (a, b, c, d) Source # | |
showps :: Serialize a => a -> STW ByteString Source #
return the serialization instead of updating the writer
rshowps :: Serialize t => t -> STW ByteString Source #
return the variable name of the serialized data, which is put in the context and does not update the writer
runR :: STR a -> ByteString -> a Source #
deserialize the string with the parser
runW :: STW () -> ByteString Source #
serialize x with the parser
showpText :: Show a => a -> STW () 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 => STR a Source #
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
showpBinary :: Binary a => a -> STW () Source #
serialize a variable which has a Binary instance
readpBinary :: Binary a => STR a Source #
deserialize a variable serialized by showpBinary
insertString :: ByteString -> STW () Source #
Write a String in the serialized output with an added whitespace. Deserializable with symbol
insertChar :: Char -> STW () Source #
Write a char in the serialized output (no spaces)
rShow :: Serialize c => c -> ByteString Source #
use the rshowp parser to serialize the object
rShow c= runW $ rshowp c
rRead :: Serialize c => ByteString -> c Source #
deserialize trough the rreadp parser
rRead str= runR rreadp $ str
insertVar :: (a -> STW ()) -> a -> STW () 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
addrHash :: Context -> a -> IO (Either Int Int) Source #
return a unique hash identifier for an object
the context assures that no StableName used in addrStr is garbage collected,
so the hashes are constant and the correspondence address - string
remain one to one as long as the context is not garbage collected.
Left is returned if it is the first time that addHash
is called for that variable
readVar :: Serialize c => STR c -> STR c Source #
deserialize a variable serialized with insertVar. Memory references are restored
Context handling
type Context = BasicHashTable Int (StableName MFun, MFun, [ShowF], Int) Source #
getRContext :: STR (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
getWContext :: STW (Context, ByteString) Source #
newContext :: IO Context Source #
showContext :: Context -> Bool -> ByteString Source #
serialize the variables. if the Bool flag is true, it prepend the text with the string "where"
runRC :: (Context, ByteString) -> STR a -> ByteString -> a Source #
read an expression with the variables definedd in a context passed as parameter.
runWC :: (Context, ByteString) -> STW () -> ByteString Source #
serialize x witn a given context and the parser