flat-0.4.4: Principled and efficient bit-oriented binary serialization.

Safe HaskellNone
LanguageHaskell2010

Flat.Instances.Base

Contents

Description

Flat instances for the base library

Orphan instances

Flat Bool Source #

One bit is plenty for a Bool.

>>> test False
(True,1,"0")
>>> test True
(True,1,"1")
Instance details

Flat Char Source #

Char's are mapped to Word32 and then encoded.

For ascii characters, the encoding is standard ascii.

>>> test 'a'
(True,8,"01100001")

For unicode characters, the encoding is non standard.

>>> test 'È'
(True,16,"11001000 00000001")
>>> test '不'
(True,24,"10001101 10011100 00000001")
>>> test "\x1F600"
(True,26,"11000000 01110110 00000011 10")
Instance details

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}
Instance details

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}
>>> test (0::Float)
(True,32,"00000000 00000000 00000000 00000000")
>>> test (1.4012984643E-45::Float)
(True,32,"00000000 00000000 00000000 00000001")
>>> test (1.1754942107E-38::Float)
(True,32,"00000000 01111111 11111111 11111111")
Instance details

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:

>>> test (0::Int)
(True,8,"00000000")
>>> test (-1::Int)
(True,8,"00000001")
>>> test (1::Int)
(True,8,"00000010")
>>> test (-2::Int)
(True,8,"00000011")
>>> test (2::Int)
(True,8,"00000100")
Instance details

Flat Int8 Source #
>>> test (0::Int8)
(True,8,"00000000")
>>> test (127::Int8)
(True,8,"11111110")
>>> test (-128::Int8)
(True,8,"11111111")
Instance details

Flat Int16 Source #
>>> test (0::Int16)
(True,8,"00000000")
>>> test (1::Int16)
(True,8,"00000010")
>>> test (-1::Int16)
(True,8,"00000001")
>>> test (minBound::Int16)
(True,24,"11111111 11111111 00000011")

equivalent to 0b1111111111111111

>>> test (maxBound::Int16)
(True,24,"11111110 11111111 00000011")

equivalent to 0b1111111111111110

Instance details

Flat Int32 Source #
>>> test (0::Int32)
(True,8,"00000000")
>>> test (minBound::Int32)
(True,40,"11111111 11111111 11111111 11111111 00001111")
>>> test (maxBound::Int32)
(True,40,"11111110 11111111 11111111 11111111 00001111")
Instance details

Flat Int64 Source #
>>> test (0::Int64)
(True,8,"00000000")
>>> test (minBound::Int64)
(True,80,"11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 00000001")
>>> test (maxBound::Int64)
(True,80,"11111110 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 00000001")
Instance details

Flat Integer Source #

Integers are encoded just as the fixed size Ints.

>>> test (0::Integer)
(True,8,"00000000")
>>> test (-1::Integer)
(True,8,"00000001")
>>> test (1::Integer)
(True,8,"00000010")
>>> test (-(2^4)::Integer)
(True,8,"00011111")
>>> test (2^4::Integer)
(True,8,"00100000")
>>> test (-(2^120)::Integer)
(True,144,"11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 11111111 00000011")
>>> test (2^120::Integer)
(True,144,"10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 00000100")
Instance details

Flat Natural Source #

Naturals are encoded just as the fixed size Words.

>>> test (0::Natural)
(True,8,"00000000")
>>> test (2^120::Natural)
(True,144,"10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 10000000 00000010")
Instance details

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

>>> test (127::Word)
(True,8,"01111111")

254 (0b11111110) is represented as Cons V126 (Elem V1) (254=128+126) and encoded as: Cons=1 V126=1111110 (Elem=0 V1=0000001):

>>> test (254::Word)
(True,16,"11111110 00000001")

Another example, 32768 (Ob1000000000000000 = 0000010 0000000 0000000):

>>> test (32768::Word32)
(True,24,"10000000 10000000 00000010")

As this is a variable length encoding, values are encoded in the same way, whatever their type:

>>> all (test (3::Word) ==) [test (3::Word16),test (3::Word32),test (3::Word64)]
True
Instance details

Flat Word8 Source #

Word8 always take 8 bits.

>>> test (0::Word8)
(True,8,"00000000")
>>> test (255::Word8)
(True,8,"11111111")
Instance details

Flat Word16 Source # 
Instance details

Flat Word32 Source # 
Instance details

Flat Word64 Source # 
Instance details

Flat () Source #

`()`, as all data types with a single constructor, has a zero-length encoding.

>>> test ()
(True,0,"")
Instance details

Methods

encode :: () -> Encoding Source #

decode :: Get () Source #

size :: () -> NumBits -> NumBits Source #

Flat All Source #

Since: 0.4.4

