Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Codec.Borsh
Synopsis
- class BorshSize a => ToBorsh a where
- encodeBorsh :: Encoder a
- newtype Encoder a = Encoder {
- runEncoder :: a -> Builder
- serialiseBorsh :: ToBorsh a => a -> ByteString
- class BorshSize a => FromBorsh a where
- decodeBorsh :: Decoder s a
- data Decoder s a
- data DeserialiseFailure = DeserialiseFailure ByteOffset String
- deserialiseBorsh :: FromBorsh a => ByteString -> Either DeserialiseFailure a
- class BorshSize (a :: Type) where
- type StaticBorshSize a :: KnownSize
- borshSize :: Proxy a -> Size (StaticBorshSize a)
- data Size (a :: KnownSize) where
- SizeKnown :: Word32 -> Size 'HasKnownSize
- SizeVariable :: Size 'HasVariableSize
- data KnownSize
- class BorshSizeSum (xss :: [[Type]]) where
- borshSizeSum :: Proxy xss -> Size (SumKnownSize xss)
- class BorshMaxSize (a :: Type) where
- borshMaxSize :: Proxy a -> Word32
- newtype AsEnum a = AsEnum {
- getEnum :: a
- newtype AsStruct a = AsStruct {
- getStruct :: a
- newtype KnownImpliesMax a = KnownImpliesMax {
- getKnownImpliesMax :: a
Serialisation
class BorshSize a => ToBorsh a where Source #
Methods
encodeBorsh :: Encoder a Source #
Encoder to Borsh
There is no generic default implementation of encodeBorsh
; instead use
deriving-via using AsStruct
or AsEnum
.
Instances
Encoder
An encoder describes how to serialise a given value in BORSH format.
Constructors
Encoder | |
Fields
|
serialiseBorsh :: ToBorsh a => a -> ByteString Source #
Deserialisation
class BorshSize a => FromBorsh a where Source #
Methods
decodeBorsh :: Decoder s a Source #
Decode from Borsh
There is no generic default implementation of decodeBorsh
; instead use
deriving-via using AsStruct
or AsEnum
.
Instances
Decoder
A decoder describes how to match against a single chunk of the input.
For decoders for primitive types, use FromBorsh
instances.
data DeserialiseFailure Source #
Error type for deserialisation.
Constructors
DeserialiseFailure | |
Fields
|
Instances
Exception DeserialiseFailure Source # | |
Defined in Codec.Borsh.Incremental.Monad Methods toException :: DeserialiseFailure -> SomeException # fromException :: SomeException -> Maybe DeserialiseFailure # | |
Show DeserialiseFailure Source # | |
Defined in Codec.Borsh.Incremental.Monad Methods showsPrec :: Int -> DeserialiseFailure -> ShowS # show :: DeserialiseFailure -> String # showList :: [DeserialiseFailure] -> ShowS # | |
Eq DeserialiseFailure Source # | |
Defined in Codec.Borsh.Incremental.Monad Methods (==) :: DeserialiseFailure -> DeserialiseFailure -> Bool # (/=) :: DeserialiseFailure -> DeserialiseFailure -> Bool # |
deserialiseBorsh :: FromBorsh a => ByteString -> Either DeserialiseFailure a Source #
Size of encodings
class BorshSize (a :: Type) where Source #
Associated Types
type StaticBorshSize a :: KnownSize Source #
Methods
Instances
data Size (a :: KnownSize) where Source #
The statically known size of encodings of values of a particular type.
Constructors
SizeKnown :: Word32 -> Size 'HasKnownSize | |
SizeVariable :: Size 'HasVariableSize |
Constructors
HasKnownSize | |
HasVariableSize |
class BorshSizeSum (xss :: [[Type]]) where Source #
Auxiliary class to BorshSize
describing the conditions under which the
size of the encoding of a value of a sum-type is known.
Methods
borshSizeSum :: Proxy xss -> Size (SumKnownSize xss) Source #
Instances
BorshSizeSum ('[] :: [[Type]]) Source # | |
Defined in Codec.Borsh.Class Methods borshSizeSum :: Proxy '[] -> Size (SumKnownSize '[]) Source # | |
BorshSizeSum (xs ': (ys ': zss)) Source # | |
Defined in Codec.Borsh.Class Methods borshSizeSum :: Proxy (xs ': (ys ': zss)) -> Size (SumKnownSize (xs ': (ys ': zss))) Source # | |
All BorshSize xs => BorshSizeSum '[xs] Source # | |
Defined in Codec.Borsh.Class Methods borshSizeSum :: Proxy '[xs] -> Size (SumKnownSize '[xs]) Source # |
class BorshMaxSize (a :: Type) where Source #
Methods
borshMaxSize :: Proxy a -> Word32 Source #
Maximum size of the Borsh encoding
There is no generic default implementation of borshMaxSize
; instead use
deriving-via using AsStruct
or AsEnum
.
However, while it is possible to use deriving-via to derive BorshMaxSize
for your own types, recursive types should not be given an instance (and
the derived function will not terminate).
Instances
Deriving-via support
Deriving-via support for enums (general ADTs)
The Borsh spec https://borsh.io/ mandates that enums have a tag indicating the constructor, even when there is only a single constructor in the enum. In Rust this makes more sense than in Haskell, since in Rust enums and structs are introduced through different keywords. In Haskell, of course, the only difference between them is that a struct is an enum with a single constructor.
The generic encoder en decoder you get in ToBorsh
and FromBorsh
when
deriving via AsEnum
will therefore add the tag, independent of the number of
constructors:
data MyEnum = .. deriving (BorshSize, ToBorsh, FromBorsh) via AsEnum MyEnum
If you want the encoding of a struct, without the tag, you need to derive via
AsStruct
.
Instances
(Generic a, All2 BorshMaxSize (Code a)) => BorshMaxSize (AsEnum a) Source # | |
Defined in Codec.Borsh.Class | |
BorshSizeSum (Code a) => BorshSize (AsEnum a) Source # | |
Defined in Codec.Borsh.Class Associated Types type StaticBorshSize (AsEnum a) :: KnownSize Source # | |
(Generic a, BorshSizeSum (Code a), All2 FromBorsh (Code a)) => FromBorsh (AsEnum a) Source # | |
Defined in Codec.Borsh.Class Methods decodeBorsh :: Decoder s (AsEnum a) Source # | |
(Generic a, BorshSizeSum (Code a), All2 ToBorsh (Code a)) => ToBorsh (AsEnum a) Source # | |
Defined in Codec.Borsh.Class Methods encodeBorsh :: Encoder (AsEnum a) Source # | |
type StaticBorshSize (AsEnum a) Source # | |
Defined in Codec.Borsh.Class |
Deriving-via support for structs
Usage:
data MyStruct = .. deriving (BorshSize, ToBorsh, FromBorsh) via AsStruct MyStruct
NOTE: Doing so may have consequences for forwards compatibility: if a tag
is present, additional constructors can be added without invalidating the
encoding of existing constructors. See also AsEnum
.
Instances
(IsProductType a xs, All BorshMaxSize xs) => BorshMaxSize (AsStruct a) Source # | |
Defined in Codec.Borsh.Class | |
(IsProductType a xs, All BorshSize xs) => BorshSize (AsStruct a) Source # | |
Defined in Codec.Borsh.Class Associated Types type StaticBorshSize (AsStruct a) :: KnownSize Source # | |
(IsProductType a xs, All BorshSize xs, All FromBorsh xs) => FromBorsh (AsStruct a) Source # | |
Defined in Codec.Borsh.Class Methods decodeBorsh :: Decoder s (AsStruct a) Source # | |
(IsProductType a xs, All BorshSize xs, All ToBorsh xs) => ToBorsh (AsStruct a) Source # | |
Defined in Codec.Borsh.Class Methods encodeBorsh :: Encoder (AsStruct a) Source # | |
type StaticBorshSize (AsStruct a) Source # | |
Defined in Codec.Borsh.Class |
newtype KnownImpliesMax a Source #
If the size of a type's Borsh encoding is statically known then we also know the maximum size of the encoding. Useful for deriving-via.
Constructors
KnownImpliesMax | |
Fields
|
Instances
(BorshSize a, StaticBorshSize a ~ 'HasKnownSize) => BorshMaxSize (KnownImpliesMax a) Source # | |
Defined in Codec.Borsh.Class Methods borshMaxSize :: Proxy (KnownImpliesMax a) -> Word32 Source # |