binary-orphans-0.1.8.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.

Methods

put :: t -> Put #

Encode a value in the Put monad.

get :: Get t #

Decode a value in the Get monad

putList :: [t] -> Put #

Encode a list of values in the Put monad. The default implementation may be overridden to be more efficient but must still have the same encoding format.

Instances

Binary Bool 

Methods

put :: Bool -> Put #

get :: Get Bool #

putList :: [Bool] -> Put #

Binary Char 

Methods

put :: Char -> Put #

get :: Get Char #

putList :: [Char] -> Put #

Binary Double 

Methods

put :: Double -> Put #

get :: Get Double #

putList :: [Double] -> Put #

Binary Float 

Methods

put :: Float -> Put #

get :: Get Float #

putList :: [Float] -> Put #

Binary Int 

Methods

put :: Int -> Put #

get :: Get Int #

putList :: [Int] -> Put #

Binary Int8 

Methods

put :: Int8 -> Put #

get :: Get Int8 #

putList :: [Int8] -> Put #

Binary Int16 

Methods

put :: Int16 -> Put #

get :: Get Int16 #

putList :: [Int16] -> Put #

Binary Int32 

Methods

put :: Int32 -> Put #

get :: Get Int32 #

putList :: [Int32] -> Put #

Binary Int64 

Methods

put :: Int64 -> Put #

get :: Get Int64 #

putList :: [Int64] -> Put #

Binary Integer 

Methods

put :: Integer -> Put #

get :: Get Integer #

putList :: [Integer] -> Put #

Binary Ordering 

Methods

put :: Ordering -> Put #

get :: Get Ordering #

putList :: [Ordering] -> Put #

Binary Word 

Methods

put :: Word -> Put #

get :: Get Word #

putList :: [Word] -> Put #

Binary Word8 

Methods

put :: Word8 -> Put #

get :: Get Word8 #

putList :: [Word8] -> Put #

Binary Word16 

Methods

put :: Word16 -> Put #

get :: Get Word16 #

putList :: [Word16] -> Put #

Binary Word32 

Methods

put :: Word32 -> Put #

get :: Get Word32 #

putList :: [Word32] -> Put #

Binary Word64 

Methods

put :: Word64 -> Put #

get :: Get Word64 #

putList :: [Word64] -> Put #

Binary () 

Methods

put :: () -> Put #

get :: Get () #

putList :: [()] -> Put #

Binary ByteString 
Binary ByteString 
Binary Scientific 
Binary Natural

Since: 0.7.3.0

Methods

put :: Natural -> Put #

get :: Get Natural #

putList :: [Natural] -> Put #

Binary Void

Since: 0.8.0.0

Methods

put :: Void -> Put #

get :: Get Void #

putList :: [Void] -> Put #

Binary Version

Since: 0.8.0.0

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

Binary Fingerprint

Since: 0.7.6.0

Binary ShortByteString 
Binary IntSet 

Methods

put :: IntSet -> Put #

get :: Get IntSet #

putList :: [IntSet] -> Put #

Binary a => Binary [a] 

Methods

put :: [a] -> Put #

get :: Get [a] #

putList :: [[a]] -> Put #

Binary a => Binary (Maybe a) 

Methods

put :: Maybe a -> Put #

get :: Get (Maybe a) #

putList :: [Maybe a] -> Put #

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

Methods

put :: Ratio a -> Put #

get :: Get (Ratio a) #

putList :: [Ratio a] -> Put #

Binary (Fixed a)

Since: 0.8.0.0

Methods

put :: Fixed a -> Put #

get :: Get (Fixed a) #

putList :: [Fixed a] -> Put #

Binary a => Binary (Complex a) 

Methods

put :: Complex a -> Put #

get :: Get (Complex a) #

putList :: [Complex a] -> Put #

Binary e => Binary (IntMap e) 

Methods

put :: IntMap e -> Put #

get :: Get (IntMap e) #

putList :: [IntMap e] -> Put #

Binary e => Binary (Tree e) 

Methods

put :: Tree e -> Put #

get :: Get (Tree e) #

putList :: [Tree e] -> Put #

Binary e => Binary (Seq e) 

Methods

put :: Seq e -> Put #

get :: Get (Seq e) #

putList :: [Seq e] -> Put #

Binary a => Binary (Set a) 

Methods

put :: Set a -> Put #

get :: Get (Set a) #

putList :: [Set a] -> Put #

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

Methods

put :: Either a b -> Put #

get :: Get (Either a b) #

putList :: [Either a b] -> Put #

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

Methods

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

get :: Get (a, b) #

putList :: [(a, b)] -> Put #

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

Methods

put :: Map k e -> Put #

get :: Get (Map k e) #

putList :: [Map k e] -> Put #

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

Methods

put :: UArray i e -> Put #

get :: Get (UArray i e) #

putList :: [UArray i e] -> Put #

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

Methods

put :: Array i e -> Put #

get :: Get (Array i e) #

putList :: [Array i e] -> Put #

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

Methods

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

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

putList :: [(a, b, c)] -> Put #

(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) #

putList :: [(a, b, c, d)] -> Put #

(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) #

putList :: [(a, b, c, d, e)] -> Put #

(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) #

putList :: [(a, b, c, d, e, f)] -> Put #

