bond-haskell-0.1.5.0: Runtime support for BOND serialization

Safe HaskellNone
LanguageHaskell2010

Data.Bond.Internal.Imports

Synopsis

Documentation

class BondEnum a where Source #

Bond enumeration class containing utility functions.

Minimal complete definition

toName, fromName

Methods

toName :: a -> Maybe Text Source #

Convert constant value to name.

fromName :: Text -> Maybe a Source #

Convert constant name to value.

class BondType a => BondStruct a where Source #

Bond top-level structure, can be de/serialized on its own.

Methods

bondStructGetUntagged :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t a Source #

Read all struct fields in order.

bondStructGetBase :: (Monad (ReaderM t), Protocol t) => a -> BondGet t a Source #

Read base struct from stream.

bondStructGetField :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => Ordinal -> a -> BondGet t a Source #

Read field with specific ordinal.

bondStructPut :: (Monad (BondPutM t), Protocol t) => a -> BondPut t Source #

Put all struct fields to stream in order.

getSchema :: Proxy a -> StructSchema Source #

Obtain struct schema.

Instances

BondStruct TypeDef Source # 
BondStruct Variant Source # 
BondStruct Metadata Source # 
BondStruct FieldDef Source # 
BondStruct StructDef Source # 
BondStruct SchemaDef Source # 

class (Typeable a, Default a) => BondType a where Source #

A type bond knows how to read and write to stream as a part of BondStruct.

Minimal complete definition

bondGet, bondPut, getName, getQualifiedName, getElementType

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t a Source #

Read value.

bondPut :: (Monad (BondPutM t), Protocol t) => a -> BondPut t Source #

Write value.

getName :: Proxy a -> Text Source #

Get name of type.

getQualifiedName :: Proxy a -> Text Source #

Get qualified name of type.

getElementType :: Proxy a -> ElementTypeInfo Source #

Get type description.

Instances

BondType Bool Source # 
BondType Double Source # 
BondType Float Source # 
BondType Int8 Source # 
BondType Int16 Source # 
BondType Int32 Source # 
BondType Int64 Source # 
BondType Word8 Source # 
BondType Word16 Source # 
BondType Word32 Source # 
BondType Word64 Source # 
BondType Blob Source # 
BondType Utf16 Source # 
BondType Utf8 Source # 
BondType BondDataType Source # 
BondType Modifier Source # 
BondType ProtocolType Source # 
BondType TypeDef Source # 
BondType Variant Source # 
BondType Metadata Source # 
BondType FieldDef Source # 
BondType StructDef Source # 
BondType SchemaDef Source # 
BondType a => BondType [a] Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t [a] Source #

bondPut :: (Monad (BondPutM t), Protocol t) => [a] -> BondPut t Source #

getName :: Proxy * [a] -> Text Source #

getQualifiedName :: Proxy * [a] -> Text Source #

getElementType :: Proxy * [a] -> ElementTypeInfo Source #

BondType a => BondType (Maybe a) Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t (Maybe a) Source #

bondPut :: (Monad (BondPutM t), Protocol t) => Maybe a -> BondPut t Source #

getName :: Proxy * (Maybe a) -> Text Source #

getQualifiedName :: Proxy * (Maybe a) -> Text Source #

getElementType :: Proxy * (Maybe a) -> ElementTypeInfo Source #

(Ord a, BondType a) => BondType (Set a) Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t (Set a) Source #

bondPut :: (Monad (BondPutM t), Protocol t) => Set a -> BondPut t Source #

getName :: Proxy * (Set a) -> Text Source #

getQualifiedName :: Proxy * (Set a) -> Text Source #

getElementType :: Proxy * (Set a) -> ElementTypeInfo Source #

(Eq a, Hashable a, BondType a) => BondType (HashSet a) Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t (HashSet a) Source #

bondPut :: (Monad (BondPutM t), Protocol t) => HashSet a -> BondPut t Source #

getName :: Proxy * (HashSet a) -> Text Source #

getQualifiedName :: Proxy * (HashSet a) -> Text Source #

getElementType :: Proxy * (HashSet a) -> ElementTypeInfo Source #

BondType a => BondType (Vector a) Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t (Vector a) Source #

bondPut :: (Monad (BondPutM t), Protocol t) => Vector a -> BondPut t Source #

getName :: Proxy * (Vector a) -> Text Source #

getQualifiedName :: Proxy * (Vector a) -> Text Source #

getElementType :: Proxy * (Vector a) -> ElementTypeInfo Source #

BondStruct a => BondType (Bonded a) Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t (Bonded a) Source #

bondPut :: (Monad (BondPutM t), Protocol t) => Bonded a -> BondPut t Source #

getName :: Proxy * (Bonded a) -> Text Source #

getQualifiedName :: Proxy * (Bonded a) -> Text Source #

getElementType :: Proxy * (Bonded a) -> ElementTypeInfo Source #

(Ord k, BondType k, BondType v) => BondType (Map k v) Source # 

Methods

bondGet :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t (Map k v) Source #

bondPut :: (Monad (BondPutM t), Protocol t) => Map k v -> BondPut t Source #

getName :: Proxy * (Map k v) -> Text Source #

getQualifiedName :: Proxy * (Map k v) -> Text Source #

getElementType :: Proxy * (Map k v) -> ElementTypeInfo Source #

class Hashable a #

The class of types that can be converted to a hash value.

Minimal implementation: hashWithSalt.

Instances

Hashable Bool 

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

Hashable Char 

Methods

hashWithSalt :: Int -> Char -> Int #

hash :: Char -> Int #

Hashable Double 

Methods

hashWithSalt :: Int -> Double -> Int #

hash :: Double -> Int #

Hashable Float 

Methods

hashWithSalt :: Int -> Float -> Int #

hash :: Float -> Int #

Hashable Int 

Methods

hashWithSalt :: Int -> Int -> Int #

hash :: Int -> Int #

