| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Data.Repa.Convert.Formats
Contents
Description
Pre-defined data formats.
- class FormatAscii a where
- type FormatAscii' a
- formatAscii :: a -> FormatAscii' a
- data a :*: b :: * -> * -> * = !a :*: !b
- data App f = App f
- data Sep f = Sep Char f
- data Tup f = Tup f
- data FixAsc = FixAsc Int
- data VarAsc = VarAsc
- data VarString = VarString
- data IntAsc = IntAsc
- data IntAsc0 = IntAsc0 Int
- data DoubleAsc = DoubleAsc
- 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
Default Ascii Format
class FormatAscii a where Source
Class of types that can be formatted in some default human readable ASCII way.
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. |
| (FormatAscii t1, FormatAscii (Plain ts)) => FormatAscii ((:*:) t1 ts) Source | Tuples are displayed with round parens and commas to separate the fields. |
Field Products
data a :*: b :: * -> * -> * infixr 9
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) | |
| (Packable f1, Packable (App fs), (~) * (Value (App fs)) (Value fs)) => Packable (App ((:*:) f1 fs)) Source | |
| (Packable f1, Packable (Sep fs), (~) * (Value (Sep fs)) (Value fs)) => Packable (Sep ((:*:) f1 fs)) Source | |
| (Packable f1, Packable (Sep fs), Format (Tup fs), (~) * (Value (Sep fs)) (Value fs)) => Packable (Tup ((:*:) f1 fs)) Source | |
| (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 | |
| (Format f1, Format (Tup fs), Format (Sep fs), (~) * (Value (Sep fs)) (Value fs)) => Format (Tup ((:*:) f1 fs)) 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) | |
| (FormatAscii t1, FormatAscii (Plain ts)) => FormatAscii ((:*:) t1 ts) Source | Tuples are displayed with round parens and commas to separate the fields. |
| 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 Value (Tup ((:*:) 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 FormatAscii' ((:*:) t1 ts) Source | |
| type Mask' ((:*:) Drop ms) ((:*:) t1 ts) = Mask' ms ts | |
| type Mask' ((:*:) Keep ms) ((:*:) t1 ts) = (:*:) t1 (Mask' ms ts) |
Field Separators
Append fields without separators.
Constructors
| App f |
Instances
| Show f => Show (App f) Source | |
| Packable (App ()) Source | |
| (Packable f1, Packable (App fs), (~) * (Value (App fs)) (Value fs)) => Packable (App ((:*:) f1 fs)) Source | |
| Format (App ()) Source | |
| (Format f1, Format (App fs), (~) * (Value (App fs)) (Value fs)) => Format (App ((:*:) f1 fs)) Source | |
| type Value (App ()) = () Source | |
| type Value (App ((:*:) f1 fs)) = (:*:) (Value f1) (Value fs) 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.
Instances
| Show f => Show (Sep f) Source | |
| Packable (Sep ()) Source | |
| (Packable f1, Packable (Sep fs), (~) * (Value (Sep fs)) (Value fs)) => Packable (Sep ((:*:) f1 fs)) Source | |
| Format (Sep ()) Source | |
| (Format f1, Format (Sep fs), (~) * (Value (Sep fs)) (Value fs)) => Format (Sep ((:*:) f1 fs)) Source | |
| type Value (Sep ()) = () Source | |
| type Value (Sep ((:*:) f1 fs)) = (:*:) (Value f1) (Value fs) Source |
Display fields as a tuple, like (x,y,z).
Constructors
| Tup f |
Instances
| Show f => Show (Tup f) Source | |
| Packable (Tup ()) Source | |
| (Packable f1, Packable (Sep fs), Format (Tup fs), (~) * (Value (Sep fs)) (Value fs)) => Packable (Tup ((:*:) f1 fs)) Source | |
| Format (Tup ()) Source | |
| (Format f1, Format (Tup fs), Format (Sep fs), (~) * (Value (Sep fs)) (Value fs)) => Format (Tup ((:*:) f1 fs)) Source | |
| type Value (Tup ()) = () Source | |
| type Value (Tup ((:*:) f1 fs)) = (:*:) (Value f1) (Value fs) Source |
Strings
Fixed length string.
- When packing, the length of the provided string must match the field width, else packing will fail.
- When unpacking, the length of the result will be as set by the field width.
Variable length raw string (with no quotes).
Constructors
| VarAsc |
Variable length string in double quotes, and standard backslash encoding of special characters.
Constructors
| VarString |
Atomic values
ASCII numeric
Human-readable ASCII Integer.
Constructors
| IntAsc |
Human-readable ASCII integer, with leading zeros.
Human-readable ASCII Double.
Constructors
| DoubleAsc |
ASCII dates
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 |