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

Portabilityunknown
Stabilityunstable
MaintainerConrad Parker <conrad@metadecks.org>

Data.ZoomCache.Types

Contents

Description

ZoomCache packet and summary types and interfaces

Synopsis

Track types and specification

data Codec Source

Constructors

forall a . ZoomReadable a => Codec a 

Instances

type TrackMap = IntMap TrackSpecSource

A map of all track numbers to their TrackSpec

data TrackSpec Source

A specification of the type and name of each track

Instances

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.

Classes

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 :: TimeStamp -> SummaryWork aSource

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

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

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

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

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

appendSummaryData :: TimeStampDiff -> SummaryData a -> TimeStampDiff -> SummaryData a -> SummaryData aSource

Append two SummaryData

deltaEncodeRaw :: SummaryWork a -> a -> aSource

Delta-encode a value.

data ZoomRaw Source

Constructors

forall a . ZoomReadable a => ZoomRaw [a] 

data ZoomSummary Source

Constructors

forall a . ZoomReadable a => ZoomSummary (Summary a) 

data ZoomWork Source

Constructors

forall a . (Typeable a, ZoomWritable a) => ZoomWork 

Fields

levels :: IntMap (Summary a -> Summary a)
 
currWork :: Maybe (SummaryWork a)
 

Types

data Summary a Source

A recorded block of summary data

Instances

summaryDuration :: Summary a -> TimeStampDiffSource

The duration covered by a summary, in units of 1 / the track's datarate

CacheFile

data CacheFile Source

Global and track headers for a zoom-cache file

Constructors

CacheFile 

mkCacheFile :: Global -> CacheFileSource

Create an empty CacheFile using the given Global

fiFull :: CacheFile -> BoolSource

Determine whether all tracks of a CacheFile are specified