| Safe Haskell | Trustworthy | 
|---|---|
| Language | Haskell2010 | 
Flat.Class
Contents
Description
Generics-based generation of Flat instances
Synopsis
- class Flat a where
- getSize :: Flat a => a -> NumBits
- module GHC.Generics
- class GFlatEncode f
- class GFlatDecode f
- class GFlatSize f
The Flat class
Class of types that can be encoded/decoded
Encoding a value involves three steps:
Minimal complete definition
Nothing
Methods
encode :: a -> Encoding Source #
Return the encoding corrresponding to the value
Decode a value
size :: a -> NumBits -> NumBits Source #
Add maximum size in bits of the value to the total count
Used to calculated maximum buffer size before encoding
Instances
| Flat All Source # | Since: 0.4.4 | 
| Flat Any Source # | Since: 0.4.4 | 
| Flat Int16 Source # | 
 
 
 
 equivalent to 0b1111111111111111 
 equivalent to 0b1111111111111110 | 
| Flat Int32 Source # | 
 
 
 | 
| Flat Int64 Source # | 
 
 
 | 
| Flat Int8 Source # | 
 
 
 | 
| Flat Word16 Source # | |
| Flat Word32 Source # | |
| Flat Word64 Source # | |
| Flat Word8 Source # | Word8 always take 8 bits. 
 
 | 
| Flat ByteString Source # | ByteString, ByteString.Lazy and ByteString.Short are all encoded as Prealigned Arrays: PreAligned a ≡ PreAligned {preFiller :: Filler, preValue :: a}
Filler ≡   FillerBit Filler
          | FillerEnd
Array v = A0
        | A1 v (Array v)
        | A2 v v (Array v)
        ...
        | A255 ... (Array v)
That's to say as a byte-aligned sequence of blocks of up to 255 elements, with every block preceded by the count of the elements in the block and a final 0-length block. 
 where: 1= PreAlignment (takes a byte if we are already on a byte boundary) 3= Number of bytes in ByteString 11,22,33= Bytes 0= End of Array 
 Pre-alignment ensures that a ByteString always starts at a byte boundary: 
 All ByteStrings are encoded in the same way: 
 | 
| Defined in Flat.Instances.ByteString | |
| Flat ByteString Source # | 
 | 
| Defined in Flat.Instances.ByteString | |
| Flat ShortByteString Source # | 
 | 
| Defined in Flat.Instances.ByteString | |
| Flat Filler Source # | Use a special encoding for the filler | 
| Flat UTF16Text Source # | |
| Flat UTF8Text Source # | |
| Flat Text Source # | Text (and Data.Text.Lazy) is encoded as a byte aligned array of bytes corresponding to its UTF8 encoding. 
 
 
 
 
 Strict and Lazy Text have the same encoding: 
 | 
| Flat Text Source # | |
| Flat Integer Source # | Integers are encoded just as the fixed size Ints. 
 
 
 
 
 
 
 | 
| Flat Natural Source # | Naturals are encoded just as the fixed size Words. 
 
 | 
| Flat () Source # | 
 
 | 
| Flat Bool Source # | One bit is plenty for a Bool. 
 
 | 
| Flat Char Source # | Char's are mapped to Word32 and then encoded. For ascii characters, the encoding is standard ascii. 
 For unicode characters, the encoding is non standard. 
 
 
 | 
| Flat Double Source # | Doubles are encoded as standard IEEE binary64 values: IEEE_754_binary64 ≡ IEEE_754_binary64 {sign :: Sign,
                                        exponent :: MostSignificantFirst Bits11,
                                        fraction :: MostSignificantFirst Bits52}
 | 
| Flat Float Source # | Floats are encoded as standard IEEE binary32 values: IEEE_754_binary32 ≡ IEEE_754_binary32 {sign :: Sign,
                                        exponent :: MostSignificantFirst Bits8,
                                        fraction :: MostSignificantFirst Bits23}
 
 
 | 
| Flat Int Source # | Integer, Int, Int16, Int32 and Int64 are defined as the ZigZag encoded version of the equivalent unsigned Word: Int ≡ Int (ZigZag Word) Int64 ≡ Int64 (ZigZag Word64) Int32 ≡ Int32 (ZigZag Word32) Int16 ≡ Int16 (ZigZag Word16) Int8 ≡ Int8 (ZigZag Word8) ZigZag a ≡ ZigZag a ZigZag encoding alternates between positive and negative numbers, so that numbers whose absolute value is small can be encoded efficiently: 
 
 
 
 
 | 