Hashable Int8 

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Hashable Int16 

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Hashable Int32 

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Hashable Int64 

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Hashable Integer 

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

Hashable Ordering 

Methods

hashWithSalt :: Int -> Ordering -> Int #

hash :: Ordering -> Int #

Hashable Word 

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Hashable Word16 

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Hashable Word32 

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Hashable Word64 

Methods

hashWithSalt :: Int -> Word64 -> Int #

hash :: Word64 -> Int #

Hashable TypeRep 

Methods

hashWithSalt :: Int -> TypeRep -> Int #

hash :: TypeRep -> Int #

Hashable () 

Methods

hashWithSalt :: Int -> () -> Int #

hash :: () -> Int #

Hashable ByteString 
Hashable Scientific 
Hashable ByteString 
Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable Value 

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Hashable BigNat 

Methods

hashWithSalt :: Int -> BigNat -> Int #

hash :: BigNat -> Int #

Hashable Natural 

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

Hashable Void 

Methods

hashWithSalt :: Int -> Void -> Int #

hash :: Void -> Int #

Hashable Version 

Methods

hashWithSalt :: Int -> Version -> Int #

hash :: Version -> Int #

Hashable Unique 

Methods

hashWithSalt :: Int -> Unique -> Int #

hash :: Unique -> Int #

Hashable ThreadId 

Methods

hashWithSalt :: Int -> ThreadId -> Int #

hash :: ThreadId -> Int #

Hashable ShortByteString 
Hashable Ordinal # 

Methods

hashWithSalt :: Int -> Ordinal -> Int #

hash :: Ordinal -> Int #

Hashable Blob # 

Methods

hashWithSalt :: Int -> Blob -> Int #

hash :: Blob -> Int #

Hashable Utf16 # 

Methods

hashWithSalt :: Int -> Utf16 -> Int #

hash :: Utf16 -> Int #

Hashable Utf8 # 

Methods

hashWithSalt :: Int -> Utf8 -> Int #

hash :: Utf8 -> Int #

Hashable BondDataType # 
Hashable Modifier # 

Methods

hashWithSalt :: Int -> Modifier -> Int #

hash :: Modifier -> Int #

Hashable ProtocolType # 
Hashable a => Hashable [a] 

Methods

hashWithSalt :: Int -> [a] -> Int #

hash :: [a] -> Int #

Hashable a => Hashable (Maybe a) 

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

Hashable a => Hashable (Ratio a) 

Methods

hashWithSalt :: Int -> Ratio a -> Int #

hash :: Ratio a -> Int #

Hashable a => Hashable (Min a) 

Methods

hashWithSalt :: Int -> Min a -> Int #

hash :: Min a -> Int #

Hashable a => Hashable (Max a) 

Methods

hashWithSalt :: Int -> Max a -> Int #

hash :: Max a -> Int #

Hashable a => Hashable (First a) 

Methods

hashWithSalt :: Int -> First a -> Int #

hash :: First a -> Int #

Hashable a => Hashable (Last a) 

Methods

hashWithSalt :: Int -> Last a -> Int #

hash :: Last a -> Int #

Hashable a => Hashable (WrappedMonoid a) 
Hashable a => Hashable (Option a) 

Methods

hashWithSalt :: Int -> Option a -> Int #

hash :: Option a -> Int #

Hashable a => Hashable (NonEmpty a) 

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

Hashable (Fixed a) 

Methods

hashWithSalt :: Int -> Fixed a -> Int #

hash :: Fixed a -> Int #

Hashable (StableName a) 

Methods

hashWithSalt :: Int -> StableName a -> Int #

hash :: StableName a -> Int #

Hashable a => Hashable (HashSet a) 

Methods

hashWithSalt :: Int -> HashSet a -> Int #

hash :: HashSet a -> Int #

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

Methods

hashWithSalt :: Int -> Either a b -> Int #

hash :: Either a b -> Int #

(Hashable a1, Hashable a2) => Hashable (a1, a2) 

Methods

hashWithSalt :: Int -> (a1, a2) -> Int #

hash :: (a1, a2) -> Int #

(Hashable k, Hashable v) => Hashable (HashMap k v) 

Methods

hashWithSalt :: Int -> HashMap k v -> Int #

hash :: HashMap k v -> Int #

(Hashable a, Hashable b) => Hashable (Arg a b) 

Methods

hashWithSalt :: Int -> Arg a b -> Int #

hash :: Arg a b -> Int #

(Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) 

Methods

hashWithSalt :: Int -> (a1, a2, a3) -> Int #

hash :: (a1, a2, a3) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4) -> Int #

hash :: (a1, a2, a3, a4) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5) -> Int #

hash :: (a1, a2, a3, a4, a5) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6) -> Int #

hash :: (a1, a2, a3, a4, a5, a6) -> Int #

(Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7) 

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6, a7) -> Int #

hash :: (a1, a2, a3, a4, a5, a6, a7) -> Int #

class IsString a where #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Minimal complete definition

fromString

Methods

fromString :: String -> a #

Instances

IsString ByteString 
IsString ByteString 
IsString Value 

Methods

fromString :: String -> Value #

IsString Utf16 # 

Methods

fromString :: String -> Utf16 #

IsString Utf8 # 

Methods

fromString :: String -> Utf8 #

(~) * a Char => IsString [a] 

Methods

fromString :: String -> [a] #

IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

(~) * a Char => IsString (DList a) 

Methods

fromString :: String -> DList a #

IsString a => IsString (Const * a b) 

Methods

fromString :: String -> Const * a b #

IsString a => IsString (Tagged k s a) 

Methods

fromString :: String -> Tagged k s a #

class NFData a #

A class of types that can be fully evaluated.

Since: 1.1.0.0

Instances

NFData Bool 

Methods

rnf :: Bool -> () #

NFData Char 

Methods

rnf :: Char -> () #

NFData Double 

Methods

rnf :: Double -> () #

NFData Float 

Methods

rnf :: Float -> () #

