zoom-cache-1.2.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.Numeric.Int and Data.ZoomCache.Numeric.Double.

Synopsis

Required interfaces

class Typeable a => 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

trackIdentifier :: a -> ByteStringSource

The track identifier used for streams of type a. The value of the argument should be ignored by any instance of ZoomReadable, so that is safe to pass undefined as the argument.

readRaw :: (Functor m, Monad m) => Iteratee ByteString m aSource

An iteratee to read one value of type a from a stream of ByteString.

readSummary :: (Functor m, Monad m) => Iteratee ByteString m (SummaryData a)Source

An iteratee to read one value of type 'SummaryData a' from a stream of ByteString.

prettyRaw :: a -> StringSource

Pretty printing, used for dumping values of type a.

prettySummaryData :: SummaryData a -> StringSource

Pretty printing for values of type 'SummaryData a'.

deltaDecodeRaw :: [a] -> [a]Source

Delta-decode a list of values

class ZoomReadable a => 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 :: SampleOffset -> SummaryWork aSource

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

updateSummaryData :: SampleOffset -> a -> SummaryWork a -> SummaryWork aSource

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

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

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

appendSummaryData :: SampleOffsetDiff -> SummaryData a -> SampleOffsetDiff -> SummaryData a -> SummaryData aSource

Append two SummaryData

deltaEncodeRaw :: SummaryWork a -> a -> aSource

Delta-encode a value.

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.

Identification

type IdentifyCodec = ByteString -> Maybe CodecSource

Identify the tracktype corresponding to a given Codec Identifier. When parsing a zoom-cache file, the zoom-cache library will try each of a given list [IdentifyTrack].

The standard zoom-cache instances are provided in standardIdentifiers.

When developing your own codecs it is not necessary to build a composite IdentifyTrack functions; it is sufficient to generate one for each new codec type. A library of related zoom-cache codecs should export its own [IdentifyTrack] functions, usually called something like mylibIdentifiers.

These can be generated with identifyCodec.

identifyCodec :: ZoomReadable a => a -> IdentifyCodecSource

Generate an IdentifyTrack function for a given type.

Raw data reading iteratees

readInt8 :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 1 byte as a signed Integral

readInt16be :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 2 bytes as a big-endian signed Integral

readInt32be :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 4 bytes as a big-endian signed Integral

readInt64be :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 8 bytes as a big-endian signed Integral

readWord8 :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 1 byte as an unsigned Integral

readWord16be :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 2 bytes as a big-endian unsigned Integral

readWord32be :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 4 bytes as a big-endian unsigned Integral

readWord64be :: (Nullable s, ListLike s Word8, Functor m, Monad m, Integral a) => Iteratee s m aSource

Read 8 bytes as a big-endian unsigned Integral

readIntegerVLC :: (Nullable s, ListLike s Word8, Functor m, Monad m) => Iteratee s m IntegerSource

Read a variable-length-coded Integer. For details of the variable-length coding format, see Data.ZoomCache.Numeric.Int.

readFloat32be :: (Nullable s, ListLike s Word8, Functor m, Monad m) => Iteratee s m FloatSource

Read 4 bytes as a big-endian Float

readDouble64be :: (Nullable s, ListLike s Word8, Functor m, Monad m) => Iteratee s m DoubleSource

Read 8 bytes as a big-endian Double

readRational64be :: (Nullable s, ListLike s Word8, Functor m, Monad m) => Iteratee s 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

type ZoomW = StateT ZoomWHandle IOSource

A StateT IO monad for writing a ZoomCache file

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.

fromIntegerVLC :: Integer -> BuilderSource

Serialize an Integer in variable-length-coding format For details of the variable-length coding format, see Data.ZoomCache.Numeric.Int.

fromFloat :: Float -> BuilderSource

Serialize a Float in big-endian IEEE 754-2008 binary32 format (IEEE 754-1985 single format).

fromDouble :: Double -> BuilderSource

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

ZoomCache Types

data Codec Source

Instances

newtype TimeStampDiff Source

Constructors

TSDiff Double 

timeStampDiff :: TimeStamp -> TimeStamp -> TimeStampDiffSource

timeStampDiff (TS t1) (TS t2) = TSDiff (t1 - t2)

sampleOffsetDiff :: SampleOffset -> SampleOffset -> SampleOffsetDiffSource

sampleOffsetDiff (SO t1) (SO t2) = SODiff (t1 - t2)

Delta encoding

Minimum and maximum floating point