repa-convert-4.2.3.2: Packing and unpacking flat tables.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Convert.Format

Contents

Description

This module provides the Format class definition, without exporting the pre-defined formats.

Synopsis

Packing single fields

class Format f where Source #

Relates a storage format to the Haskell type of the value that is stored in that format.

Associated Types

type Value f Source #

Get the type of a value with this format.

Methods

fieldCount :: f -> Int Source #

Yield the number of separate fields in this format.

minSize :: f -> Int Source #

Yield the minumum number of bytes that a value of this format will take up.

Packing a value into this format is guaranteed to use at least this many bytes. This is exact for fixed-size formats.

fixedSize :: f -> Maybe Int Source #

For fixed size formats, yield their size (length) in bytes.

Yields Nothing if this is not a fixed size format.

packedSize :: f -> Value f -> Maybe Int Source #

Yield the maximum packed size of the value in this format.

If fixedSize returns a size then packedSize returns the same size.

For variable length formats, packedSize is an over-approximation. We allow the actual packed value to use less space, as it may not be possible to determine how much space it needs without actually packing it.

Yields Nothing when a collection of values is to be packed into a fixed length format, but the size of the collection does not match the format.

Instances
Format () Source # 
Instance details

Defined in Data.Repa.Convert.Format.Fields

Associated Types

type Value () :: Type Source #

Methods

fieldCount :: () -> Int Source #

minSize :: () -> Int Source #

fixedSize :: () -> Maybe Int Source #

packedSize :: () -> Value () -> Maybe Int Source #

Format DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Associated Types

type Value DoubleFixedPack :: Type Source #

Format DoubleAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Associated Types

type Value DoubleAsc :: Type Source #

Format IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Associated Types

type Value IntAsc0 :: Type Source #

Format IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Associated Types

type Value IntAsc :: Type Source #

Format VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Associated Types

type Value VarBytes :: Type Source #

Format Float64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Float64be :: Type Source #

Format Float32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Float32be :: Type Source #

Format Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int64be :: Type Source #

Format Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word64be :: Type Source #

Format Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int32be :: Type Source #

Format Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word32be :: Type Source #

Format Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int16be :: Type Source #

Format Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word16be :: Type Source #

Format Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int8be :: Type Source #

Format Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word8be :: Type Source #

Format ExactChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Associated Types

type Value ExactChars :: Type Source #

Format VarCharString Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Associated Types

type Value VarCharString :: Type Source #

Format VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Associated Types

type Value VarChars :: Type Source #

Format FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Associated Types

type Value FixChars :: Type Source #

Format UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Associated Types

type Value UnitAsc :: Type Source #

Format VarTextString Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Associated Types

type Value VarTextString :: Type Source #

Format VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Associated Types

type Value VarText :: Type Source #

Format DDsMMsYYYY Source # 
Instance details

Defined in Data.Repa.Convert.Format.Date32

Associated Types

type Value DDsMMsYYYY :: Type Source #

Format YYYYsMMsDD Source # 
Instance details

Defined in Data.Repa.Convert.Format.Date32

Associated Types

type Value YYYYsMMsDD :: Type Source #

