Safe Haskell | None |
---|---|
Language | Haskell98 |
Pre-defined data formats.
Synopsis
- class FormatAscii a where
- type FormatAscii' a
- formatAscii :: a -> 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.
type FormatAscii' a Source #
The format for values of this type.
formatAscii :: a -> FormatAscii' a Source #
Get the standard ASCII format for a value.
The element value itself is not demanded.
Instances
Units
A particular ASCII string.
Maybes
data MaybeChars f Source #
Maybe a raw list of characters, or something else.
Instances
data MaybeBytes f Source #
Maybe a raw sequence of bytes, or something else.
Instances
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.
Like FixChars
, but with a variable length.
data VarCharString Source #
Variable length string in double quotes, and standard backslash encoding of non-printable characters.
Instances
data ExactChars Source #
Match an exact sequence of characters.
Instances
Show ExactChars Source # | |
Defined in Data.Repa.Convert.Format.String showsPrec :: Int -> ExactChars -> ShowS # show :: ExactChars -> String # showList :: [ExactChars] -> ShowS # | |
Format ExactChars Source # | |
Defined in Data.Repa.Convert.Format.String type Value ExactChars :: Type Source # fieldCount :: ExactChars -> Int Source # minSize :: ExactChars -> Int Source # fixedSize :: ExactChars -> Maybe Int Source # packedSize :: ExactChars -> Value ExactChars -> Maybe Int Source # | |
Unpackable ExactChars Source # | |
Defined in Data.Repa.Convert.Format.String | |
Packable ExactChars Source # | |
Defined in Data.Repa.Convert.Format.String pack :: ExactChars -> Value ExactChars -> Packer Source # packer :: ExactChars -> Value ExactChars -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source # | |
type Value ExactChars Source # | |
Defined in Data.Repa.Convert.Format.String |
for Data.Text
Variable length unicode text, represented as a Data.Text thing.
data VarTextString Source #
Variable length string in double quotes, and standard backslash encoding of non-printable characters.
Instances
for Data.ByteString
Variable length sequence of bytes, represented as a ByteString
.
ASCII Atoms
ASCII integers
Human-readable ASCII Integer.
Human-readable ASCII integer, using leading zeros to pad the encoding out to a fixed length.
ASCII doubles
Human-readable ASCII Double.
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.
Instances
ASCII dates
data YYYYsMMsDD Source #
Human readable ASCII date in YYYYsMMsDD format.
Instances
Eq YYYYsMMsDD Source # | |
Defined in Data.Repa.Convert.Format.Date32 (==) :: YYYYsMMsDD -> YYYYsMMsDD -> Bool # (/=) :: YYYYsMMsDD -> YYYYsMMsDD -> Bool # | |
Show YYYYsMMsDD Source # | |
Defined in Data.Repa.Convert.Format.Date32 showsPrec :: Int -> YYYYsMMsDD -> ShowS # show :: YYYYsMMsDD -> String # showList :: [YYYYsMMsDD] -> ShowS # | |
Format YYYYsMMsDD Source # | |
Defined in Data.Repa.Convert.Format.Date32 type Value YYYYsMMsDD :: Type Source # fieldCount :: YYYYsMMsDD -> Int Source # minSize :: YYYYsMMsDD -> Int Source # fixedSize :: YYYYsMMsDD -> Maybe Int Source # packedSize :: YYYYsMMsDD -> Value YYYYsMMsDD -> Maybe Int Source # | |
Unpackable YYYYsMMsDD Source # | |
Defined in Data.Repa.Convert.Format.Date32 | |
Packable YYYYsMMsDD Source # | |
Defined in Data.Repa.Convert.Format.Date32 pack :: YYYYsMMsDD -> Value YYYYsMMsDD -> Packer Source # packer :: YYYYsMMsDD -> Value YYYYsMMsDD -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source # | |
type Value YYYYsMMsDD Source # | |
Defined in Data.Repa.Convert.Format.Date32 |
data DDsMMsYYYY Source #
Human readable ASCII date in DDsMMsYYYY format.
Instances
Eq DDsMMsYYYY Source # | |
Defined in Data.Repa.Convert.Format.Date32 (==) :: DDsMMsYYYY -> DDsMMsYYYY -> Bool # (/=) :: DDsMMsYYYY -> DDsMMsYYYY -> Bool # | |
Show DDsMMsYYYY Source # | |
Defined in Data.Repa.Convert.Format.Date32 showsPrec :: Int -> DDsMMsYYYY -> ShowS # show :: DDsMMsYYYY -> String # showList :: [DDsMMsYYYY] -> ShowS # | |
Format DDsMMsYYYY Source # | |
Defined in Data.Repa.Convert.Format.Date32 type Value DDsMMsYYYY :: Type Source # fieldCount :: DDsMMsYYYY -> Int Source # minSize :: DDsMMsYYYY -> Int Source # fixedSize :: DDsMMsYYYY -> Maybe Int Source # packedSize :: DDsMMsYYYY -> Value DDsMMsYYYY -> Maybe Int Source # | |
Unpackable DDsMMsYYYY Source # | |
Defined in Data.Repa.Convert.Format.Date32 | |
Packable DDsMMsYYYY Source # | |
Defined in Data.Repa.Convert.Format.Date32 pack :: DDsMMsYYYY -> Value DDsMMsYYYY -> Packer Source # packer :: DDsMMsYYYY -> Value DDsMMsYYYY -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source # | |
type Value DDsMMsYYYY Source # | |
Defined in Data.Repa.Convert.Format.Date32 |
Binary Atoms
8-bit binary
Big-endian 8-bit unsigned word.
Big-endian 8-bit signed integer.
16-bit binary
Big-endian 32-bit unsigned word.
32-bit binary
Big-endian 32-bit unsigned word.
Big-endian 32-bit signed integer.
Big-endian 32-bit IEEE 754 float.
64-bit binary
Big-endian 64-bit unsigned word.
Big-endian 64-bit signed integer.
Big-endian 64-bit IEEE 754 float.
Compounds
Appended fields
Append fields without separators.
App f |
Instances
Format (App ()) Source # | |
(Format f1, Format (App fs), Value (App fs) ~ Value fs) => Format (App (f1 :*: fs)) Source # | |
Defined in Data.Repa.Convert.Format.App | |
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 # | |
Defined in Data.Repa.Convert.Format.App | |
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 # | |
Defined in Data.Repa.Convert.Format.Sep | |
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 # | |
Defined in Data.Repa.Convert.Format.Sep | |
type Value (Sep (f1 :*: fs)) Source # | |
Object with labeled fields
Format of a simple object format with labeled fields.
class ObjectFormat f Source #
mkObjectFields
Instances
ObjectFormat () Source # | |
Defined in Data.Repa.Convert.Format.Object type ObjectFormat' () :: Type mkObjectFields :: () -> ObjectFields (ObjectFormat' ()) | |
(Format f1, ObjectFormat fs) => ObjectFormat (Field f1 :*: fs) Source # | |
Defined in Data.Repa.Convert.Format.Object mkObjectFields :: (Field f1 :*: fs) -> ObjectFields (ObjectFormat' (Field f1 :*: fs)) |
A single field in an object.
Field | |
|
Instances
(Format f1, ObjectFormat fs) => ObjectFormat (Field f1 :*: fs) Source # | |
Defined in Data.Repa.Convert.Format.Object mkObjectFields :: (Field f1 :*: fs) -> ObjectFields (ObjectFormat' (Field f1 :*: fs)) |
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
A strict product type, written infix.
!a :*: !b infixr 9 |