NFData Int 

Methods

rnf :: Int -> () #

NFData Int8 

Methods

rnf :: Int8 -> () #

NFData Int16 

Methods

rnf :: Int16 -> () #

NFData Int32 

Methods

rnf :: Int32 -> () #

NFData Int64 

Methods

rnf :: Int64 -> () #

NFData Integer 

Methods

rnf :: Integer -> () #

NFData Word 

Methods

rnf :: Word -> () #

NFData Word8 

Methods

rnf :: Word8 -> () #

NFData Word16 

Methods

rnf :: Word16 -> () #

NFData Word32 

Methods

rnf :: Word32 -> () #

NFData Word64 

Methods

rnf :: Word64 -> () #

NFData CallStack

Since: 1.4.2.0

Methods

rnf :: CallStack -> () #

NFData TypeRep

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TypeRep -> () #

NFData () 

Methods

rnf :: () -> () #

NFData TyCon

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TyCon -> () #

NFData ByteString 

Methods

rnf :: ByteString -> () #

NFData Scientific 

Methods

rnf :: Scientific -> () #

NFData Number 

Methods

rnf :: Number -> () #

NFData ByteString 

Methods

rnf :: ByteString -> () #

NFData UTCTime 

Methods

rnf :: UTCTime -> () #

NFData JSONPathElement 

Methods

rnf :: JSONPathElement -> () #

NFData Value 

Methods

rnf :: Value -> () #

NFData Natural

Since: 1.4.0.0

Methods

rnf :: Natural -> () #

NFData Void

Defined as rnf = absurd.

Since: 1.4.0.0

Methods

rnf :: Void -> () #

NFData Version

Since: 1.3.0.0

Methods

rnf :: Version -> () #

NFData Unique

Since: 1.4.0.0

Methods

rnf :: Unique -> () #

NFData ThreadId

Since: 1.4.0.0

Methods

rnf :: ThreadId -> () #

NFData ExitCode

Since: 1.4.2.0

Methods

rnf :: ExitCode -> () #

NFData CChar

Since: 1.4.0.0

Methods

rnf :: CChar -> () #

NFData CSChar

Since: 1.4.0.0

Methods

rnf :: CSChar -> () #

NFData CUChar

Since: 1.4.0.0

Methods

rnf :: CUChar -> () #

NFData CShort

Since: 1.4.0.0

Methods

rnf :: CShort -> () #

NFData CUShort

Since: 1.4.0.0

Methods

rnf :: CUShort -> () #

NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () #

NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () #

NFData CLong

Since: 1.4.0.0

Methods

rnf :: CLong -> () #

NFData CULong

Since: 1.4.0.0

Methods

rnf :: CULong -> () #

NFData CLLong

Since: 1.4.0.0

Methods

rnf :: CLLong -> () #

NFData CULLong

Since: 1.4.0.0

Methods

rnf :: CULLong -> () #

NFData CFloat

Since: 1.4.0.0

Methods

rnf :: CFloat -> () #

NFData CDouble

Since: 1.4.0.0

Methods

rnf :: CDouble -> () #

NFData CPtrdiff

Since: 1.4.0.0

Methods

rnf :: CPtrdiff -> () #

NFData CSize

Since: 1.4.0.0

Methods

rnf :: CSize -> () #

NFData CWchar

Since: 1.4.0.0

Methods

rnf :: CWchar -> () #

NFData CSigAtomic

Since: 1.4.0.0

Methods

rnf :: CSigAtomic -> () #

NFData CClock

Since: 1.4.0.0

Methods

rnf :: CClock -> () #

NFData CTime

Since: 1.4.0.0

Methods

rnf :: CTime -> () #

NFData CUSeconds

Since: 1.4.0.0

Methods

rnf :: CUSeconds -> () #

NFData CSUSeconds

Since: 1.4.0.0

Methods

rnf :: CSUSeconds -> () #

NFData CFile

Since: 1.4.0.0

Methods

rnf :: CFile -> () #

NFData CFpos

Since: 1.4.0.0

Methods

rnf :: CFpos -> () #

NFData CJmpBuf

Since: 1.4.0.0

Methods

rnf :: CJmpBuf -> () #

NFData CIntPtr

Since: 1.4.0.0

Methods

rnf :: CIntPtr -> () #

NFData CUIntPtr

Since: 1.4.0.0

Methods

rnf :: CUIntPtr -> () #

NFData CIntMax

Since: 1.4.0.0

Methods

rnf :: CIntMax -> () #

NFData CUIntMax

Since: 1.4.0.0

Methods

rnf :: CUIntMax -> () #

NFData All

Since: 1.4.0.0

Methods

rnf :: All -> () #

NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> () #

NFData Fingerprint

Since: 1.4.0.0

Methods

rnf :: Fingerprint -> () #

NFData SrcLoc

Since: 1.4.2.0

Methods

rnf :: SrcLoc -> () #

NFData IntSet 

Methods

rnf :: IntSet -> () #

NFData LocalTime 

Methods

rnf :: LocalTime -> () #

NFData ZonedTime 

Methods

rnf :: ZonedTime -> () #

NFData TimeOfDay 

Methods

rnf :: TimeOfDay -> () #

NFData NominalDiffTime 

Methods

rnf :: NominalDiffTime -> () #

NFData Day 

Methods

rnf :: Day -> () #

NFData Ordinal # 

Methods

rnf :: Ordinal -> () #

NFData Blob # 

Methods

rnf :: Blob -> () #

NFData Utf16 # 

Methods

rnf :: Utf16 -> () #

NFData Utf8 # 

Methods

rnf :: Utf8 -> () #

NFData BondDataType # 

Methods

rnf :: BondDataType -> () #

NFData Struct # 

Methods

rnf :: Struct -> () #

NFData Value # 

Methods

rnf :: Value -> () #

NFData Modifier # 

Methods

rnf :: Modifier -> () #

NFData ProtocolType # 

Methods

