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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Convert.Formats

Contents

Description

Pre-defined data formats.

Synopsis

Default

class FormatAscii a where Source

Class of types that can be formatted in some default human readable ASCII way.

Associated Types

type FormatAscii' a Source

The format for values of this type.

Methods

formatAscii :: a -> FormatAscii' a Source

Get the standard ASCII format for a value.

The element value itself is not demanded.

Instances

FormatAscii Double Source

Doubles are formatted as base-10 decimal.

FormatAscii Int Source

Ints are formated in base-10.

FormatAscii String Source

Strings are formatted with double quotes and back-slash escaping of special characters.

FormatAscii () Source

Empty tuples produce no output.

FormatAscii Date32 Source

Dates are formatted as YYYY-MM-DD.

Units

Maybes

data MaybeChars f Source

Maybe a raw list of characters, or something else.

Constructors

MaybeChars String f 

data MaybeBytes f Source

Maybe a raw sequence of bytes, or something else.

Constructors

MaybeBytes ByteString f 

String Formats

for Haskell Strings

data FixChars Source

Fixed length sequence of characters, represented as a (hated) Haskell String.

  • The runtime performance of the Haskell String is atrocious. You really shouldn't be using them for large data sets.
  • When packing, the length of the provided string must match the width of the format, else packing will fail.
  • When unpacking, the length of the result will be the width of the format.

Constructors

FixChars Int 

data VarCharString Source

Variable length string in double quotes, and standard backslash encoding of non-printable characters.

Constructors

VarCharString 

data ExactChars Source

Match an exact sequence of characters.

Constructors

ExactChars String 

for Data.Text

data VarText Source

Variable length unicode text, represented as a Data.Text thing.

Constructors

VarText 

data VarTextString Source

Variable length string in double quotes, and standard backslash encoding of non-printable characters.

Constructors

VarTextString 

for Data.ByteString

data VarBytes Source

Variable length sequence of bytes, represented as a ByteString.

Constructors

VarBytes 

ASCII Atoms

ASCII integers

data IntAsc Source

Human-readable ASCII Integer.

Constructors

IntAsc 

data IntAsc0 Source

Human-readable ASCII integer, using leading zeros to pad the encoding out to a fixed length.

Constructors

IntAsc0 Int 

ASCII doubles

data DoubleFixedPack Source

Human-readable ASCII Double.

When packing we use a fixed number of zeros after the decimal point, though when unpacking we allow a greater precision.

Constructors

DoubleFixedPack Int 

ASCII dates

Binary Atoms

8-bit binary

data Word8be Source

Big-endian 8-bit unsigned word.

Constructors

Word8be 

data Int8be Source

Big-endian 8-bit signed integer.

Constructors

Int8be 

16-bit binary

32-bit binary

data Int32be Source

Big-endian 32-bit signed integer.

Constructors

Int32be 

64-bit binary

data Int64be Source

Big-endian 64-bit signed integer.

Constructors

Int64be 

Compounds

Appended fields

data App f Source

Append fields without separators.

Constructors

App f 

Instances

Format (App ()) Source 
(Format f1, Format (App fs), (~) * (Value (App fs)) (Value fs)) => Format (App ((:*:) f1 fs)) Source 
Unpackable (App ()) Source 
(Unpackable f1, Unpackable (App fs), (~) * (Value (App fs)) (Value fs)) => Unpackable (App ((:*:) f1 fs)) Source 
Packable (App ()) Source 
(Packable f1, Packable (App fs), (~) * (Value (App fs)) (Value fs)) => Packable (App ((:*:) f1 fs)) Source 
type Value (App ()) = () Source 
type Value (App ((:*:) f1 fs)) = (:*:) (Value f1) (Value fs) Source 

Separated fields

data Sep f Source

Separate fields with the given character.

  • The separating character is un-escapable.
  • The format (Sep ',') does NOT parse a CSV file according to the CSV specification: http://tools.ietf.org/html/rfc4180.
  • The type is kept abstract as we cache some pre-computed values we use to unpack this format. Use mkSep to make one.

Instances

Format (Sep ()) Source 
(Format f1, Format (Sep fs), (~) * (Value (Sep fs)) (Value fs)) => Format (Sep ((:*:) f1 fs)) Source 
Unpackable (Sep ()) 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 
(Unpackable f1, (~) * (Value (Sep ())) (Value ())) => Unpackable (Sep ((:*:) f1 ())) Source 
Packable (Sep ()) 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 
(Packable f1, (~) * (Value (Sep ())) (Value ())) => Packable (Sep ((:*:) f1 ())) Source 
type Value (Sep ()) = () Source 
type Value (Sep ((:*:) f1 fs)) = (:*:) (Value f1) (Value fs) Source 