(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) #

putList :: [(a, b, c, d, e, f, g)] -> Put #

(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) #

putList :: [(a, b, c, d, e, f, g, h)] -> Put #

(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) #

putList :: [(a, b, c, d, e, f, g, h, i)] -> Put #

(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) #

putList :: [(a, b, c, d, e, f, g, h, i, j)] -> Put #

Module re-export

Orphan instances

Binary UTCTime Source # 

Methods

put :: UTCTime -> Put #

get :: Get UTCTime #

putList :: [UTCTime] -> Put #

Binary Value Source # 

Methods

put :: Value -> Put #

get :: Get Value #

putList :: [Value] -> Put #

Binary All Source #

Since: binary-orphans-0.1.1.0

Methods

put :: All -> Put #

get :: Get All #

putList :: [All] -> Put #

Binary Any Source #

Since: binary-orphans-0.1.1.0

Methods

put :: Any -> Put #

get :: Get Any #

putList :: [Any] -> Put #

Binary AbsoluteTime Source #

Since: binary-orphans-0.1.4.0

Binary LocalTime Source # 
Binary ZonedTime Source #

Since: binary-orphans-0.1.8.0

Binary TimeOfDay Source # 
Binary TimeZone Source # 

Methods

put :: TimeZone -> Put #

get :: Get TimeZone #

putList :: [TimeZone] -> Put #

Binary NominalDiffTime Source # 
Binary Day Source # 

Methods

put :: Day -> Put #

get :: Get Day #

putList :: [Day] -> Put #

Binary UniversalTime Source # 
Binary DiffTime Source # 

Methods

put :: DiffTime -> Put #

get :: Get DiffTime #

putList :: [DiffTime] -> Put #

Binary a => Binary (Min a) Source #

Since: binary-orphans-0.1.3.0

Methods

put :: Min a -> Put #

get :: Get (Min a) #

putList :: [Min a] -> Put #

Binary a => Binary (Max a) Source #

Since: binary-orphans-0.1.3.0

Methods

put :: Max a -> Put #

get :: Get (Max a) #

putList :: [Max a] -> Put #

Binary a => Binary (First a) Source #

Since: binary-orphans-0.1.3.0

Methods

put :: First a -> Put #

get :: Get (First a) #

putList :: [First a] -> Put #

Binary a => Binary (Last a) Source #

Since: binary-orphans-0.1.3.0

Methods

put :: Last a -> Put #

get :: Get (Last a) #

putList :: [Last a] -> Put #

Binary m => Binary (WrappedMonoid m) Source #

Since: binary-orphans-0.1.5.0

Binary a => Binary (Option a) Source #

Since: binary-orphans-0.1.3.0

Methods

put :: Option a -> Put #

get :: Get (Option a) #

putList :: [Option a] -> Put #

Binary a => Binary (NonEmpty a) Source #

Since: binary-orphans-0.1.3.0

Methods

put :: NonEmpty a -> Put #

get :: Get (NonEmpty a) #

putList :: [NonEmpty a] -> Put #

Binary a => Binary (Dual a) Source #

Since: 0.1.1.0

Methods

put :: Dual a -> Put #

get :: Get (Dual a) #

putList :: [Dual a] -> Put #

Binary a => Binary (Sum a) Source #

Since: binary-orphans-0.1.1.0

Methods

put :: Sum a -> Put #

get :: Get (Sum a) #

putList :: [Sum a] -> Put #

Binary a => Binary (Product a) Source #

Since: binary-orphans-0.1.1.0

Methods

put :: Product a -> Put #

get :: Get (Product a) #

putList :: [Product a] -> Put #

Binary a => Binary (First a) Source #

Since: binary-orphans-0.1.1.0

Methods

put :: First a -> Put #

get :: Get (First a) #

putList :: [First a] -> Put #

Binary a => Binary (Last a) Source #

Since: binary-orphans-0.1.1.0

Methods

put :: Last a -> Put #

get :: Get (Last a) #

putList :: [Last a] -> Put #

(FoldCase a, Binary a) => Binary (CI a) Source #

Since: binary-orphans-0.1.5.0

Methods

put :: CI a -> Put #

get :: Get (CI a) #

putList :: [CI a] -> Put #

(Hashable a, Binary a) => Binary (Hashed a) Source # 

Methods

put :: Hashed a -> Put #

get :: Get (Hashed a) #

putList :: [Hashed a] -> Put #

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

Methods

put :: HashSet v -> Put #

get :: Get (HashSet v) #

putList :: [HashSet v] -> Put #

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

Methods

put :: HashMap k v -> Put #

get :: Get (HashMap k v) #

putList :: [HashMap k v] -> Put #

(Binary a, Binary b) => Binary (Arg a b) Source #

Since: binary-orphans-0.1.5.0

Methods

put :: Arg a b -> Put #

get :: Get (Arg a b) #

putList :: [Arg a b] -> Put #

Binary (f a) => Binary (Alt k f a) Source #

Since: binary-orphans-0.1.5.0

Methods

put :: Alt k f a -> Put #

get :: Get (Alt k f a) #

putList :: [Alt k f a] -> Put #

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

Methods

put :: Tagged k s b -> Put #

get :: Get (Tagged k s b) #

putList :: [Tagged k s b] -> Put #