Format f => Format (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Associated Types

type Value (MaybeBytes f) :: Type Source #

Format f => Format (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Associated Types

type Value (MaybeChars f) :: Type Source #

Format (Sep ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Associated Types

type Value (Sep ()) :: Type Source #

Methods

fieldCount :: Sep () -> Int Source #

minSize :: Sep () -> Int Source #

fixedSize :: Sep () -> Maybe Int Source #

packedSize :: Sep () -> Value (Sep ()) -> Maybe Int Source #

(Format f1, Format (Sep fs), Value (Sep fs) ~ Value fs) => Format (Sep (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Associated Types

type Value (Sep (f1 :*: fs)) :: Type Source #

Methods

fieldCount :: Sep (f1 :*: fs) -> Int Source #

minSize :: Sep (f1 :*: fs) -> Int Source #

fixedSize :: Sep (f1 :*: fs) -> Maybe Int Source #

packedSize :: Sep (f1 :*: fs) -> Value (Sep (f1 :*: fs)) -> Maybe Int Source #

(Format (ObjectFields fs), Value (ObjectFields fs) ~ Value fs) => Format (Object fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Associated Types

type Value (Object fs) :: Type Source #

Format (App ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Associated Types

type Value (App ()) :: Type Source #

Methods

fieldCount :: App () -> Int Source #

minSize :: App () -> Int Source #

fixedSize :: App () -> Maybe Int Source #

packedSize :: App () -> Value (App ()) -> Maybe Int Source #

(Format f1, Format (App fs), Value (App fs) ~ Value fs) => Format (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Associated Types

type Value (App (f1 :*: fs)) :: Type Source #

Methods

fieldCount :: App (f1 :*: fs) -> Int Source #

minSize :: App (f1 :*: fs) -> Int Source #

fixedSize :: App (f1 :*: fs) -> Maybe Int Source #

packedSize :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Maybe Int Source #

(Format a, Format b) => Format (a :*: b) Source #

Formatting fields.

Instance details

Defined in Data.Repa.Convert.Format.Fields

Associated Types

type Value (a :*: b) :: Type Source #

Methods

fieldCount :: (a :*: b) -> Int Source #

minSize :: (a :*: b) -> Int Source #

fixedSize :: (a :*: b) -> Maybe Int Source #

packedSize :: (a :*: b) -> Value (a :*: b) -> Maybe Int Source #

Packable

class Format format => Packable format where Source #

Class of storage formats that can have values packed and unpacked from foreign bufferes.

The methods are written using continuations to make it easier for GHC to optimise its core code when packing/unpacking many fields.

Minimal complete definition

packer

Methods

pack Source #

Arguments

:: format

Storage format.

-> Value format

Value to pack.

-> Packer

Packer that can write the value.

Pack a value into a buffer using the given format.

packer Source #

Arguments

:: format

Data format.

-> Value format

Value to pack.

-> Addr#

Pointer to start of buffer.

-> IO ()

Signal failure.

-> (Addr# -> IO ())

Accept the address after the packed field.

-> IO () 

Low level packing function for the given format.

Instances
Packable () Source # 
Instance details

Defined in Data.Repa.Convert.Format.Fields

Methods

pack :: () -> Value () -> Packer Source #

packer :: () -> Value () -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Packable DoubleAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

pack :: DoubleAsc -> Value DoubleAsc -> Packer Source #

packer :: DoubleAsc -> Value DoubleAsc -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

pack :: IntAsc0 -> Value IntAsc0 -> Packer Source #

packer :: IntAsc0 -> Value IntAsc0 -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

pack :: IntAsc -> Value IntAsc -> Packer Source #

packer :: IntAsc -> Value IntAsc -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Methods

pack :: VarBytes -> Value VarBytes -> Packer Source #

packer :: VarBytes -> Value VarBytes -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Float64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Float64be -> Value Float64be -> Packer Source #

packer :: Float64be -> Value Float64be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Float32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Float32be -> Value Float32be -> Packer Source #

packer :: Float32be -> Value Float32be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int64be -> Value Int64be -> Packer Source #

packer :: Int64be -> Value Int64be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word64be -> Value Word64be -> Packer Source #

packer :: Word64be -> Value Word64be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int32be -> Value Int32be -> Packer Source #

packer :: Int32be -> Value Int32be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word32be -> Value Word32be -> Packer Source #

packer :: Word32be -> Value Word32be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int16be -> Value Int16be -> Packer Source #

packer :: Int16be -> Value Int16be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word16be -> Value Word16be -> Packer Source #

packer :: Word16be -> Value Word16be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int8be -> Value Int8be -> Packer Source #

packer :: Int8be -> Value Int8be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word8be -> Value Word8be -> Packer Source #

packer :: Word8be -> Value Word8be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable ExactChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

pack :: ExactChars -> Value ExactChars -> Packer Source #

packer :: ExactChars -> Value ExactChars -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable VarCharString Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Packable VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

pack :: VarChars -> Value VarChars -> Packer Source #

packer :: VarChars -> Value VarChars -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

pack :: FixChars -> Value FixChars -> Packer Source #

packer :: FixChars -> Value FixChars -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Methods

pack :: UnitAsc -> Value UnitAsc -> Packer Source #

packer :: UnitAsc -> Value UnitAsc -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable VarTextString Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Packable VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Methods

pack :: VarText -> Value VarText -> Packer Source #

packer :: VarText -> Value VarText -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable DDsMMsYYYY Source # 
Instance details

Defined in Data.Repa.Convert.Format.Date32

Methods

pack :: DDsMMsYYYY -> Value DDsMMsYYYY -> Packer Source #

packer :: DDsMMsYYYY -> Value DDsMMsYYYY -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable YYYYsMMsDD Source # 
Instance details

Defined in Data.Repa.Convert.Format.Date32

Methods

pack :: YYYYsMMsDD -> Value YYYYsMMsDD -> Packer Source #

packer :: YYYYsMMsDD -> Value YYYYsMMsDD -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable f => Packable (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

pack :: MaybeBytes f -> Value (MaybeBytes f) -> Packer Source #

packer :: MaybeBytes f -> Value (MaybeBytes f) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable f => Packable (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

pack :: MaybeChars f -> Value (MaybeChars f) -> Packer Source #

packer :: MaybeChars f -> Value (MaybeChars f) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable (Sep ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep () -> Value (Sep ()) -> Packer Source #

packer :: Sep () -> Value (Sep ()) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Packable f1, Packable (Sep (f2 :*: fs)), Value (Sep (f2 :*: fs)) ~ Value (f2 :*: fs), Value (Sep fs) ~ Value fs) => Packable (Sep (f1 :*: (f2 :*: fs))) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep (f1 :*: (f2 :*: fs)) -> Value (Sep (f1 :*: (f2 :*: fs))) -> Packer Source #

packer :: Sep (f1 :*: (f2 :*: fs)) -> Value (Sep (f1 :*: (f2 :*: fs))) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Packable f1, Value (Sep ()) ~ Value ()) => Packable (Sep (f1 :*: ())) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep (f1 :*: ()) -> Value (Sep (f1 :*: ())) -> Packer Source #

packer :: Sep (f1 :*: ()) -> Value (Sep (f1 :*: ())) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Format (Object f), Value (ObjectFields f) ~ Value f, Packable (ObjectFields f)) => Packable (Object f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Methods

pack :: Object f -> Value (Object f) -> Packer Source #

packer :: Object f -> Value (Object f) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable (App ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

pack :: App () -> Value (App ()) -> Packer Source #

packer :: App () -> Value (App ()) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Packable f1, Packable (App fs), Value (App fs) ~ Value fs) => Packable (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

pack :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Packer Source #

packer :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

data Packer Source #

Packer wraps a function that can write to a buffer.

Constructors

Packer 

Fields

  • fromPacker :: Addr# -> IO () -> (Addr# -> IO ()) -> IO ()

    Takes start of buffer; failure action; and a continuation.

    We try to pack data into the given buffer. If packing succeeds then we call the continuation with a pointer to the next byte after the packed value, otherwise we call the failure action.

Instances
Semigroup Packer Source # 
Instance details

Defined in Data.Repa.Convert.Internal.Packer

Monoid Packer Source # 
Instance details

Defined in Data.Repa.Convert.Internal.Packer

unsafeRunPacker Source #

Arguments

:: Packer

Packer to run.

-> Ptr Word8

Start of buffer.

-> IO (Maybe (Ptr Word8))

Pointer to the byte after the last one written.

Pack data into the given buffer.

PRECONDITION: The buffer needs to be big enough to hold the packed data, otherwise you'll corrupt the heap (bad). Use packedSize to work out how big it needs to be.

Unpackable

class Format format => Unpackable format where Source #

Minimal complete definition

unpacker

Methods

unpack Source #

Arguments

:: format

Storage format.

-> Unpacker (Value format)

Unpacker for that format.

Unpack a value from a buffer using the given format.

unpacker Source #

Arguments

:: format

Data format.

-> Addr#

Start of buffer.

-> Addr#

Pointer to first byte after end of buffer.

-> (Word8 -> Bool)

Detect a field terminator.

-> IO ()

Signal failure.

-> (Addr# -> Value format -> IO ())

Accept an unpacked value.

-> IO () 

Low level unpacking function for the given format.

Instances
Unpackable () Source # 
Instance details

Defined in Data.Repa.Convert.Format.Fields

Methods

unpack :: () -> Unpacker (Value ()) Source #

unpacker :: () -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value () -> IO ()) -> IO () Source #

Unpackable DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Unpackable DoubleAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

unpack :: DoubleAsc -> Unpacker (Value DoubleAsc) Source #

unpacker :: DoubleAsc -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value DoubleAsc -> IO ()) -> IO () Source #

Unpackable IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

unpack :: IntAsc0 -> Unpacker (Value IntAsc0) Source #

unpacker :: IntAsc0 -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value IntAsc0 -> IO ()) -> IO () Source #

Unpackable IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

unpack :: IntAsc -> Unpacker (Value IntAsc) Source #

unpacker :: IntAsc -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value IntAsc -> IO ()) -> IO () Source #

Unpackable VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Methods

unpack :: VarBytes -> Unpacker (Value VarBytes) Source #

unpacker :: VarBytes -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value VarBytes -> IO ()) -> IO () Source #

Unpackable Float64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Float64be -> Unpacker (Value Float64be) Source #

unpacker :: Float64be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Float64be -> IO ()) -> IO () Source #

Unpackable Float32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Float32be -> Unpacker (Value Float32be) Source #

unpacker :: Float32be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Float32be -> IO ()) -> IO () Source #

Unpackable Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int64be -> Unpacker (Value Int64be) Source #

unpacker :: Int64be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int64be -> IO ()) -> IO () Source #

Unpackable Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word64be -> Unpacker (Value Word64be) Source #

unpacker :: Word64be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word64be -> IO ()) -> IO () Source #

Unpackable Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int32be -> Unpacker (Value Int32be) Source #

unpacker :: Int32be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int32be -> IO ()) -> IO () Source #

Unpackable Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word32be -> Unpacker (Value Word32be) Source #

unpacker :: Word32be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word32be -> IO ()) -> IO () Source #

Unpackable Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int16be -> Unpacker (Value Int16be) Source #

unpacker :: Int16be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int16be -> IO ()) -> IO () Source #

