binary-orphans-0.1.3.0: Orphan instances for binary

Copyright(C) 2015 Oleg Grenrus
LicenseBSD3
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

Data.Binary.Orphans

Contents

Description

Provides orphan Binary instances for types in various packages:

  • aeson
  • scientific (prior to scientific-0.3.4.0)
  • semigroups
  • tagged
  • text (through text-binary, or text >= 1.2.1)
  • time
  • unordered-containers
  • vector (through vector-binary-instances)

Also there is Binary Fixed instance.

Synopsis

Class re-export

class Binary t where

The Binary class provides put and get, methods to encode and decode a Haskell value to a lazy ByteString. It mirrors the Read and Show classes for textual representation of Haskell types, and is suitable for serialising Haskell values to disk, over the network.

For decoding and generating simple external binary formats (e.g. C structures), Binary may be used, but in general is not suitable for complex protocols. Instead use the Put and Get primitives directly.

Instances of Binary should satisfy the following property:

decode . encode == id

That is, the get and put methods should be the inverse of each other. A range of instances are provided for basic Haskell types.

Minimal complete definition

Nothing

Methods

put :: t -> Put

Encode a value in the Put monad.

get :: Get t

Decode a value in the Get monad

Instances

Binary Bool 

Methods

put :: Bool -> Put

get :: Get Bool

Binary Char 

Methods

put :: Char -> Put

get :: Get Char

Binary Double 

Methods

put :: Double -> Put

get :: Get Double

Binary Float 

Methods

put :: Float -> Put

get :: Get Float

Binary Int 

Methods

put :: Int -> Put

get :: Get Int

Binary Int8 

Methods

put :: Int8 -> Put

get :: Get Int8

Binary Int16 

Methods

put :: Int16 -> Put

get :: Get Int16

Binary Int32 

Methods

put :: Int32 -> Put

get :: Get Int32

Binary Int64 

Methods

put :: Int64 -> Put

get :: Get Int64

Binary Integer 

Methods

put :: Integer -> Put

get :: Get Integer

Binary Ordering 

Methods

put :: Ordering -> Put

get :: Get Ordering

Binary Word 

Methods

put :: Word -> Put

get :: Get Word

Binary Word8 

Methods

put :: Word8 -> Put

get :: Get Word8

Binary Word16 

Methods

put :: Word16 -> Put

get :: Get Word16

Binary Word32 

Methods

put :: Word32 -> Put

get :: Get Word32

Binary Word64 

Methods

put :: Word64 -> Put

get :: Get Word64

Binary () 

Methods

put :: () -> Put

get :: Get ()

Binary ByteString 
Binary Scientific 
Binary ByteString 
Binary Natural 

Methods

put :: Natural -> Put

get :: Get Natural

Binary IntSet 

Methods

put :: IntSet -> Put

get :: Get IntSet

Binary a => Binary [a] 

Methods

put :: [a] -> Put

get :: Get [a]

(Binary a, Integral a) => Binary (Ratio a) 

Methods

put :: Ratio a -> Put

get :: Get (Ratio a)

Binary a => Binary (Maybe a) 

Methods

put :: Maybe a -> Put

get :: Get (Maybe a)

Binary e => Binary (IntMap e) 

Methods

put :: IntMap e -> Put

get :: Get (IntMap e)

Binary a => Binary (Set a) 

Methods

put :: Set a -> Put

get :: Get (Set a)

Binary e => Binary (Tree e) 

Methods

put :: Tree e -> Put

get :: Get (Tree e)

Binary e => Binary (Seq e) 

Methods

put :: Seq e -> Put

get :: Get (Seq e)

(Binary a, Binary b) => Binary (Either a b) 

Methods

put :: Either a b -> Put

get :: Get (Either a b)

(Binary a, Binary b) => Binary (a, b) 

Methods

put :: (a, b) -> Put

get :: Get (a, b)

(Binary k, Binary e) => Binary (Map k e) 

Methods

put :: Map k e -> Put

get :: Get (Map k e)

(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) 

Methods

put :: UArray i e -> Put

get :: Get (UArray i e)

(Binary i, Ix i, Binary e) => Binary (Array i e) 

Methods

put :: Array i e -> Put

get :: Get (Array i e)

(Binary a, Binary b, Binary c) => Binary (a, b, c) 

Methods

put :: (a, b, c) -> Put

get :: Get (a, b, c)

