Safe Haskell | None |
---|---|
Language | Haskell98 |
Data.Repa.Convert.Formats
Contents
Description
Pre-defined data formats.
- class FormatAscii a where
- type FormatAscii' a
- data UnitAsc = UnitAsc String
- data MaybeChars f = MaybeChars String f
- data MaybeBytes f = MaybeBytes ByteString f
- data FixChars = FixChars Int
- data VarChars = VarChars
- data VarCharString = VarCharString
- data ExactChars = ExactChars String
- data VarText = VarText
- data VarTextString = VarTextString
- data VarBytes = VarBytes
- data IntAsc = IntAsc
- data IntAsc0 = IntAsc0 Int
- data DoubleAsc = DoubleAsc
- data DoubleFixedPack = DoubleFixedPack Int
- data YYYYsMMsDD = YYYYsMMsDD Char
- data DDsMMsYYYY = DDsMMsYYYY Char
- data Word8be = Word8be
- data Int8be = Int8be
- data Word16be = Word16be
- data Int16be = Int16be
- data Word32be = Word32be
- data Int32be = Int32be
- data Float32be = Float32be
- data Word64be = Word64be
- data Int64be = Int64be
- data Float64be = Float64be
- data App f = App f
- data Sep f where
- class SepFormat f where
- data Object fields
- class ObjectFormat f
- data Field f = Field {
- fieldName :: String
- fieldFormat :: f
- fieldInclude :: Maybe (Value f -> Bool)
- mkObject :: ObjectFormat f => f -> Object (ObjectFormat' f)
- data a :*: b :: * -> * -> * = ~a :*: ~b
Default
class FormatAscii a where Source #
Class of types that can be formatted in some default human readable ASCII way.
Minimal complete definition
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 () Source # | Empty tuples produce no output. |
FormatAscii String Source # | Strings are formatted with double quotes and back-slash escaping of special characters. |
FormatAscii Date32 Source # | Dates are formatted as YYYY-MM-DD. |
Units
A particular ASCII string.
Maybes
data MaybeChars f Source #
Maybe a raw list of characters, or something else.
Constructors
MaybeChars String f |
Instances
Eq f => Eq (MaybeChars f) Source # | |
Show f => Show (MaybeChars f) Source # | |
Format f => Format (MaybeChars f) Source # | |
Unpackable f => Unpackable (MaybeChars f) Source # | |
Packable f => Packable (MaybeChars f) Source # | |
type Value (MaybeChars f) Source # | |
data MaybeBytes f Source #
Maybe a raw sequence of bytes, or something else.
Constructors
MaybeBytes ByteString f |
Instances
Eq f => Eq (MaybeBytes f) Source # | |
Show f => Show (MaybeBytes f) Source # | |
Format f => Format (MaybeBytes f) Source # | |
Unpackable f => Unpackable (MaybeBytes f) Source # | |
Packable f => Packable (MaybeBytes f) Source # | |
type Value (MaybeBytes f) Source # | |
String Formats
for Haskell Strings
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.
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 |
Instances
for Data.Text
data VarTextString Source #
Variable length string in double quotes, and standard backslash encoding of non-printable characters.
Constructors
VarTextString |
for Data.ByteString
Variable length sequence of bytes, represented as a ByteString
.
Constructors
VarBytes |
ASCII Atoms
ASCII integers
Human-readable ASCII Integer.
Constructors
IntAsc |
Human-readable ASCII integer, using leading zeros to pad the encoding out to a fixed length.
ASCII doubles
Human-readable ASCII Double.
Constructors
DoubleAsc |
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
data YYYYsMMsDD Source #
Human readable ASCII date in YYYYsMMsDD format.
Constructors
YYYYsMMsDD Char |
Instances
data DDsMMsYYYY Source #
Human readable ASCII date in DDsMMsYYYY format.
Constructors
DDsMMsYYYY Char |
Instances
Binary Atoms
8-bit binary
Big-endian 8-bit unsigned word.
Constructors
Word8be |
Big-endian 8-bit signed integer.
Constructors
Int8be |
16-bit binary
Big-endian 32-bit unsigned word.
Constructors
Word16be |
Constructors
Int16be |
32-bit binary
Big-endian 32-bit unsigned word.
Constructors
Word32be |
Big-endian 32-bit signed integer.
Constructors
Int32be |
Big-endian 32-bit IEEE 754 float.
Constructors
Float32be |
64-bit binary
Big-endian 64-bit unsigned word.
Constructors
Word64be |
Big-endian 64-bit signed integer.
Constructors
Int64be |
Big-endian 64-bit IEEE 754 float.
Constructors
Float64be |
Compounds
Appended fields
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)) Source # | |
Separated fields
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)) Source # | |
Object with labeled fields
Format of a simple object format with labeled fields.
class ObjectFormat f Source #
Minimal complete definition
mkObjectFields
Instances
ObjectFormat () Source # | |
(Format f1, ObjectFormat fs) => ObjectFormat ((:*:) (Field f1) fs) Source # | |
A single field in an object.
Constructors
Field | |
Fields
|
Instances
(Format f1, ObjectFormat fs) => ObjectFormat ((:*:) (Field f1) fs) Source # | |
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