| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Bond.Internal.Imports
- class BondType a => BondStruct a where
- bondStructGetUntagged :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => BondGet t a
- bondStructGetBase :: (Monad (ReaderM t), Protocol t) => a -> BondGet t a
- bondStructGetField :: (Functor (ReaderM t), Monad (ReaderM t), Protocol t) => Ordinal -> a -> BondGet t a
- bondStructPut :: (Monad (BondPutM t), Protocol t) => a -> BondPut t
- getSchema :: Proxy a -> StructSchema
- class (Typeable a, Default a) => BondType a where
- class Hashable a
- class IsString a where
- fromString :: String -> a
- class Protocol t where
- type ReaderM t :: * -> *
- type WriterM t :: * -> *
- bondPutStruct :: BondStruct a => a -> BondPut t
- bondPutBaseStruct :: BondStruct a => a -> BondPut t
- bondGetStruct :: BondStruct a => BondGet t a
- bondGetBaseStruct :: BondStruct a => BondGet t a
- bondPutField :: (BondType a, BondStruct b) => Proxy b -> Ordinal -> a -> BondPut t
- bondPutDefNothingField :: (BondType a, BondStruct b) => Proxy b -> Ordinal -> Maybe a -> BondPut t
- bondPutBool :: Bool -> BondPut t
- bondPutUInt8 :: Word8 -> BondPut t
- bondPutUInt16 :: Word16 -> BondPut t
- bondPutUInt32 :: Word32 -> BondPut t
- bondPutUInt64 :: Word64 -> BondPut t
- bondPutInt8 :: Int8 -> BondPut t
- bondPutInt16 :: Int16 -> BondPut t
- bondPutInt32 :: Int32 -> BondPut t
- bondPutInt64 :: Int64 -> BondPut t
- bondPutFloat :: Float -> BondPut t
- bondPutDouble :: Double -> BondPut t
- bondPutString :: Utf8 -> BondPut t
- bondPutWString :: Utf16 -> BondPut t
- bondPutBlob :: Blob -> BondPut t
- bondPutList :: BondType a => [a] -> BondPut t
- bondPutVector :: BondType a => Vector a -> BondPut t
- bondPutHashSet :: BondType a => HashSet a -> BondPut t
- bondPutSet :: BondType a => Set a -> BondPut t
- bondPutMap :: (BondType k, BondType v) => Map k v -> BondPut t
- bondPutNullable :: BondType a => Maybe a -> BondPut t
- bondPutBonded :: BondStruct a => Bonded a -> BondPut t
- bondGetBool :: BondGet t Bool
- bondGetUInt8 :: BondGet t Word8
- bondGetUInt16 :: BondGet t Word16
- bondGetUInt32 :: BondGet t Word32
- bondGetUInt64 :: BondGet t Word64
- bondGetInt8 :: BondGet t Int8
- bondGetInt16 :: BondGet t Int16
- bondGetInt32 :: BondGet t Int32
- bondGetInt64 :: BondGet t Int64
- bondGetFloat :: BondGet t Float
- bondGetDouble :: BondGet t Double
- bondGetString :: BondGet t Utf8
- bondGetWString :: BondGet t Utf16
- bondGetBlob :: BondGet t Blob
- bondGetList :: BondType a => BondGet t [a]
- bondGetVector :: BondType a => BondGet t (Vector a)
- bondGetHashSet :: (Eq a, Hashable a, BondType a) => BondGet t (HashSet a)
- bondGetSet :: (Ord a, BondType a) => BondGet t (Set a)
- bondGetMap :: (Ord k, BondType k, BondType v) => BondGet t (Map k v)
- bondGetNullable :: BondType a => BondGet t (Maybe a)
- bondGetDefNothing :: BondType a => BondGet t (Maybe a)
- bondGetBonded :: BondStruct a => BondGet t (Bonded a)
- ap :: Monad m => m (a -> b) -> m a -> m b
- asProxyTypeOf :: a -> Proxy * a -> a
- fromOrdinalList :: [Ordinal] -> OrdinalSet
Documentation
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.
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.
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 ProtocolType Source | |
| BondType Modifier Source | |
| BondType Variant Source | |
| BondType Metadata Source | |
| BondType TypeDef Source | |
| BondType FieldDef Source | |
| BondType StructDef Source | |
| BondType SchemaDef Source | |
| BondType a => BondType [a] Source | |
| BondType a => BondType (Maybe a) Source | |
| (Ord a, BondType a) => BondType (Set a) Source | |
| (Eq a, Hashable a, BondType a) => BondType (HashSet a) Source | |
| BondType a => BondType (Vector a) Source | |
| BondStruct a => BondType (Bonded a) Source | |
| (Ord k, BondType k, BondType v) => BondType (Map k v) Source |
class Hashable a
The class of types that can be converted to a hash value.
Minimal implementation: hashWithSalt.
Instances
class IsString a where
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString :: String -> a
Bond serialization protocol, implements all operations.
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
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