asif-6.0.3: Library for creating and querying segmented feeds

Safe HaskellNone
LanguageHaskell2010

Arbor.File.Format.Asif.Write

Contents

Description

Functions to make it easier to write ASIF files without needing to deal with raw Handles and ByteStrings too much.

Synopsis

Encode an entire ASIF bytestring

Facilities for writing an entire ASIF file, either to an actual file or to a ByteString.

  • * Usage: Use the various *segment functions to produce a FoldM. These are designed to allow you to take some large type (e.g. a tuple or a product type) and pull out the constituent pieces to encode into Segments.

FoldMs are composable using <>. Once you have a single, provide it to writeAsif or asifContent along with an appropriate foldable. Both these functions will stream from the input, assuming the foldable is something that can be streamed from.

writeAsif :: (Foldable f, MonadResource m) => Handle -> String -> Maybe POSIXTime -> FoldM m a [Segment Handle] -> f a -> m () Source #

Write an ASIF file to the supplied handle. Streams the input foldable if possible.

asifContent :: (Foldable f, MonadResource m) => String -> Maybe POSIXTime -> FoldM m a [Segment Handle] -> f a -> m ByteString Source #

Builds a lazy ASIF bytestring. Streams the input foldable if possible.

asifContentC :: (Foldable f, MonadResource m) => String -> Maybe POSIXTime -> FoldM m a [Segment Handle] -> f a -> ConduitT () ByteString m () Source #

Returns ASIF content as a conduit

Folds for Segments

Use these to build FoldMs for the types you want to encode. Compose them together using <>.

lazyByteStringSegment :: MonadResource m => Whatever Format -> (a -> ByteString) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment from lazy bytestrings. This can in priciple cover any bytestring-y format, including StringZ, Text, Binary, Bitmap, and Bitstring, as well as unknown encodings. Correctly encoding the value is the responsibility of the caller.

nullTerminatedStringSegment :: MonadResource m => (a -> Text) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of null-termianted strings. Note that the input itself does *not* need to be null-terminated. The null-termination is added by this function.

textSegment :: MonadResource m => (a -> Text) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Texts.

asciiSegment :: MonadResource m => (a -> Char) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Chars.

boolSegment :: MonadResource m => (a -> Bool) -> Text -> FoldM m a [Segment Handle] Source #

Build a segment of Bools, encoded as Word8s, where False == 0, and True == 1

word8Segment :: MonadResource m => (a -> Word8) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Word8s.

word16Segment :: MonadResource m => (a -> Word16) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Word16s.

word32Segment :: MonadResource m => (a -> Word32) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Word32s.

word64Segment :: MonadResource m => (a -> Word64) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Word64s.

int8Segment :: MonadResource m => (a -> Int8) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Int8s.

int16Segment :: MonadResource m => (a -> Int16) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Int16s.

int32Segment :: MonadResource m => (a -> Int32) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Int32s.

int64Segment :: MonadResource m => (a -> Int64) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of Int64s.

ipv4Segment :: MonadResource m => (a -> IpAddress) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of IPv4s.

ipv6Segment :: MonadResource m => (a -> IpAddress) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of IPv6s.

ipv4BlockSegment :: MonadResource m => (a -> IpBlock Canonical) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of IPv4 CIDR blocks

ipv6BlockSegment :: MonadResource m => (a -> IpBlock Canonical) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of IPv6 CIDR blocks

utcTimeMicrosSegment :: MonadResource m => (a -> UTCTime) -> Text -> FoldM m a [Segment Handle] Source #

Builds a segment of UTCTimes, accurate to microseconds.

Lookup segments

lookupSegment Source #

Arguments

:: (MonadResource m, Ord b, Eq i, Num i, Bounded i) 
=> Text

Lookup segment name

-> (a -> Maybe b)

Extract "dictionary" value

-> Whatever Format

Format of lookup segment

-> (i -> Builder)

Write a lookup value

-> FoldM m b [Segment Handle]

A fold that represents a dictionary segment

-> FoldM m a [Segment Handle] 

Creates a lookup segment for every input into a value in an "inner" dictionary segment. Missing values are represented as maxBound for the key type.

word16LookupSegment :: (MonadResource m, Ord b) => Text -> (a -> Maybe b) -> FoldM m b [Segment Handle] -> FoldM m a [Segment Handle] Source #

Creates a lookup segment where index keys are Word16 Missing values are represented by 'maxBound :: Word16'

word16LookupSegment name f = lookupSegment name f (Known F.Word16LE) BB.word16LE

word32LookupSegment :: (MonadResource m, Ord b) => Text -> (a -> Maybe b) -> FoldM m b [Segment Handle] -> FoldM m a [Segment Handle] Source #

Creates a lookup segment where index keys are Word32 Missing values are represented by 'maxBound :: Word32'

word32LookupSegment name f = lookupSegment name f (Known F.Word32LE) BB.word32LE

word64LookupSegment :: (MonadResource m, Ord b) => Text -> (a -> Maybe b) -> FoldM m b [Segment Handle] -> FoldM m a [Segment Handle] Source #

Creates a lookup segment where index keys are Word64 Missing values are represented by 'maxBound :: Word64'

word64LookupSegment name f = lookupSegment name f (Known F.Word64LE) BB.word64LE

Utility functions

Helper functions for creating FoldMs from scratch.

genericStep :: MonadResource m => (a -> Builder) -> Handle -> a -> m Handle Source #

genericFold :: MonadResource m => (a -> Builder) -> Whatever Format -> (b -> a) -> Text -> FoldM m b [Segment Handle] Source #