Unpackable Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word16be -> Unpacker (Value Word16be) Source #

unpacker :: Word16be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word16be -> IO ()) -> IO () Source #

Unpackable Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int8be -> Unpacker (Value Int8be) Source #

unpacker :: Int8be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int8be -> IO ()) -> IO () Source #

Unpackable Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word8be -> Unpacker (Value Word8be) Source #

unpacker :: Word8be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word8be -> IO ()) -> IO () Source #

Unpackable ExactChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Unpackable VarCharString Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Unpackable VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

unpack :: VarChars -> Unpacker (Value VarChars) Source #

unpacker :: VarChars -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value VarChars -> IO ()) -> IO () Source #

Unpackable FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

unpack :: FixChars -> Unpacker (Value FixChars) Source #

unpacker :: FixChars -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value FixChars -> IO ()) -> IO () Source #

Unpackable UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Methods

unpack :: UnitAsc -> Unpacker (Value UnitAsc) Source #

unpacker :: UnitAsc -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value UnitAsc -> IO ()) -> IO () Source #

Unpackable VarTextString Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Unpackable VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Methods

unpack :: VarText -> Unpacker (Value VarText) Source #

unpacker :: VarText -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value VarText -> IO ()) -> IO () Source #

Unpackable DDsMMsYYYY Source # 
Instance details

