RefSerialize-0.3.0.0: Write to and read from ByteStrings maintaining internal memory references

Safe HaskellNone

Data.RefSerialize

Contents

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.

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; }

Synopsis

Documentation

class Serialize c whereSource

Methods

showpSource

Arguments

:: c 
-> STW ()

shows the content of a expression, must be defined bu the user

readpSource

Arguments

:: STR 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) 

rshowp :: Serialize c => c -> STW ()Source

insert a reference (a variable in the where section).

showps :: Serialize a => a -> STW ByteStringSource

return the serialization instead of updating the writer

rshowps :: Serialize c => c -> STW ByteStringSource

return the variable name of the serialized data, which is put in the context and does not update the writer

runR :: STR a -> ByteString -> aSource

deserialize the string with the parser

runW :: STW () -> ByteStringSource

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 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

showpBinary :: Binary a => a -> STW ()Source

serialize a variable which has a Binary instance

readpBinary :: Binary a => STR aSource

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 -> 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 -> 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

readVar :: Serialize c => STR c -> STR cSource

deserialize a variable serialized with insertVar. Memory references are restored

showHexp :: (Num a, Integral a, Show a) => a -> STW ()Source

Context handling

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

showContext :: Context -> Bool -> ByteStringSource

serialize the variables. if the Bool flag is true, it prepend the text with the string where

runRC :: (Context, ByteString) -> STR a -> ByteString -> aSource

read an expression with the variables definedd in a context passed as parameter.

runWC :: (Context, ByteString) -> STW () -> ByteStringSource

serialize x witn a given context and the parser