| 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 :: Int -> Size 'HasKnownSize
- SizeVariable :: Size 'HasVariableSize
- data KnownSize
- class BorshSizeSum (xss :: [[Type]]) where
- borshSizeSum :: Proxy xss -> Size (SumKnownSize xss)
- newtype Struct a = Struct {
- getStruct :: a
Serialisation
class BorshSize a => ToBorsh a where Source #
Minimal complete definition
Nothing
Methods
encodeBorsh :: Encoder a Source #
Encoder to Borsh
NOTE: The default generic encoder uses the Borsh encoding for enums,
and will therefore use constructor tag; see Struct for detailed
discussion. Since the spec mandates the presence of that constructor tag,
the generic encoder/decoder does not apply to types without constructors.
default encodeBorsh :: (Generic a, BorshSizeSum (Code a), All2 ToBorsh (Code a)) => Encoder a Source #
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 #
Minimal complete definition
Nothing
Methods
decodeBorsh :: Decoder s a Source #
Decode from Borsh
See encodeBorsh for discussion of the generic instance.
default decodeBorsh :: (Generic a, BorshSizeSum (Code a), All2 FromBorsh (Code a)) => Decoder s a Source #
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 #
Minimal complete definition
Nothing
Associated Types
type StaticBorshSize a :: KnownSize Source #
type StaticBorshSize a = SumKnownSize (Code a)
Methods
borshSize :: Proxy a -> Size (StaticBorshSize a) Source #
Size of the Borsh encoding, if known ahead of time
See encodeBorsh for discussion of the generic instance.
default borshSize :: (StaticBorshSize a ~ SumKnownSize (Code a), BorshSizeSum (Code a)) => Proxy a -> Size (StaticBorshSize a) Source #
Instances
data Size (a :: KnownSize) where Source #
The statically known size of encodings of values of a particular type.
Constructors
| SizeKnown :: Int -> 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 # | |
Deriving-via support
Deriving-via support for structs
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 default generic encoder en decoder you get in ToBorsh and FromBorsh
will therefore add the tag, independent of the number of constructors. If
you want the encoding of a struct, without the tag, you need to use deriving
via:
data MyStruct = .. deriving (BorshSize, ToBorsh, FromBorsh) via Struct 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.
Instances
| (IsProductType a xs, All BorshSize xs) => BorshSize (Struct a) Source # | |
Defined in Codec.Borsh.Class Associated Types type StaticBorshSize (Struct a) :: KnownSize Source # | |
| (IsProductType a xs, All BorshSize xs, All FromBorsh xs) => FromBorsh (Struct a) Source # | |
Defined in Codec.Borsh.Class Methods decodeBorsh :: Decoder s (Struct a) Source # | |
| (IsProductType a xs, All BorshSize xs, All ToBorsh xs) => ToBorsh (Struct a) Source # | |
Defined in Codec.Borsh.Class Methods encodeBorsh :: Encoder (Struct a) Source # | |
| type StaticBorshSize (Struct a) Source # | |
Defined in Codec.Borsh.Class | |