| Flat Word Source # | Natural, Word, Word16, Word32 and Word64 are encoded as a non empty list of 7 bits chunks (least significant chunk first and most significant bit first in every chunk). Words are always encoded in a whole number of bytes, as every chunk is 8 bits long (1 bit for the List constructor, plus 7 bits for the value). The actual definition is: Word64 ≡   Word64 Word
Word32 ≡   Word32 Word
Word16 ≡   Word16 Word
Word ≡   Word (LeastSignificantFirst (NonEmptyList (MostSignificantFirst Word7)))
LeastSignificantFirst a ≡   LeastSignificantFirst a
NonEmptyList a ≡   Elem a
                 | Cons a (NonEmptyList a)
MostSignificantFirst a ≡   MostSignificantFirst a
Word7 ≡   V0
        | V1
        | V2
        ...
        | V127
Values between as 0 and 127 fit in a single byte. 127 (0b1111111) is represented as Elem V127 and encoded as: Elem=0 127=1111111 
 254 (0b11111110) is represented as Cons V126 (Elem V1) (254=128+126) and encoded as: Cons=1 V126=1111110 (Elem=0 V1=0000001): 
 Another example, 32768 (Ob1000000000000000 = 0000010 0000000 0000000): 
 As this is a variable length encoding, values are encoded in the same way, whatever their type: 
 Word/Int decoders return an error if the encoded value is outside their valid range: 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 
 | 
| Flat a => Flat (Complex a) Source # | 
 | 
| Flat a => Flat (Identity a) Source # | Since: 0.4.4 | 
| Flat a => Flat (First a) Source # | Since: 0.4.4 | 
| Flat a => Flat (Last a) Source # | Since: 0.4.4 | 
| Flat a => Flat (Max a) Source # | Since: 0.4.4 | 
| Flat a => Flat (Min a) Source # | Since: 0.4.4 | 
| Flat a => Flat (Dual a) Source # | Since: 0.4.4 | 
| Flat a => Flat (Product a) Source # | Since: 0.4.4 | 
| Flat a => Flat (Sum a) Source # | Since: 0.4.4 | 
| (Integral a, Flat a) => Flat (Ratio a) Source # | Ratios are encoded as tuples of (numerator,denominator) 
 | 
| Flat a => Flat (IntMap a) Source # | Maps are defined as a list of (Key,Value) tuples: Map = List (Key,Value) List a = Nil | Cons a (List a) 
 
 | 
| Flat a => Flat (Seq a) Source # | Data.Sequence.Seq is encoded as a list. 
 In flat <0.4, it was encoded as an Array. If you want to restore the previous behaviour, use AsArray: 
 
 | 
| (Flat a, Ord a) => Flat (Set a) Source # | Data.Set is encoded as a list 
 | 
| Flat a => Flat (Tree a) Source # | 
 | 
| Flat a => Flat (DList a) Source # | 
 
 | 
| Flat a => Flat (AsBin a) Source # | |
| Flat a => Flat (AsSize a) Source # | |
| Flat a => Flat (PostAligned a) Source # | |
| Defined in Flat.Filler | |
| Flat a => Flat (PreAligned a) Source # | |
| Defined in Flat.Filler | |
| (IsSequence r, Flat (Element r)) => Flat (AsArray r) Source # | |
| (IsSequence l, Flat (Element l)) => Flat (AsList l) Source # | |
| (IsMap map, Flat (ContainerKey map), Flat (MapValue map)) => Flat (AsMap map) Source # | |
| (IsSet set, Flat (Element set)) => Flat (AsSet set) Source # | |
| (Hashable a, Eq a, Flat a) => Flat (HashSet a) Source # | 
 | 
| Flat a => Flat (Vector a) Source # | Vectors are encoded as arrays. 
 All Vectors are encoded in the same way: 
 | 
| (Storable a, Flat a) => Flat (Vector a) Source # | |
| (Unbox a, Flat a) => Flat (Vector a) Source # | |
| Flat a => Flat (NonEmpty a) Source # | 
 
 | 
| Flat a => Flat (Maybe a) Source # | 
 
 | 
| Flat [Char] Source # | For better encoding/decoding performance, it is useful to declare instances of concrete list types, such as [Char]. 
 
 | 
| Flat a => Flat [a] Source # | 
 
 This instance and other similar ones are declared as  | 
| (Flat i, Flat e, Ix i, IArray UArray e) => Flat (UArray i e) Source # | |
| (Flat a, Flat b) => Flat (Either a b) Source # | 
 
 | 
| Flat (Fixed a) Source # | 
 
 | 
| (Flat i, Flat e, Ix i) => Flat (Array i e) Source # | Array is encoded as (lowBound,highBound,AsArray (elems array)): 
 As it's easy to see: 
 
 Arrays and Unboxed Arrays are encoded in the same way: 
 | 