Instance details

Flat Any Source #

Since: 0.4.4

Instance details

Flat [Char] Source #

For better encoding/decoding performance, it is useful to declare instances of concrete list types, such as [Char].

>>> test ""
(True,1,"0")
>>> test "aaa"
(True,28,"10110000 11011000 01101100 0010")
Instance details

Flat a => Flat [a] Source #
>>> test ([]::[Bool])
(True,1,"0")
>>> test [False,False]
(True,5,"10100")
Instance details

Methods

encode :: [a] -> Encoding Source #

decode :: Get [a] Source #

size :: [a] -> NumBits -> NumBits Source #

Flat a => Flat (Maybe a) Source #
>>> test (Nothing::Maybe Bool)
(True,1,"0")
>>> test (Just False::Maybe Bool)
(True,2,"10")
Instance details

(Integral a, Flat a) => Flat (Ratio a) Source #

Ratios are encoded as tuples of (numerator,denominator)

>>> test (3%4::Ratio Word8)
(True,16,"00000011 00000100")
Instance details

Flat a => Flat (Complex a) Source #
>>> test (4 :+ 2 :: Complex Word8)
(True,16,"00000100 00000010")
Instance details

Flat (Fixed a) Source #
>>> test (MkFixed 123 :: Fixed E0)
(True,16,"11110110 00000001")
>>> test (MkFixed 123 :: Fixed E0) == test (MkFixed 123 :: Fixed E2)
True
Instance details

Flat a => Flat (Min a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (Max a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (First a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (Last a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (Option a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (Identity a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (Dual a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (Sum a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (Product a) Source #

Since: 0.4.4

Instance details

Flat a => Flat (NonEmpty a) Source #
>>> test (B.fromList [True])
(True,2,"10")
>>> test (B.fromList [False,False])
(True,4,"0100")
Instance details

(Flat a, Flat b) => Flat (Either a b) Source #
>>> test (Left False::Either Bool ())
(True,2,"00")
>>> test (Right ()::Either Bool ())
(True,1,"1")
Instance details

(Flat a, Flat b) => Flat (a, b) Source #

Tuples are supported up to 7 elements.

>>> test (False,())
(True,1,"0")
>>> test ((),())
(True,0,"")

"7 elements tuples ought to be enough for anybody" (Bill Gates - apocryphal)

>>> test (False,True,True,True,False,True,True)
(True,7,"0111011")

tst (1::Int,"2","3","4","5","6","7","8") ...error

Instance details

Methods

encode :: (a, b) -> Encoding Source #

decode :: Get (a, b) Source #

size :: (a, b) -> NumBits -> NumBits Source #

(Flat a, Flat b, Flat c) => Flat (a, b, c) Source # 
Instance details

Methods

encode :: (a, b, c) -> Encoding Source #

decode :: Get (a, b, c) Source #

size :: (a, b, c) -> NumBits -> NumBits Source #

Flat (f a) => Flat (Alt f a) Source #
>>> let w = Just (11::Word8); a = Alt w <> Alt (Just 24) in tst a == tst w
True
>>> let w = Just (11::Word8); a = Alt Nothing <> Alt w in tst a == tst w
True

Since: 0.4.4

Instance details

Methods

encode :: Alt f a -> Encoding Source #

decode :: Get (Alt f a) Source #

size :: Alt f a -> NumBits -> NumBits Source #

(Flat a, Flat b, Flat c, Flat d) => Flat (a, b, c, d) Source # 
Instance details

Methods

encode :: (a, b, c, d) -> Encoding Source #

decode :: Get (a, b, c, d) Source #

size :: (a, b, c, d) -> NumBits -> NumBits Source #

(Flat a, Flat b, Flat c, Flat d, Flat e) => Flat (a, b, c, d, e) Source # 
Instance details

Methods

encode :: (a, b, c, d, e) -> Encoding Source #

decode :: Get (a, b, c, d, e) Source #

size :: (a, b, c, d, e) -> NumBits -> NumBits Source #

(Flat a, Flat b, Flat c, Flat d, Flat e, Flat f) => Flat (a, b, c, d, e, f) Source # 
Instance details

Methods

encode :: (a, b, c, d, e, f) -> Encoding Source #

decode :: Get (a, b, c, d, e, f) Source #

size :: (a, b, c, d, e, f) -> NumBits -> NumBits Source #

(Flat a, Flat b, Flat c, Flat d, Flat e, Flat f, Flat g) => Flat (a, b, c, d, e, f, g) Source # 
Instance details

Methods

encode :: (a, b, c, d, e, f, g) -> Encoding Source #

decode :: Get (a, b, c, d, e, f, g) Source #

size :: (a, b, c, d, e, f, g) -> NumBits -> NumBits Source #