zoom-cache-0.6.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

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 DataRateType Source

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

Constructors

ConstantDR 
VariableDR 

Instances

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

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

readSummary :: (Nullable s, ListLike s Word8, Functor m, Monad m) => Iteratee s m (SummaryData a)Source

An iteratee to read one value of type 'SummaryData a' from a stream of something like '[Word8]' or 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'.

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 recorded block of summary data

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

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 -> DataRateType -> 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