| (Flat a, Flat b, Ord a) => Flat (Map a b) Source # | Maps are encoded as lists: 
 
 Key/Values are encoded in order: 
 IntMap and Map are encoded in the same way: 
 | 
| (Hashable k, Eq k, Flat k, Flat v) => Flat (HashMap k v) Source # | 
 
 | 
| (Flat a, Flat b) => Flat (a, b) Source # | Tuples are supported up to 7 elements. 
 
 "7 elements tuples ought to be enough for anybody" (Bill Gates - apocryphal) 
 tst (1::Int,"2","3","4","5","6","7","8") ...error | 
| Flat (f a) => Flat (Alt f a) Source # | 
 
 Since: 0.4.4 | 
| (Flat a, Flat b, Flat c) => Flat (a, b, c) Source # | |
| (Flat a, Flat b, Flat c, Flat d) => Flat (a, b, c, d) Source # | |
| (Flat a, Flat b, Flat c, Flat d, Flat e) => Flat (a, b, c, d, e) Source # | |
| (Flat a, Flat b, Flat c, Flat d, Flat e, Flat f) => Flat (a, b, c, d, e, f) Source # | |
| (Flat a, Flat b, Flat c, Flat d, Flat e, Flat f, Flat g) => Flat (a, b, c, d, e, f, g) Source # | |
getSize :: Flat a => a -> NumBits Source #
Calculate the maximum size in bits of the serialisation of the value
module GHC.Generics
class GFlatEncode f Source #
Generic Encoder
Minimal complete definition
gencode
Instances
| GFlatEncode (U1 :: Type -> Type) Source # | |
| Defined in Flat.Class | |
| GFlatEncode (V1 :: Type -> Type) Source # | |
| Defined in Flat.Class | |
| (GFlatEncode a, GFlatEncode b) => GFlatEncode (a :*: b) Source # | |
| Defined in Flat.Class | |
| (NumConstructors (a :+: b) <= 512, GFlatEncodeSum (a :+: b)) => GFlatEncode (a :+: b) Source # | |
| Defined in Flat.Class | |
| GFlatEncode a => GFlatEncode (D1 i (C1 c a)) Source # | |
| Defined in Flat.Class | |
| Flat a => GFlatEncode (K1 i a :: Type -> Type) Source # | |
| Defined in Flat.Class | |
| GFlatEncode f => GFlatEncode (M1 i c f) Source # | |
| Defined in Flat.Class | |
class GFlatDecode f Source #
Generic Decoding
Minimal complete definition
gget
Instances
| GFlatDecode (U1 :: Type -> Type) Source # | Constructor without arguments | 
| Defined in Flat.Class | |
| GFlatDecode (V1 :: Type -> Type) Source # | Type without constructors | 
| Defined in Flat.Class | |
| (GFlatDecode a, GFlatDecode b) => GFlatDecode (a :*: b) Source # | Product: constructor with parameters | 
| Defined in Flat.Class | |
| (GFlatDecode a, GFlatDecode b) => GFlatDecode (C1 m1 a :+: C1 m2 b) Source # | |
| (NumConstructors (a :+: b) <= 512, GFlatDecodeSum (a :+: b)) => GFlatDecode (a :+: b) Source # | Data types with up to 512 constructors Uses a custom constructor decoding state instance {-# OVERLAPPABLE #-} (GFlatDecodeSum (a :+: b),GFlatDecode a, GFlatDecode b) => GFlatDecode (a :+: b) where | 
| Defined in Flat.Class | |
| Flat a => GFlatDecode (K1 i a :: Type -> Type) Source # | Constants, additional parameters, and rank-1 recursion | 
| Defined in Flat.Class | |
| GFlatDecode a => GFlatDecode (M1 i c a) Source # | Metadata (constructor name, etc) | 
| Defined in Flat.Class | |
Calculate the number of bits required for the serialisation of a value Implemented as a function that adds the maximum size to a running total
Minimal complete definition
gsize
Instances
| GFlatSize (U1 :: Type -> Type) Source # | Constructor without arguments | 
| Defined in Flat.Class | |
| GFlatSize (V1 :: Type -> Type) Source # | Type without constructors | 
| Defined in Flat.Class | |
| (GFlatSize a, GFlatSize b) => GFlatSize (a :*: b) Source # | |
| Defined in Flat.Class | |
| GFlatSizeSum (a :+: b) => GFlatSize (a :+: b) Source # | |
| Defined in Flat.Class | |
| Flat a => GFlatSize (K1 i a :: Type -> Type) Source # | Skip metadata | 
| Defined in Flat.Class | |
| GFlatSize f => GFlatSize (M1 i c f) Source # | Skip metadata | 
| Defined in Flat.Class | |