(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) 

Methods

put :: (a, b, c, d) -> Put

get :: Get (a, b, c, d)

(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) 

Methods

put :: (a, b, c, d, e) -> Put

get :: Get (a, b, c, d, e)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) 

Methods

put :: (a, b, c, d, e, f) -> Put

get :: Get (a, b, c, d, e, f)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) 

Methods

put :: (a, b, c, d, e, f, g) -> Put

get :: Get (a, b, c, d, e, f, g)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h) => Binary (a, b, c, d, e, f, g, h) 

Methods

put :: (a, b, c, d, e, f, g, h) -> Put

get :: Get (a, b, c, d, e, f, g, h)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i) => Binary (a, b, c, d, e, f, g, h, i) 

Methods

put :: (a, b, c, d, e, f, g, h, i) -> Put

get :: Get (a, b, c, d, e, f, g, h, i)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i, Binary j) => Binary (a, b, c, d, e, f, g, h, i, j) 

Methods

put :: (a, b, c, d, e, f, g, h, i, j) -> Put

get :: Get (a, b, c, d, e, f, g, h, i, j)

Module re-export

Orphan instances

Binary UTCTime Source 

Methods

put :: UTCTime -> Put

get :: Get UTCTime

Binary Value Source 

Methods

put :: Value -> Put

get :: Get Value

Binary All Source

Since: binary-orphans-0.1.1.0

Methods

put :: All -> Put

get :: Get All

Binary Any Source

Since: binary-orphans-0.1.1.0

Methods

put :: Any -> Put

get :: Get Any

Binary LocalTime Source 

Methods

put :: LocalTime -> Put

get :: Get LocalTime

Binary TimeOfDay Source 

Methods

put :: TimeOfDay -> Put

get :: Get TimeOfDay

Binary TimeZone Source 

Methods

put :: TimeZone -> Put

get :: Get TimeZone

Binary NominalDiffTime Source 
Binary Day Source 

Methods

put :: Day -> Put

get :: Get Day

Binary UniversalTime Source 
Binary DiffTime Source 

Methods

put :: DiffTime -> Put

get :: Get DiffTime

Binary (Fixed a) Source 

Methods

put :: Fixed a -> Put

get :: Get (Fixed a)

Binary a => Binary (Dual a) Source

Since: 0.1.1.0

Methods

put :: Dual a -> Put

get :: Get (Dual a)

Binary a => Binary (Sum a) Source

Since: binary-orphans-0.1.1.0

Methods

put :: Sum a -> Put

get :: Get (Sum a)

Binary a => Binary (Product a) Source

Since: binary-orphans-0.1.1.0

Methods

put :: Product a -> Put

get :: Get (Product a)

Binary a => Binary (First a) Source

Since: binary-orphans-0.1.1.0

Methods

put :: First a -> Put

get :: Get (First a)

Binary a => Binary (Last a) Source

Since: binary-orphans-0.1.1.0

Methods

put :: Last a -> Put

get :: Get (Last a)

Binary a => Binary (Min a) Source

Since: binary-orphans-0.1.3.0

Methods

put :: Min a -> Put

get :: Get (Min a)

Binary a => Binary (Max a) Source

Since: binary-orphans-0.1.3.0

Methods

put :: Max a -> Put

get :: Get (Max a)

Binary a => Binary (First a) Source

Since: binary-orphans-0.1.3.0

Methods

put :: First a -> Put

get :: Get (First a)

Binary a => Binary (Last a) Source

Since: binary-orphans-0.1.3.0

Methods

put :: Last a -> Put

get :: Get (Last a)

Binary a => Binary (Option a) Source

Since: binary-orphans-0.1.3.0

Methods

put :: Option a -> Put

get :: Get (Option a)

Binary a => Binary (NonEmpty a) Source

Since: binary-orphans-0.1.3.0

Methods

put :: NonEmpty a -> Put

get :: Get (NonEmpty a)

(Hashable v, Eq v, Binary v) => Binary (HashSet v) Source 

Methods

put :: HashSet v -> Put

get :: Get (HashSet v)

(Hashable k, Eq k, Binary k, Binary v) => Binary (HashMap k v) Source 

Methods

put :: HashMap k v -> Put

get :: Get (HashMap k v)

Binary b => Binary (Tagged k s b) Source 

Methods

put :: Tagged k s b -> Put

get :: Get (Tagged k s b)