monad-codec-0.2.0: Monadic conversion between complex data structures and unique integers

Safe HaskellNone

Control.Monad.Codec

Description

The Codec monad provides functions for encoding and decoding complex data structures with unique integer numbers. In the simplest case the entire sturecture can be transformed to unique atom (see example1 below). When it is not sufficient to encode the input object with one codec, more complex codec structure can be used (see example2 below). The library relies on a 'data-lens' package which provides types and functions for codec manipulations.

Example:

 example1 = evalCodec empty $ do
     let xs = "abcabd"
     ys <- mapM (encode idLens) xs
     zs <- mapM (decode idLens) ys
     return $ zip zs ys
>>> example1
>>> [('a',0),('b',1),('c',2),('a',0),('b',1),('d',3)]
 example2 = evalCodec (empty, empty) $ do
     let xs = zip "abcabd" [1, 34342, 5435, 34342, 124, 1]
     ys <- forM xs $ \(x, y) ->
         (,) <$> encode fstLens x <*> encode sndLens y
     zs <- forM ys $ \(i, j) -> 
         (,) <$> decode fstLens i <*> decode sndLens j
     return (zs, ys)
>>> fst example2
>>> [('a',1),('b',34342),('c',5435),('a',34342),('b',124),('d',1)]
>>> snd example2
>>> [(0,0),(1,1),(2,2),(0,1),(1,3),(3,0)]

Synopsis

Documentation

data Codec c a Source

A Codec monad preserves mappings between objects and respective codec components.

Instances

data AtomCodec a Source

Atomic Codec component, which represents to and fro mapping between a objects and unique intergers.

Constructors

AtomCodec 

Fields

to :: !(Map a Int)
 
from :: !(IntMap a)
 

Instances

(Ord a, Binary a) => Binary (AtomCodec a) 

empty :: AtomCodec aSource

Empty codec component.

type AtomLens c a = Lens c (AtomCodec a)Source

Just a type synonym for a lens between codec and codec component.

maybeEncode :: Ord a => AtomLens c a -> a -> Codec c (Maybe Int)Source

Encode the object with codec component identified by the lens. Return Nothing if the object is not present in the atomic codec component.

encode :: Ord a => AtomLens c a -> a -> Codec c IntSource

Encode the object with codec component identified by the lens.

encode' :: Ord a => AtomLens c a -> a -> Codec c IntSource

Version of encode which doesn't update the return componenent of the atom codec. It is useful when we know that particular value (e.g. value of a condition observation) won't be decoded afterwards so there is no need to store it and waste memory.

maybeDecode :: Ord a => AtomLens c a -> Int -> Codec c (Maybe a)Source

Decode the number with codec component identified by the lens. Return Nothing if the object is not present in the atomic codec component.

decode :: Ord a => AtomLens c a -> Int -> Codec c aSource

Decode the number with codec component identified by the lens. Report error when the number is not present in the codec component.

runCodec :: c -> Codec c a -> (a, c)Source

Run the Codec monad with the initial codec value. Return both the result and the final codec state. The obtained codec can be used next to perform subsequent decoding or encoding.

evalCodec :: c -> Codec c a -> aSource

Evaluate the Codec monad with the initial codec value. Only the monad result will be returned.

execCodec :: c -> Codec c a -> cSource

Execute the Codec monad with the initial codec value. Only the final codec state will be returned.

idLens :: Lens a aSource

Identity lenses should be used whenever the structure of the codec is simple, i.e. only one atomic codec is used.