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

Portabilityunknown
Stabilityunstable
MaintainerConrad Parker <conrad@metadecks.org>

Data.ZoomCache

Contents

Description

API for implementing ZoomCache applications

Synopsis

TimeStamps

newtype TimeStampDiff Source

Constructors

TSDiff Double 

timeStampDiff :: TimeStamp -> TimeStamp -> TimeStampDiffSource

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

Types

data Codec Source

Constructors

forall a . ZoomReadable a => Codec a 

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.

data SampleRateType Source

Constant or Variable samplerate. For constant samplerate, timestamps are implied as incrementing by 1/samplerate For variable samplerate, explicit timestamps are attached to each datum, encoded as a separate block of SampleOffset in the Raw Data packet.

Constructors

ConstantSR 
VariableSR 

data CacheFile Source

Global and track headers for a zoom-cache file

Constructors

CacheFile 

class Typeable a => ZoomReadable a whereSource

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

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

data ZoomRaw Source

Constructors

forall a . ZoomReadable a => ZoomRaw [a] 

data ZoomSummary Source

Constructors

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

data Summary a Source

A summary block with samplecounts converted to TimeStamp

data ZoomSummarySO Source

Constructors

forall a . ZoomReadable a => ZoomSummarySO (SummarySO a) 

data SummarySO a Source

A recorded block of summary data

Instances

Track specification

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

The ZoomWrite class

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.

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.

The ZoomW monad

type ZoomW = StateT ZoomWHandle IOSource

A StateT IO monad for writing a ZoomCache file

withFileWriteSource

Arguments

:: TrackMap 
-> Bool

Whether or not to write raw data packets. If False, only summary blocks are written.

-> ZoomW () 
-> FilePath 
-> IO () 

Run a ZoomW () action on a given file handle, using the specified TrackMap specification

flush :: ZoomW ()Source

Force a flush of ZoomCache summary blocks to disk. It is not usually necessary to call this function as summary blocks are transparently written at regular intervals.

ZoomWHandle IO functions

openWriteSource

Arguments

:: TrackMap 
-> Bool

Whether or not to write raw data packets. If False, only summary blocks are written.

-> FilePath 
-> IO ZoomWHandle 

Open a new ZoomCache file for writing, using a specified TrackMap.

Watermarks

watermark :: TrackNo -> ZoomW (Maybe Int)Source

Query the maximum number of data points to buffer for a given track before forcing a flush of all buffered data and summaries.

setWatermark :: TrackNo -> Int -> ZoomW ()Source

Set the maximum number of data points to buffer for a given track before forcing a flush of all buffered data and summaries.

TrackSpec helpers

oneTrack :: ZoomReadable a => a -> Bool -> Bool -> SampleRateType -> Rational -> ByteString -> TrackMapSource

Create a track map for a stream of a given type, as track no. 1

Standard identifiers

standardIdentifiers :: [IdentifyCodec]Source

IdentifyTrack functions provided for standard codecs provided by the zoom-cache library.

Iteratee parsers

Pretty printing