rnf :: ProtocolType -> () #

NFData TypeDef # 

Methods

rnf :: TypeDef -> () #

NFData Variant # 

Methods

rnf :: Variant -> () #

NFData Metadata # 

Methods

rnf :: Metadata -> () #

NFData FieldDef # 

Methods

rnf :: FieldDef -> () #

NFData StructDef # 

Methods

rnf :: StructDef -> () #

NFData SchemaDef # 

Methods

rnf :: SchemaDef -> () #

NFData a => NFData [a] 

Methods

rnf :: [a] -> () #

NFData a => NFData (Maybe a) 

Methods

rnf :: Maybe a -> () #

NFData a => NFData (Ratio a) 

Methods

rnf :: Ratio a -> () #

NFData (Ptr a)

Since: 1.4.2.0

Methods

rnf :: Ptr a -> () #

NFData (FunPtr a)

Since: 1.4.2.0

Methods

rnf :: FunPtr a -> () #

NFData a => NFData (IResult a) 

Methods

rnf :: IResult a -> () #

NFData a => NFData (Result a) 

Methods

rnf :: Result a -> () #

NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () #

NFData a => NFData (Min a)

Since: 1.4.2.0

Methods

rnf :: Min a -> () #

NFData a => NFData (Max a)

Since: 1.4.2.0

Methods

rnf :: Max a -> () #

NFData a => NFData (First a)

Since: 1.4.2.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.2.0

Methods

rnf :: Last a -> () #

NFData m => NFData (WrappedMonoid m)

Since: 1.4.2.0

Methods

rnf :: WrappedMonoid m -> () #

NFData a => NFData (Option a)

Since: 1.4.2.0

Methods

rnf :: Option a -> () #

NFData a => NFData (NonEmpty a)

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () #

NFData (Fixed a)

Since: 1.3.0.0

Methods

rnf :: Fixed a -> () #

NFData a => NFData (Complex a) 

Methods

rnf :: Complex a -> () #

NFData (StableName a)

Since: 1.4.0.0

Methods

rnf :: StableName a -> () #

NFData a => NFData (ZipList a)

Since: 1.4.0.0

Methods

rnf :: ZipList a -> () #

NFData a => NFData (Dual a)

Since: 1.4.0.0

Methods

rnf :: Dual a -> () #

NFData a => NFData (Sum a)

Since: 1.4.0.0

Methods

rnf :: Sum a -> () #

NFData a => NFData (Product a)

Since: 1.4.0.0

Methods

rnf :: Product a -> () #

NFData a => NFData (First a)

Since: 1.4.0.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.0.0

Methods

rnf :: Last a -> () #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: IORef a -> () #

NFData a => NFData (Down a)

Since: 1.4.0.0

Methods

rnf :: Down a -> () #

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: MVar a -> () #

NFData a => NFData (Digit a) 

Methods

rnf :: Digit a -> () #

NFData a => NFData (Node a) 

Methods

rnf :: Node a -> () #

NFData a => NFData (Elem a) 

Methods

rnf :: Elem a -> () #

NFData a => NFData (FingerTree a) 

Methods

rnf :: FingerTree a -> () #

NFData a => NFData (IntMap a) 

Methods

rnf :: IntMap a -> () #

NFData a => NFData (Tree a) 

Methods

rnf :: Tree a -> () #

NFData a => NFData (Seq a) 

Methods

rnf :: Seq a -> () #

NFData a => NFData (Set a) 

Methods

rnf :: Set a -> () #

NFData a => NFData (DList a) 

Methods

rnf :: DList a -> () #

NFData a => NFData (HashSet a) 

Methods

rnf :: HashSet a -> () #

NFData a => NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData a => NFData (Bonded a) # 

Methods

rnf :: Bonded a -> () #

NFData (a -> b)

This instance is for convenience and consistency with seq. This assumes that WHNF is equivalent to NF for functions.

Since: 1.3.0.0

Methods

rnf :: (a -> b) -> () #

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

Methods

rnf :: Either a b -> () #

(NFData a, NFData b) => NFData (a, b) 

Methods

rnf :: (a, b) -> () #

(NFData k, NFData v) => NFData (HashMap k v) 

Methods

rnf :: HashMap k v -> () #

(NFData k, NFData a) => NFData (Map k a) 

Methods

rnf :: Map k a -> () #

(NFData a, NFData b) => NFData (Array a b) 

Methods

rnf :: Array a b -> () #

(NFData i, NFData r) => NFData (IResult i r) 

Methods

rnf :: IResult i r -> () #

(NFData a, NFData b) => NFData (Arg a b)

Since: 1.4.2.0

Methods

rnf :: Arg a b -> () #

NFData (Proxy k a)

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () #

NFData (STRef s a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: STRef s a -> () #

(NFData k, NFData v) => NFData (Leaf k v) 

Methods

rnf :: Leaf k v -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

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

Methods

rnf :: (a, b, c) -> () #

NFData a => NFData (Const k a b)

Since: 1.4.0.0

Methods

rnf :: Const k a b -> () #

NFData b => NFData (Tagged k s b) 

Methods

rnf :: Tagged k s b -> () #

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

Methods

rnf :: (a, b, c, d) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 

Methods

rnf :: (a1, a2, a3, a4, a5) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> () #

class Protocol t where Source #

Bond serialization protocol, implements all operations.

Associated Types

type ReaderM t :: * -> * Source #

type WriterM t :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut t Source #

Serialize top-level struct

bondPutBaseStruct :: BondStruct a => a -> BondPut t Source #

Serialize base struct

bondGetStruct :: BondStruct a => BondGet t a Source #

Deserialize top-level struct

bondGetBaseStruct :: BondStruct a => BondGet t a Source #

Deserialize base struct

bondPutField :: (BondType a, BondStruct b) => Proxy b -> Ordinal -> a -> BondPut t Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy b -> Ordinal -> Maybe a -> BondPut t Source #

bondPutBool :: Bool -> BondPut t Source #

bondPutUInt8 :: Word8 -> BondPut t Source #

bondPutUInt16 :: Word16 -> BondPut t Source #

bondPutUInt32 :: Word32 -> BondPut t Source #

bondPutUInt64 :: Word64 -> BondPut t Source #

bondPutInt8 :: Int8 -> BondPut t Source #

bondPutInt16 :: Int16 -> BondPut t Source #

bondPutInt32 :: Int32 -> BondPut t Source #

bondPutInt64 :: Int64 -> BondPut t Source #

bondPutFloat :: Float -> BondPut t Source #

bondPutDouble :: Double -> BondPut t Source #

bondPutString :: Utf8 -> BondPut t Source #

bondPutWString :: Utf16 -> BondPut t Source #

bondPutBlob :: Blob -> BondPut t Source #

bondPutList :: BondType a => [a] -> BondPut t Source #

bondPutVector :: BondType a => Vector a -> BondPut t Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut t Source #

bondPutSet :: BondType a => Set a -> BondPut t Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut t Source #

bondPutNullable :: BondType a => Maybe a -> BondPut t Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut t Source #

bondGetBool :: BondGet t Bool Source #

bondGetUInt8 :: BondGet t Word8 Source #

bondGetUInt16 :: BondGet t Word16 Source #

bondGetUInt32 :: BondGet t Word32 Source #

bondGetUInt64 :: BondGet t Word64 Source #

bondGetInt8 :: BondGet t Int8 Source #

bondGetInt16 :: BondGet t Int16 Source #

bondGetInt32 :: BondGet t Int32 Source #

bondGetInt64 :: BondGet t Int64 Source #

bondGetFloat :: BondGet t Float Source #

bondGetDouble :: BondGet t Double Source #

bondGetString :: BondGet t Utf8 Source #

bondGetWString :: BondGet t Utf16 Source #

bondGetBlob :: BondGet t Blob Source #

bondGetList :: BondType a => BondGet t [a] Source #

bondGetVector :: BondType a => BondGet t (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet t (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet t (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet t (Map k v) Source #

bondGetNullable :: BondType a => BondGet t (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet t (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet t (Bonded a) Source #

Instances

Protocol CompactBinaryV1Proto Source # 

Associated Types

type ReaderM CompactBinaryV1Proto :: * -> * Source #

type WriterM CompactBinaryV1Proto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut CompactBinaryV1Proto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut CompactBinaryV1Proto Source #

bondGetStruct :: BondStruct a => BondGet CompactBinaryV1Proto a Source #

bondGetBaseStruct :: BondStruct a => BondGet CompactBinaryV1Proto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut CompactBinaryV1Proto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut CompactBinaryV1Proto Source #

bondPutBool :: Bool -> BondPut CompactBinaryV1Proto Source #

bondPutUInt8 :: Word8 -> BondPut CompactBinaryV1Proto Source #

bondPutUInt16 :: Word16 -> BondPut CompactBinaryV1Proto Source #

bondPutUInt32 :: Word32 -> BondPut CompactBinaryV1Proto Source #

bondPutUInt64 :: Word64 -> BondPut CompactBinaryV1Proto Source #

bondPutInt8 :: Int8 -> BondPut CompactBinaryV1Proto Source #

bondPutInt16 :: Int16 -> BondPut CompactBinaryV1Proto Source #

bondPutInt32 :: Int32 -> BondPut CompactBinaryV1Proto Source #

bondPutInt64 :: Int64 -> BondPut CompactBinaryV1Proto Source #

bondPutFloat :: Float -> BondPut CompactBinaryV1Proto Source #

bondPutDouble :: Double -> BondPut CompactBinaryV1Proto Source #

bondPutString :: Utf8 -> BondPut CompactBinaryV1Proto Source #

bondPutWString :: Utf16 -> BondPut CompactBinaryV1Proto Source #

bondPutBlob :: Blob -> BondPut CompactBinaryV1Proto Source #

bondPutList :: BondType a => [a] -> BondPut CompactBinaryV1Proto Source #

bondPutVector :: BondType a => Vector a -> BondPut CompactBinaryV1Proto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut CompactBinaryV1Proto Source #

bondPutSet :: BondType a => Set a -> BondPut CompactBinaryV1Proto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut CompactBinaryV1Proto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut CompactBinaryV1Proto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut CompactBinaryV1Proto Source #

bondGetBool :: BondGet CompactBinaryV1Proto Bool Source #

bondGetUInt8 :: BondGet CompactBinaryV1Proto Word8 Source #

bondGetUInt16 :: BondGet CompactBinaryV1Proto Word16 Source #

bondGetUInt32 :: BondGet CompactBinaryV1Proto Word32 Source #

bondGetUInt64 :: BondGet CompactBinaryV1Proto Word64 Source #

bondGetInt8 :: BondGet CompactBinaryV1Proto Int8 Source #

bondGetInt16 :: BondGet CompactBinaryV1Proto Int16 Source #

bondGetInt32 :: BondGet CompactBinaryV1Proto Int32 Source #

bondGetInt64 :: BondGet CompactBinaryV1Proto Int64 Source #

bondGetFloat :: BondGet CompactBinaryV1Proto Float Source #

bondGetDouble :: BondGet CompactBinaryV1Proto Double Source #

bondGetString :: BondGet CompactBinaryV1Proto Utf8 Source #

bondGetWString :: BondGet CompactBinaryV1Proto Utf16 Source #

bondGetBlob :: BondGet CompactBinaryV1Proto Blob Source #

bondGetList :: BondType a => BondGet CompactBinaryV1Proto [a] Source #

bondGetVector :: BondType a => BondGet CompactBinaryV1Proto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet CompactBinaryV1Proto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet CompactBinaryV1Proto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet CompactBinaryV1Proto (Map k v) Source #

bondGetNullable :: BondType a => BondGet CompactBinaryV1Proto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet CompactBinaryV1Proto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet CompactBinaryV1Proto (Bonded a) Source #

Protocol CompactBinaryProto Source # 

Associated Types

type ReaderM CompactBinaryProto :: * -> * Source #

type WriterM CompactBinaryProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut CompactBinaryProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut CompactBinaryProto Source #

bondGetStruct :: BondStruct a => BondGet CompactBinaryProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet CompactBinaryProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut CompactBinaryProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut CompactBinaryProto Source #

bondPutBool :: Bool -> BondPut CompactBinaryProto Source #

bondPutUInt8 :: Word8 -> BondPut CompactBinaryProto Source #

bondPutUInt16 :: Word16 -> BondPut CompactBinaryProto Source #

bondPutUInt32 :: Word32 -> BondPut CompactBinaryProto Source #

bondPutUInt64 :: Word64 -> BondPut CompactBinaryProto Source #

bondPutInt8 :: Int8 -> BondPut CompactBinaryProto Source #

bondPutInt16 :: Int16 -> BondPut CompactBinaryProto Source #

bondPutInt32 :: Int32 -> BondPut CompactBinaryProto Source #

bondPutInt64 :: Int64 -> BondPut CompactBinaryProto Source #

bondPutFloat :: Float -> BondPut CompactBinaryProto Source #

bondPutDouble :: Double -> BondPut CompactBinaryProto Source #

bondPutString :: Utf8 -> BondPut CompactBinaryProto Source #

bondPutWString :: Utf16 -> BondPut CompactBinaryProto Source #

bondPutBlob :: Blob -> BondPut CompactBinaryProto Source #

bondPutList :: BondType a => [a] -> BondPut CompactBinaryProto Source #

bondPutVector :: BondType a => Vector a -> BondPut CompactBinaryProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut CompactBinaryProto Source #

bondPutSet :: BondType a => Set a -> BondPut CompactBinaryProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut CompactBinaryProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut CompactBinaryProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut CompactBinaryProto Source #

bondGetBool :: BondGet CompactBinaryProto Bool Source #

bondGetUInt8 :: BondGet CompactBinaryProto Word8 Source #

bondGetUInt16 :: BondGet CompactBinaryProto Word16 Source #

bondGetUInt32 :: BondGet CompactBinaryProto Word32 Source #

bondGetUInt64 :: BondGet CompactBinaryProto Word64 Source #

bondGetInt8 :: BondGet CompactBinaryProto Int8 Source #

bondGetInt16 :: BondGet CompactBinaryProto Int16 Source #

bondGetInt32 :: BondGet CompactBinaryProto Int32 Source #

bondGetInt64 :: BondGet CompactBinaryProto Int64 Source #

bondGetFloat :: BondGet CompactBinaryProto Float Source #

bondGetDouble :: BondGet CompactBinaryProto Double Source #

bondGetString :: BondGet CompactBinaryProto Utf8 Source #

bondGetWString :: BondGet CompactBinaryProto Utf16 Source #

bondGetBlob :: BondGet CompactBinaryProto Blob Source #

bondGetList :: BondType a => BondGet CompactBinaryProto [a] Source #

bondGetVector :: BondType a => BondGet CompactBinaryProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet CompactBinaryProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet CompactBinaryProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet CompactBinaryProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet CompactBinaryProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet CompactBinaryProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet CompactBinaryProto (Bonded a) Source #

Protocol FastBinaryProto Source # 

Associated Types

type ReaderM FastBinaryProto :: * -> * Source #

type WriterM FastBinaryProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut FastBinaryProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut FastBinaryProto Source #

bondGetStruct :: BondStruct a => BondGet FastBinaryProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet FastBinaryProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut FastBinaryProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut FastBinaryProto Source #

bondPutBool :: Bool -> BondPut FastBinaryProto Source #

bondPutUInt8 :: Word8 -> BondPut FastBinaryProto Source #

bondPutUInt16 :: Word16 -> BondPut FastBinaryProto Source #

bondPutUInt32 :: Word32 -> BondPut FastBinaryProto Source #

bondPutUInt64 :: Word64 -> BondPut FastBinaryProto Source #

bondPutInt8 :: Int8 -> BondPut FastBinaryProto Source #

bondPutInt16 :: Int16 -> BondPut FastBinaryProto Source #

bondPutInt32 :: Int32 -> BondPut FastBinaryProto Source #

bondPutInt64 :: Int64 -> BondPut FastBinaryProto Source #

bondPutFloat :: Float -> BondPut FastBinaryProto Source #

bondPutDouble :: Double -> BondPut FastBinaryProto Source #

bondPutString :: Utf8 -> BondPut FastBinaryProto Source #

bondPutWString :: Utf16 -> BondPut FastBinaryProto Source #

bondPutBlob :: Blob -> BondPut FastBinaryProto Source #

bondPutList :: BondType a => [a] -> BondPut FastBinaryProto Source #

bondPutVector :: BondType a => Vector a -> BondPut FastBinaryProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut FastBinaryProto Source #

bondPutSet :: BondType a => Set a -> BondPut FastBinaryProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut FastBinaryProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut FastBinaryProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut FastBinaryProto Source #

bondGetBool :: BondGet FastBinaryProto Bool Source #

bondGetUInt8 :: BondGet FastBinaryProto Word8 Source #

bondGetUInt16 :: BondGet FastBinaryProto Word16 Source #

bondGetUInt32 :: BondGet FastBinaryProto Word32 Source #

bondGetUInt64 :: BondGet FastBinaryProto Word64 Source #

bondGetInt8 :: BondGet FastBinaryProto Int8 Source #

bondGetInt16 :: BondGet FastBinaryProto Int16 Source #

bondGetInt32 :: BondGet FastBinaryProto Int32 Source #

bondGetInt64 :: BondGet FastBinaryProto Int64 Source #

bondGetFloat :: BondGet FastBinaryProto Float Source #

bondGetDouble :: BondGet FastBinaryProto Double Source #

bondGetString :: BondGet FastBinaryProto Utf8 Source #

bondGetWString :: BondGet FastBinaryProto Utf16 Source #

bondGetBlob :: BondGet FastBinaryProto Blob Source #

bondGetList :: BondType a => BondGet FastBinaryProto [a] Source #

bondGetVector :: BondType a => BondGet FastBinaryProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet FastBinaryProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet FastBinaryProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet FastBinaryProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet FastBinaryProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet FastBinaryProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet FastBinaryProto (Bonded a) Source #

Protocol JsonProto Source # 

Associated Types

type ReaderM JsonProto :: * -> * Source #

type WriterM JsonProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut JsonProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut JsonProto Source #

bondGetStruct :: BondStruct a => BondGet JsonProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet JsonProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut JsonProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut JsonProto Source #

bondPutBool :: Bool -> BondPut JsonProto Source #

bondPutUInt8 :: Word8 -> BondPut JsonProto Source #

bondPutUInt16 :: Word16 -> BondPut JsonProto Source #

bondPutUInt32 :: Word32 -> BondPut JsonProto Source #

bondPutUInt64 :: Word64 -> BondPut JsonProto Source #

bondPutInt8 :: Int8 -> BondPut JsonProto Source #

bondPutInt16 :: Int16 -> BondPut JsonProto Source #

bondPutInt32 :: Int32 -> BondPut JsonProto Source #

bondPutInt64 :: Int64 -> BondPut JsonProto Source #

bondPutFloat :: Float -> BondPut JsonProto Source #

bondPutDouble :: Double -> BondPut JsonProto Source #

bondPutString :: Utf8 -> BondPut JsonProto Source #

bondPutWString :: Utf16 -> BondPut JsonProto Source #

bondPutBlob :: Blob -> BondPut JsonProto Source #

bondPutList :: BondType a => [a] -> BondPut JsonProto Source #

bondPutVector :: BondType a => Vector a -> BondPut JsonProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut JsonProto Source #

bondPutSet :: BondType a => Set a -> BondPut JsonProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut JsonProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut JsonProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut JsonProto Source #

bondGetBool :: BondGet JsonProto Bool Source #

bondGetUInt8 :: BondGet JsonProto Word8 Source #

bondGetUInt16 :: BondGet JsonProto Word16 Source #

bondGetUInt32 :: BondGet JsonProto Word32 Source #

bondGetUInt64 :: BondGet JsonProto Word64 Source #

bondGetInt8 :: BondGet JsonProto Int8 Source #

bondGetInt16 :: BondGet JsonProto Int16 Source #

bondGetInt32 :: BondGet JsonProto Int32 Source #

bondGetInt64 :: BondGet JsonProto Int64 Source #

bondGetFloat :: BondGet JsonProto Float Source #

bondGetDouble :: BondGet JsonProto Double Source #

bondGetString :: BondGet JsonProto Utf8 Source #

bondGetWString :: BondGet JsonProto Utf16 Source #

bondGetBlob :: BondGet JsonProto Blob Source #

bondGetList :: BondType a => BondGet JsonProto [a] Source #

bondGetVector :: BondType a => BondGet JsonProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet JsonProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet JsonProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet JsonProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet JsonProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet JsonProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet JsonProto (Bonded a) Source #

Protocol SimpleBinaryV1Proto Source # 

Associated Types

type ReaderM SimpleBinaryV1Proto :: * -> * Source #

type WriterM SimpleBinaryV1Proto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut SimpleBinaryV1Proto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut SimpleBinaryV1Proto Source #

bondGetStruct :: BondStruct a => BondGet SimpleBinaryV1Proto a Source #

bondGetBaseStruct :: BondStruct a => BondGet SimpleBinaryV1Proto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut SimpleBinaryV1Proto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut SimpleBinaryV1Proto Source #

bondPutBool :: Bool -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt8 :: Word8 -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt16 :: Word16 -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt32 :: Word32 -> BondPut SimpleBinaryV1Proto Source #

bondPutUInt64 :: Word64 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt8 :: Int8 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt16 :: Int16 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt32 :: Int32 -> BondPut SimpleBinaryV1Proto Source #

bondPutInt64 :: Int64 -> BondPut SimpleBinaryV1Proto Source #

bondPutFloat :: Float -> BondPut SimpleBinaryV1Proto Source #

bondPutDouble :: Double -> BondPut SimpleBinaryV1Proto Source #

bondPutString :: Utf8 -> BondPut SimpleBinaryV1Proto Source #

bondPutWString :: Utf16 -> BondPut SimpleBinaryV1Proto Source #

bondPutBlob :: Blob -> BondPut SimpleBinaryV1Proto Source #

bondPutList :: BondType a => [a] -> BondPut SimpleBinaryV1Proto Source #

bondPutVector :: BondType a => Vector a -> BondPut SimpleBinaryV1Proto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut SimpleBinaryV1Proto Source #

bondPutSet :: BondType a => Set a -> BondPut SimpleBinaryV1Proto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut SimpleBinaryV1Proto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut SimpleBinaryV1Proto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut SimpleBinaryV1Proto Source #

bondGetBool :: BondGet SimpleBinaryV1Proto Bool Source #

bondGetUInt8 :: BondGet SimpleBinaryV1Proto Word8 Source #

bondGetUInt16 :: BondGet SimpleBinaryV1Proto Word16 Source #

bondGetUInt32 :: BondGet SimpleBinaryV1Proto Word32 Source #

bondGetUInt64 :: BondGet SimpleBinaryV1Proto Word64 Source #

bondGetInt8 :: BondGet SimpleBinaryV1Proto Int8 Source #

bondGetInt16 :: BondGet SimpleBinaryV1Proto Int16 Source #

bondGetInt32 :: BondGet SimpleBinaryV1Proto Int32 Source #

bondGetInt64 :: BondGet SimpleBinaryV1Proto Int64 Source #

bondGetFloat :: BondGet SimpleBinaryV1Proto Float Source #

bondGetDouble :: BondGet SimpleBinaryV1Proto Double Source #

bondGetString :: BondGet SimpleBinaryV1Proto Utf8 Source #

bondGetWString :: BondGet SimpleBinaryV1Proto Utf16 Source #

bondGetBlob :: BondGet SimpleBinaryV1Proto Blob Source #

bondGetList :: BondType a => BondGet SimpleBinaryV1Proto [a] Source #

bondGetVector :: BondType a => BondGet SimpleBinaryV1Proto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet SimpleBinaryV1Proto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet SimpleBinaryV1Proto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet SimpleBinaryV1Proto (Map k v) Source #

bondGetNullable :: BondType a => BondGet SimpleBinaryV1Proto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet SimpleBinaryV1Proto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet SimpleBinaryV1Proto (Bonded a) Source #

Protocol SimpleBinaryProto Source # 

Associated Types

type ReaderM SimpleBinaryProto :: * -> * Source #

type WriterM SimpleBinaryProto :: * -> * Source #

Methods

bondPutStruct :: BondStruct a => a -> BondPut SimpleBinaryProto Source #

bondPutBaseStruct :: BondStruct a => a -> BondPut SimpleBinaryProto Source #

bondGetStruct :: BondStruct a => BondGet SimpleBinaryProto a Source #

bondGetBaseStruct :: BondStruct a => BondGet SimpleBinaryProto a Source #

bondPutField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> a -> BondPut SimpleBinaryProto Source #

bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy * b -> Ordinal -> Maybe a -> BondPut SimpleBinaryProto Source #

bondPutBool :: Bool -> BondPut SimpleBinaryProto Source #

bondPutUInt8 :: Word8 -> BondPut SimpleBinaryProto Source #

bondPutUInt16 :: Word16 -> BondPut SimpleBinaryProto Source #

bondPutUInt32 :: Word32 -> BondPut SimpleBinaryProto Source #

bondPutUInt64 :: Word64 -> BondPut SimpleBinaryProto Source #

bondPutInt8 :: Int8 -> BondPut SimpleBinaryProto Source #

bondPutInt16 :: Int16 -> BondPut SimpleBinaryProto Source #

bondPutInt32 :: Int32 -> BondPut SimpleBinaryProto Source #

bondPutInt64 :: Int64 -> BondPut SimpleBinaryProto Source #

bondPutFloat :: Float -> BondPut SimpleBinaryProto Source #

bondPutDouble :: Double -> BondPut SimpleBinaryProto Source #

bondPutString :: Utf8 -> BondPut SimpleBinaryProto Source #

bondPutWString :: Utf16 -> BondPut SimpleBinaryProto Source #

bondPutBlob :: Blob -> BondPut SimpleBinaryProto Source #

bondPutList :: BondType a => [a] -> BondPut SimpleBinaryProto Source #

bondPutVector :: BondType a => Vector a -> BondPut SimpleBinaryProto Source #

bondPutHashSet :: BondType a => HashSet a -> BondPut SimpleBinaryProto Source #

bondPutSet :: BondType a => Set a -> BondPut SimpleBinaryProto Source #

bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut SimpleBinaryProto Source #

bondPutNullable :: BondType a => Maybe a -> BondPut SimpleBinaryProto Source #

bondPutBonded :: BondStruct a => Bonded a -> BondPut SimpleBinaryProto Source #

bondGetBool :: BondGet SimpleBinaryProto Bool Source #

bondGetUInt8 :: BondGet SimpleBinaryProto Word8 Source #

bondGetUInt16 :: BondGet SimpleBinaryProto Word16 Source #

bondGetUInt32 :: BondGet SimpleBinaryProto Word32 Source #

bondGetUInt64 :: BondGet SimpleBinaryProto Word64 Source #

bondGetInt8 :: BondGet SimpleBinaryProto Int8 Source #

bondGetInt16 :: BondGet SimpleBinaryProto Int16 Source #

bondGetInt32 :: BondGet SimpleBinaryProto Int32 Source #

bondGetInt64 :: BondGet SimpleBinaryProto Int64 Source #

bondGetFloat :: BondGet SimpleBinaryProto Float Source #

bondGetDouble :: BondGet SimpleBinaryProto Double Source #

bondGetString :: BondGet SimpleBinaryProto Utf8 Source #

bondGetWString :: BondGet SimpleBinaryProto Utf16 Source #

bondGetBlob :: BondGet SimpleBinaryProto Blob Source #

bondGetList :: BondType a => BondGet SimpleBinaryProto [a] Source #

bondGetVector :: BondType a => BondGet SimpleBinaryProto (Vector a) Source #

bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet SimpleBinaryProto (HashSet a) Source #

bondGetSet :: (Ord a, BondType a) => BondGet SimpleBinaryProto (Set a) Source #

bondGetMap :: (Ord k, BondType k, BondType v) => BondGet SimpleBinaryProto (Map k v) Source #

bondGetNullable :: BondType a => BondGet SimpleBinaryProto (Maybe a) Source #

bondGetDefNothing :: BondType a => BondGet SimpleBinaryProto (Maybe a) Source #

bondGetBonded :: BondStruct a => BondGet SimpleBinaryProto (Bonded a) Source #

ap :: Monad m => m (a -> b) -> m a -> m b #

In many situations, the liftM operations can be replaced by uses of ap, which promotes function application.

      return f `ap` x1 `ap` ... `ap` xn

is equivalent to

      liftMn f x1 x2 ... xn

asProxyTypeOf :: a -> Proxy * a -> a #

asProxyTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the tag of the second.

fromOrdinalList :: [Ordinal] -> OrdinalSet Source #