Defined in Data.Repa.Convert.Format.Date32

Unpackable YYYYsMMsDD Source # 
Instance details

Defined in Data.Repa.Convert.Format.Date32

Unpackable f => Unpackable (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

unpack :: MaybeBytes f -> Unpacker (Value (MaybeBytes f)) Source #

unpacker :: MaybeBytes f -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (MaybeBytes f) -> IO ()) -> IO () Source #

Unpackable f => Unpackable (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

unpack :: MaybeChars f -> Unpacker (Value (MaybeChars f)) Source #

unpacker :: MaybeChars f -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (MaybeChars f) -> IO ()) -> IO () Source #

Unpackable (Sep ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep () -> Unpacker (Value (Sep ())) Source #

unpacker :: Sep () -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep ()) -> IO ()) -> IO () Source #

(Unpackable f1, Unpackable (Sep (f2 :*: fs)), Value (Sep (f2 :*: fs)) ~ Value (f2 :*: fs), Value (Sep fs) ~ Value fs) => Unpackable (Sep (f1 :*: (f2 :*: fs))) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep (f1 :*: (f2 :*: fs)) -> Unpacker (Value (Sep (f1 :*: (f2 :*: fs)))) Source #

unpacker :: Sep (f1 :*: (f2 :*: fs)) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep (f1 :*: (f2 :*: fs))) -> IO ()) -> IO () Source #

