Portability | unknown |
---|---|
Stability | unstable |
Maintainer | Conrad Parker <conrad@metadecks.org> |
ZoomCache packet and summary types and interfaces
- data Codec = forall a . ZoomReadable a => Codec a
- type TrackMap = IntMap TrackSpec
- data TrackSpec = TrackSpec {
- specType :: !Codec
- specDeltaEncode :: !Bool
- specZlibCompress :: !Bool
- specDRType :: !DataRateType
- specRate :: !Rational
- specName :: !ByteString
- type IdentifyCodec = ByteString -> Maybe Codec
- class Typeable a => ZoomReadable a where
- data SummaryData a :: *
- trackIdentifier :: a -> ByteString
- readRaw :: (Functor m, Monad m) => Iteratee ByteString m a
- readSummary :: (Functor m, Monad m) => Iteratee ByteString m (SummaryData a)
- prettyRaw :: a -> String
- prettySummaryData :: SummaryData a -> String
- deltaDecodeRaw :: [a] -> [a]
- class ZoomReadable a => ZoomWritable a where
- data SummaryWork a :: *
- fromRaw :: a -> Builder
- fromSummaryData :: SummaryData a -> Builder
- initSummaryWork :: TimeStamp -> SummaryWork a
- updateSummaryData :: TimeStamp -> a -> SummaryWork a -> SummaryWork a
- toSummaryData :: TimeStampDiff -> SummaryWork a -> SummaryData a
- appendSummaryData :: TimeStampDiff -> SummaryData a -> TimeStampDiff -> SummaryData a -> SummaryData a
- deltaEncodeRaw :: SummaryWork a -> a -> a
- data ZoomRaw = forall a . ZoomReadable a => ZoomRaw [a]
- data ZoomSummary = forall a . ZoomReadable a => ZoomSummary (Summary a)
- data ZoomWork = forall a . (Typeable a, ZoomWritable a) => ZoomWork {}
- data Packet = Packet {
- packetTrack :: !TrackNo
- packetEntryTime :: !TimeStamp
- packetExitTime :: !TimeStamp
- packetCount :: !Int
- packetData :: !ZoomRaw
- packetTimeStamps :: ![TimeStamp]
- data Summary a = Summary {
- summaryTrack :: !TrackNo
- summaryLevel :: !Int
- summaryEntryTime :: !TimeStamp
- summaryExitTime :: !TimeStamp
- summaryData :: !(SummaryData a)
- summaryDuration :: Summary a -> TimeStampDiff
- data CacheFile = CacheFile {}
- mkCacheFile :: Global -> CacheFile
- fiFull :: CacheFile -> Bool
Track types and specification
A specification of the type and name of each track
TrackSpec | |
|
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.
data SummaryData a :: *Source
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
data SummaryWork a :: *Source
Intermediate calculations
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.
forall a . ZoomReadable a => ZoomRaw [a] |
data ZoomSummary Source
forall a . ZoomReadable a => ZoomSummary (Summary a) |
forall a . (Typeable a, ZoomWritable a) => ZoomWork | |
Types
Packet | |
|
A recorded block of summary data
Summary | |
|
summaryDuration :: Summary a -> TimeStampDiffSource
The duration covered by a summary, in units of 1 / the track's datarate
CacheFile
Global and track headers for a zoom-cache file