Safe Haskell | None |
---|---|
Language | Haskell2010 |
Functions to make it easier to write ASIF files without needing to deal with raw Handles and ByteStrings too much.
Synopsis
- writeAsif :: (Foldable f, MonadResource m) => Handle -> String -> Maybe POSIXTime -> FoldM m a [Segment Handle] -> f a -> m ()
- asifContent :: (Foldable f, MonadResource m) => String -> Maybe POSIXTime -> FoldM m a [Segment Handle] -> f a -> m ByteString
- asifContentC :: (Foldable f, MonadResource m) => String -> Maybe POSIXTime -> FoldM m a [Segment Handle] -> f a -> ConduitT () ByteString m ()
- lazyByteStringSegment :: MonadResource m => Whatever Format -> (a -> ByteString) -> Text -> FoldM m a [Segment Handle]
- nullTerminatedStringSegment :: MonadResource m => (a -> Text) -> Text -> FoldM m a [Segment Handle]
- textSegment :: MonadResource m => (a -> Text) -> Text -> FoldM m a [Segment Handle]
- asciiSegment :: MonadResource m => (a -> Char) -> Text -> FoldM m a [Segment Handle]
- boolSegment :: MonadResource m => (a -> Bool) -> Text -> FoldM m a [Segment Handle]
- word8Segment :: MonadResource m => (a -> Word8) -> Text -> FoldM m a [Segment Handle]
- word16Segment :: MonadResource m => (a -> Word16) -> Text -> FoldM m a [Segment Handle]
- word32Segment :: MonadResource m => (a -> Word32) -> Text -> FoldM m a [Segment Handle]
- word64Segment :: MonadResource m => (a -> Word64) -> Text -> FoldM m a [Segment Handle]
- int8Segment :: MonadResource m => (a -> Int8) -> Text -> FoldM m a [Segment Handle]
- int16Segment :: MonadResource m => (a -> Int16) -> Text -> FoldM m a [Segment Handle]
- int32Segment :: MonadResource m => (a -> Int32) -> Text -> FoldM m a [Segment Handle]
- int64Segment :: MonadResource m => (a -> Int64) -> Text -> FoldM m a [Segment Handle]
- ipv4Segment :: MonadResource m => (a -> IPv4) -> Text -> FoldM m a [Segment Handle]
- ipv6Segment :: MonadResource m => (a -> IPv6) -> Text -> FoldM m a [Segment Handle]
- utcTimeMicrosSegment :: MonadResource m => (a -> UTCTime) -> Text -> FoldM m a [Segment Handle]
- genericInitial :: MonadResource m => Text -> m Handle
- genericStep :: MonadResource m => (a -> Builder) -> Handle -> a -> m Handle
- genericExtract :: MonadResource m => Text -> Whatever Format -> Handle -> m [Segment Handle]
- genericFold :: MonadResource m => (a -> Builder) -> Whatever Format -> (b -> a) -> Text -> FoldM m b [Segment Handle]
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
Segment
s.
FoldM
s 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
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 Text
s.
asciiSegment :: MonadResource m => (a -> Char) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Char
s.
boolSegment :: MonadResource m => (a -> Bool) -> Text -> FoldM m a [Segment Handle] Source #
word8Segment :: MonadResource m => (a -> Word8) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Word8
s.
word16Segment :: MonadResource m => (a -> Word16) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Word16
s.
word32Segment :: MonadResource m => (a -> Word32) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Word32
s.
word64Segment :: MonadResource m => (a -> Word64) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Word64
s.
int8Segment :: MonadResource m => (a -> Int8) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Int8
s.
int16Segment :: MonadResource m => (a -> Int16) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Int16
s.
int32Segment :: MonadResource m => (a -> Int32) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Int32
s.
int64Segment :: MonadResource m => (a -> Int64) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of Int64
s.
ipv4Segment :: MonadResource m => (a -> IPv4) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of IPv4
s.
ipv6Segment :: MonadResource m => (a -> IPv6) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of IPv6
s.
utcTimeMicrosSegment :: MonadResource m => (a -> UTCTime) -> Text -> FoldM m a [Segment Handle] Source #
Builds a segment of UTCTime
s, accurate to microseconds.
Utility functions
Helper functions for creating FoldM
s from scratch.
genericInitial :: MonadResource m => Text -> m Handle Source #
genericStep :: MonadResource m => (a -> Builder) -> Handle -> a -> m Handle Source #
genericExtract :: MonadResource m => Text -> Whatever Format -> Handle -> m [Segment Handle] Source #