(Unpackable f1, Value (Sep ()) ~ Value ()) => Unpackable (Sep (f1 :*: ())) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep (f1 :*: ()) -> Unpacker (Value (Sep (f1 :*: ()))) Source #

unpacker :: Sep (f1 :*: ()) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep (f1 :*: ())) -> IO ()) -> IO () Source #

Unpackable (App ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

unpack :: App () -> Unpacker (Value (App ())) Source #

unpacker :: App () -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (App ()) -> IO ()) -> IO () Source #

(Unpackable f1, Unpackable (App fs), Value (App fs) ~ Value fs) => Unpackable (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

unpack :: App (f1 :*: fs) -> Unpacker (Value (App (f1 :*: fs))) Source #

unpacker :: App (f1 :*: fs) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (App (f1 :*: fs)) -> IO ()) -> IO () Source #

data Unpacker a Source #

Constructors

Unpacker 

Fields

  • fromUnpacker :: Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> a -> IO ()) -> IO ()

    Takes pointers to the first byte in the buffer; the first byte after the buffer; a predicate to detect a field terminator; a failure action; and a continuation.

    The field terminator is used by variable length encodings where the length of the encoded data cannot be determined from the encoding itself.

    We try to unpack a value from the buffer. If unpacking succeeds then call the continuation with a pointer to the next byte after the unpacked value, and the value itself, otherwise call the failure action.

Instances
Monad Unpacker Source # 
Instance details

Defined in Data.Repa.Convert.Internal.Unpacker

Methods

(>>=) :: Unpacker a -> (a -> Unpacker b) -> Unpacker b #

(>>) :: Unpacker a -> Unpacker b -> Unpacker b #

return :: a -> Unpacker a #

fail :: String -> Unpacker a #

Functor Unpacker Source # 
Instance details

Defined in Data.Repa.Convert.Internal.Unpacker

Methods

fmap :: (a -> b) -> Unpacker a -> Unpacker b #

(<$) :: a -> Unpacker b -> Unpacker a #

Applicative Unpacker Source # 
Instance details

Defined in Data.Repa.Convert.Internal.Unpacker

Methods

pure :: a -> Unpacker a #

(<*>) :: Unpacker (a -> b) -> Unpacker a -> Unpacker b #

liftA2 :: (a -> b -> c) -> Unpacker a -> Unpacker b -> Unpacker c #

(*>) :: Unpacker a -> Unpacker b -> Unpacker b #

(<*) :: Unpacker a -> Unpacker b -> Unpacker a #

unsafeRunUnpacker Source #

Arguments

:: Unpacker a

Unpacker to run.

-> Ptr Word8

Source buffer.

-> Int

Length of source buffer.

-> (Word8 -> Bool)

Detect a field terminator.

-> IO (Maybe (a, Ptr Word8))

Unpacked result, and pointer to the byte after the last one read.

Unpack data from the given buffer.

PRECONDITION: The buffer must be at least the minimum size of the format (minSize). This allows us to avoid repeatedly checking for buffer overrun when unpacking fixed size format. If the buffer is not long enough then you'll get an indeterminate result (bad).