zoom-cache-0.4.0.0: A streamable, seekable, zoomable cache file format

Portabilityunknown
Stabilityunstable
MaintainerConrad Parker <conrad@metadecks.org>

Data.ZoomCache.Codec

Contents

Description

This module re-exports the required interfaces and some useful functions for developing zoom-cache codecs.

To implement a codec, specify SummaryData and SummaryWork types, and implement the methods of the ZoomReadable and ZoomWritable classes.

For sample implementations, read the source of the provided instances Data.ZoomCache.Int and Data.ZoomCache.Double.

Synopsis

Required interfaces

class ZoomReadable a whereSource

A codec instance must specify a SummaryData type, and implement all methods of this class.

Associated Types

data SummaryData a :: *Source

Summaries of a subsequence of values of type a. In the default instances for Int and Double, this is a record containing values such as the maximum, minimum and mean of the subsequence.

Methods

readRaw :: (Functor m, MonadIO m) => Iteratee [Word8] m aSource

An iteratee to read one value of type a from a stream of '[Word8]'.

readSummary :: (Functor m, MonadIO m) => Iteratee [Word8] m (SummaryData a)Source

An iteratee to read one value of type 'SummaryData a' from a stream of '[Word8]'.

prettyRaw :: a -> StringSource

Pretty printing, used for dumping values of type a.

prettySummaryData :: SummaryData a -> StringSource

Pretty printing for values of type 'SummaryData a'.

class ZoomWritable a whereSource

A codec instance must additionally specify a SummaryWork type

Associated Types

data SummaryWork a :: *Source

Intermediate calculations

Methods

fromRaw :: a -> BuilderSource

Serialize a value of type a

fromSummaryData :: SummaryData a -> BuilderSource

Serialize a 'SummaryData a'

initSummaryWork :: TimeStamp -> SummaryWork aSource

Generate a new 'SummaryWork a', given an initial timestamp.

updateSummaryData :: Int -> TimeStamp -> a -> SummaryWork a -> SummaryWork aSource

Update a SummaryData with the value of a occuring at the given TimeStamp.

toSummaryData :: Double -> SummaryWork a -> SummaryData aSource

Finalize a 'SummaryWork a', generating a 'SummaryData a'.

appendSummaryData :: Double -> SummaryData a -> Double -> SummaryData a -> SummaryData aSource

Append two SummaryData

class ZoomWrite t whereSource

The ZoomWrite class provides write, a method to write a Haskell value to an open ZoomCache file.

Methods

write :: TrackNo -> t -> ZoomW ()Source

Write a value to an open ZoomCache file.

Raw data reading iteratees

readInt16be :: (Functor m, MonadIO m) => Iteratee [Word8] m IntSource

Read 2 bytes as a big-endian Int.

readInt32be :: (Functor m, MonadIO m) => Iteratee [Word8] m IntSource

Read 4 bytes as a big-endian Int.

readInt64be :: (Functor m, MonadIO m, Integral a) => Iteratee [Word8] m aSource

Read 8 bytes as a big-endian Integer

readDouble64be :: (Functor m, MonadIO m) => Iteratee [Word8] m DoubleSource

Read 8 bytes as a big-endian Double

readRational64be :: (Functor m, MonadIO m) => Iteratee [Word8] m RationalSource

Read 16 bytes as a big-endian Rational, encoded as an 8 byte big endian numerator followed by an 8 byte big endian denominator.

ZoomWrite instance helpers

Builders

fromRational64 :: Rational -> BuilderSource

Serialize a Rational as a sequence of two 64bit big endian format integers.

fromIntegral32be :: forall a. Integral a => a -> BuilderSource

Serialize an Integral in 32bit big endian format.

fromDouble :: Double -> BuilderSource

Serialize a Double in big-endian IEEE 754-2008 binary64 format (IEEE 754-1985 double format).

ZoomCache Types