class SepFormat f where Source

Methods

mkSep :: Char -> f -> Sep f Source

Instances

Object with labeled fields

data Object fields Source

Format of a simple object format with labeled fields.

Instances

(Format (ObjectFields fs), (~) * (Value (ObjectFields fs)) (Value fs)) => Format (Object fs) Source 
(Format (Object f), (~) * (Value (ObjectFields f)) (Value f), Packable (ObjectFields f)) => Packable (Object f) Source 
type Value (Object fs) = Value fs Source 

class ObjectFormat f Source

Minimal complete definition

mkObjectFields

Instances

data Field f Source

A single field in an object.

Constructors

Field 

Instances

mkObject :: ObjectFormat f => f -> Object (ObjectFormat' f) Source

Make an object format with the given labeled fields. For example:

> let fmt =   mkObject 
          $   Field "index"   IntAsc                      Nothing
          :*: Field "message" (VarCharString '-')         Nothing 
          :*: Field "value"   (MaybeChars NULL DoubleAsc) (Just isJust)
          :*: ()

Packing this produces:

> let Just str = packToString fmt (27 :*: "foo" :*: Nothing :*: ())
> putStrLn str
> {"index":27,"message":"foo"}

Note that the encodings that this format can generate are a superset of the JavaScript Object Notation (JSON). With the Repa format, the fields of an object can directly encode dates and other values, wheras in JSON these values must be represented by strings.

Products

data a :*: b :: * -> * -> * infixr 9

A strict product type, written infix.

Constructors

!a :*: !b infixr 9 

Instances

IsProdList ts => Select Z ((:*:) t1 ts) 
IsProdList ts => Discard Z ((:*:) t1 ts) 
(Unbox a, Unbox b) => Vector Vector ((:*:) a b) 
(Unbox a, Unbox b) => MVector MVector ((:*:) a b) 
(Format f1, Format (App fs), (~) * (Value (App fs)) (Value fs)) => Format (App ((:*:) f1 fs)) Source 
(Format f1, Format (Sep fs), (~) * (Value (Sep fs)) (Value fs)) => Format (Sep ((:*:) f1 fs)) Source 
(Unpackable f1, Unpackable (App fs), (~) * (Value (App fs)) (Value fs)) => Unpackable (App ((:*:) f1 fs)) 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 
(Unpackable f1, (~) * (Value (Sep ())) (Value ())) => Unpackable (Sep ((:*:) f1 ())) Source 
(Packable f1, Packable (App fs), (~) * (Value (App fs)) (Value fs)) => Packable (App ((:*:) f1 fs)) 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 
(Packable f1, (~) * (Value (Sep ())) (Value ())) => Packable (Sep ((:*:) f1 ())) Source 
Select n ts => Select (S n) ((:*:) t1 ts) 
Discard n ts => Discard (S n) ((:*:) t1 ts) 
(Eq a, Eq b) => Eq ((:*:) a b) 
(Show a, Show b) => Show ((:*:) a b) 
IsProdList fs => IsProdList ((:*:) f fs) 
(Unbox a, Unbox b) => Unbox ((:*:) a b) 
(Format f1, SepFormat fs) => SepFormat ((:*:) f1 fs) Source 
(Format f1, ObjectFormat fs) => ObjectFormat ((:*:) (Field f1) fs) Source 
Mask ms ts => Mask ((:*:) Drop ms) ((:*:) t1 ts) 
Mask ms ts => Mask ((:*:) Keep ms) ((:*:) t1 ts) 
type Select' Z ((:*:) t1 ts) = t1 
type Discard' Z ((:*:) t1 ts) = ts 
data MVector s ((:*:) a b) = MV_Prod !Int !(MVector s a) !(MVector s b) 
type Value (App ((:*:) f1 fs)) = (:*:) (Value f1) (Value fs) Source 
type Value (Sep ((:*:) f1 fs)) = (:*:) (Value f1) (Value fs) Source 
type Select' (S n) ((:*:) t1 ts) = Select' n ts 
type Discard' (S n) ((:*:) t1 ts) = (:*:) t1 (Discard' n ts) 
data Vector ((:*:) a b) = V_Prod !Int !(Vector a) !(Vector b) 
type Value ((:*:) a b) = (:*:) (Value a) (Value b) Source 
type Mask' ((:*:) Drop ms) ((:*:) t1 ts) = Mask' ms ts 
type Mask' ((:*:) Keep ms) ((:*:) t1 ts) = (:*:) t1 (Mask' ms ts)