{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoStarIsType #-}
module Cardano.Ledger.Binary.Encoding.EncCBOR (
EncCBOR (..),
withWordSize,
PreEncoded (..),
toByronCBOR,
Range (..),
szEval,
Size,
Case (..),
caseValue,
LengthOf (..),
SizeOverride (..),
isTodo,
szCases,
szLazy,
szGreedy,
szForce,
szWithCtx,
szSimplify,
apMono,
szBounds,
encodedVerKeyDSIGNSizeExpr,
encodedSignKeyDSIGNSizeExpr,
encodedSigDSIGNSizeExpr,
encodedSignedDSIGNSizeExpr,
encodedVerKeyKESSizeExpr,
encodedSignKeyKESSizeExpr,
encodedSigKESSizeExpr,
encodedVerKeyVRFSizeExpr,
encodedSignKeyVRFSizeExpr,
encodedCertVRFSizeExpr,
)
where
import Cardano.Crypto.DSIGN.Class (
DSIGNAlgorithm,
SigDSIGN,
SignKeyDSIGN,
SignedDSIGN,
VerKeyDSIGN,
sizeSigDSIGN,
sizeSignKeyDSIGN,
sizeVerKeyDSIGN,
)
import Cardano.Crypto.Hash.Class (
Hash (..),
HashAlgorithm,
hashToBytes,
sizeHash,
)
import Cardano.Crypto.KES.Class (
KESAlgorithm,
SigKES,
SignKeyKES,
VerKeyKES,
sizeSigKES,
sizeSignKeyKES,
sizeVerKeyKES,
)
import Cardano.Crypto.VRF.Class (
CertVRF,
CertifiedVRF (..),
OutputVRF (..),
SignKeyVRF,
VRFAlgorithm,
VerKeyVRF,
sizeCertVRF,
sizeOutputVRF,
sizeSignKeyVRF,
sizeVerKeyVRF,
)
import Cardano.Crypto.VRF.Mock (MockVRF)
import qualified Cardano.Crypto.VRF.Praos as Praos
import Cardano.Crypto.VRF.Simple (SimpleVRF)
import Cardano.Ledger.Binary.Crypto
import Cardano.Ledger.Binary.Encoding.Encoder
import Cardano.Ledger.Binary.Version (Version, byronProtVer, getVersion64)
import Cardano.Slotting.Block (BlockNo (..))
import Cardano.Slotting.Slot (
EpochInterval (..),
EpochNo (..),
EpochSize (..),
SlotNo (..),
WithOrigin (..),
)
import Cardano.Slotting.Time (SystemStart (..))
import Codec.CBOR.ByteArray (ByteArray (..))
import Codec.CBOR.ByteArray.Sliced (SlicedByteArray (SBA), fromByteArray)
import qualified Codec.CBOR.Encoding as C (Encoding (..))
import Codec.CBOR.Term (Term (..))
import qualified Codec.Serialise as Serialise (Serialise (encode))
import Control.Category (Category ((.)))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BS.Lazy
import qualified Data.ByteString.Short as SBS (length)
#if MIN_VERSION_bytestring(0,11,1)
import Data.ByteString.Short (ShortByteString(SBS))
#else
import Data.ByteString.Short.Internal (ShortByteString(SBS))
#endif
import qualified Cardano.Binary as Plain (Encoding, ToCBOR (..))
import Data.Fixed (Fixed (..))
import Data.Foldable (toList)
import Data.Functor.Foldable (cata, project)
import Data.IP (IPv4, IPv6)
import Data.Int (Int16, Int32, Int64, Int8)
import Data.List.NonEmpty (NonEmpty)
import qualified Data.Map.Strict as Map
import qualified Data.Maybe.Strict as SMaybe
import qualified Data.Primitive.ByteArray as Prim (ByteArray (..))
import Data.Ratio (Ratio)
import qualified Data.Sequence as Seq
import qualified Data.Sequence.Strict as SSeq
import qualified Data.Set as Set
import Data.Tagged (Tagged (..))
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Text.Lazy.Builder (Builder)
import Data.Time.Clock (UTCTime (..))
import Data.Typeable (Proxy (..), TypeRep, Typeable, typeRep)
import qualified Data.VMap as VMap
import qualified Data.Vector as V
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
import Data.Void (Void, absurd)
import Data.Word (Word16, Word32, Word64, Word8)
import Foreign.Storable (sizeOf)
import Formatting (bprint, build, shown, stext)
import qualified Formatting.Buildable as B (Buildable (..))
import Numeric.Natural (Natural)
import qualified PlutusLedgerApi.V1 as PV1
import qualified PlutusLedgerApi.V2 as PV2
import qualified PlutusLedgerApi.V3 as PV3
import Prelude hiding (encodeFloat, (.))
#if MIN_VERSION_recursion_schemes(5,2,0)
import Data.Fix (Fix(..))
#else
import Data.Functor.Foldable (Fix(..))
#endif
class Typeable a => EncCBOR a where
encCBOR :: a -> Encoding
default encCBOR :: Plain.ToCBOR a => a -> Encoding
encCBOR = Encoding -> Encoding
fromPlainEncoding forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. ToCBOR a => a -> Encoding
Plain.toCBOR
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
todo
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
encodedListSizeExpr = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
defaultEncodedListSizeExpr
newtype LengthOf xs = LengthOf xs
instance Typeable xs => EncCBOR (LengthOf xs) where
encCBOR :: LengthOf xs -> Encoding
encCBOR = forall a. HasCallStack => [Char] -> a
error [Char]
"The `LengthOf` type cannot be encoded!"
defaultEncodedListSizeExpr ::
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) ->
Proxy [a] ->
Size
defaultEncodedListSizeExpr :: forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
defaultEncodedListSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy [a]
_ =
Size
2 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf [a])) forall a. Num a => a -> a -> a
* forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
newtype PreEncoded = PreEncoded {PreEncoded -> ByteString
unPreEncoded :: BS.ByteString}
instance EncCBOR PreEncoded where
encCBOR :: PreEncoded -> Encoding
encCBOR = ByteString -> Encoding
encodePreEncoded forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. PreEncoded -> ByteString
unPreEncoded
instance EncCBOR Version where
encCBOR :: Version -> Encoding
encCBOR = Version -> Encoding
encodeVersion
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Version -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
f Proxy Version
px = forall t. EncCBOR t => Proxy t -> Size
f (Version -> Word64
getVersion64 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy Version
px)
toByronCBOR :: EncCBOR a => a -> Plain.Encoding
toByronCBOR :: forall a. EncCBOR a => a -> Encoding
toByronCBOR = Version -> Encoding -> Encoding
toPlainEncoding Version
byronProtVer forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. EncCBOR a => a -> Encoding
encCBOR
(.:) :: (c -> d) -> (a -> b -> c) -> (a -> b -> d)
c -> d
f .: :: forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: a -> b -> c
g = \a
x b
y -> c -> d
f (a -> b -> c
g a
x b
y)
type Size = Fix SizeF
data SizeF t
=
AddF t t
|
MulF t t
|
SubF t t
|
AbsF t
|
NegF t
|
SgnF t
|
CasesF [Case t]
|
ValueF Natural
|
ApF Text (Natural -> Natural) t
|
forall a. EncCBOR a => TodoF (forall x. EncCBOR x => Proxy x -> Size) (Proxy a)
instance Functor SizeF where
fmap :: forall a b. (a -> b) -> SizeF a -> SizeF b
fmap a -> b
f = \case
AddF a
x a
y -> forall t. t -> t -> SizeF t
AddF (a -> b
f a
x) (a -> b
f a
y)
MulF a
x a
y -> forall t. t -> t -> SizeF t
MulF (a -> b
f a
x) (a -> b
f a
y)
SubF a
x a
y -> forall t. t -> t -> SizeF t
SubF (a -> b
f a
x) (a -> b
f a
y)
AbsF a
x -> forall t. t -> SizeF t
AbsF (a -> b
f a
x)
NegF a
x -> forall t. t -> SizeF t
NegF (a -> b
f a
x)
SgnF a
x -> forall t. t -> SizeF t
SgnF (a -> b
f a
x)
CasesF [Case a]
xs -> forall t. [Case t] -> SizeF t
CasesF (forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) [Case a]
xs)
ValueF Natural
x -> forall t. Natural -> SizeF t
ValueF Natural
x
ApF Text
n Natural -> Natural
g a
x -> forall t. Text -> (Natural -> Natural) -> t -> SizeF t
ApF Text
n Natural -> Natural
g (a -> b
f a
x)
TodoF forall t. EncCBOR t => Proxy t -> Size
g Proxy a
x -> forall t a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> SizeF t
TodoF forall t. EncCBOR t => Proxy t -> Size
g Proxy a
x
instance Num (Fix SizeF) where
+ :: Size -> Size -> Size
(+) = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: forall t. t -> t -> SizeF t
AddF
* :: Size -> Size -> Size
(*) = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: forall t. t -> t -> SizeF t
MulF
(-) = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: forall t. t -> t -> SizeF t
SubF
negate :: Size -> Size
negate = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. t -> SizeF t
NegF
abs :: Size -> Size
abs = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. t -> SizeF t
AbsF
signum :: Size -> Size
signum = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. t -> SizeF t
SgnF
fromInteger :: Integer -> Size
fromInteger = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. Natural -> SizeF t
ValueF forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Num a => Integer -> a
fromInteger
instance B.Buildable t => B.Buildable (SizeF t) where
build :: SizeF t -> Builder
build SizeF t
x_ =
let showp2 :: (B.Buildable a, B.Buildable b) => a -> Text -> b -> Builder
showp2 :: forall a b. (Buildable a, Buildable b) => a -> Text -> b -> Builder
showp2 = forall a. Format Builder a -> a
bprint (Format (a -> Text -> b -> Builder) (a -> Text -> b -> Builder)
"(" forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (Text -> b -> Builder) (Text -> b -> Builder)
" " forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall r. Format r (Text -> r)
stext forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (b -> Builder) (b -> Builder)
" " forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
")")
in case SizeF t
x_ of
AddF t
x t
y -> forall a b. (Buildable a, Buildable b) => a -> Text -> b -> Builder
showp2 t
x Text
"+" t
y
MulF t
x t
y -> forall a b. (Buildable a, Buildable b) => a -> Text -> b -> Builder
showp2 t
x Text
"*" t
y
SubF t
x t
y -> forall a b. (Buildable a, Buildable b) => a -> Text -> b -> Builder
showp2 t
x Text
"-" t
y
NegF t
x -> forall a. Format Builder a -> a
bprint (Format (t -> Builder) (t -> Builder)
"-" forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build) t
x
AbsF t
x -> forall a. Format Builder a -> a
bprint (Format (t -> Builder) (t -> Builder)
"|" forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
"|") t
x
SgnF t
x -> forall a. Format Builder a -> a
bprint (Format (t -> Builder) (t -> Builder)
"sgn(" forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
")") t
x
CasesF [Case t]
xs ->
forall a. Format Builder a -> a
bprint (Format (Builder -> Builder) (Builder -> Builder)
"{ " forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
"}") forall a b. (a -> b) -> a -> b
$ forall (t :: Type -> Type) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall a. Format Builder a -> a
bprint (forall a r. Buildable a => Format r (a -> r)
build forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
" ")) [Case t]
xs
ValueF Natural
x -> forall a. Format Builder a -> a
bprint forall a r. Show a => Format r (a -> r)
shown (forall a. Integral a => a -> Integer
toInteger Natural
x)
ApF Text
n Natural -> Natural
_ t
x -> forall a. Format Builder a -> a
bprint (forall r. Format r (Text -> r)
stext forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (t -> Builder) (t -> Builder)
"(" forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
")") Text
n t
x
TodoF forall t. EncCBOR t => Proxy t -> Size
_ Proxy a
x -> forall a. Format Builder a -> a
bprint (Format (TypeRep -> Builder) (TypeRep -> Builder)
"(_ :: " forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Show a => Format r (a -> r)
shown forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Builder Builder
")") (forall {k} (proxy :: k -> Type) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep Proxy a
x)
instance B.Buildable (Fix SizeF) where
build :: Size -> Builder
build Size
x = forall a. Format Builder a -> a
bprint forall a r. Buildable a => Format r (a -> r)
build (forall t. Recursive t => t -> Base t t
project @(Fix _) Size
x)
szCases :: [Case Size] -> Size
szCases :: [Case Size] -> Size
szCases = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. [Case t] -> SizeF t
CasesF
data Case t
= Case Text t
deriving (forall a b. a -> Case b -> Case a
forall a b. (a -> b) -> Case a -> Case b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Case b -> Case a
$c<$ :: forall a b. a -> Case b -> Case a
fmap :: forall a b. (a -> b) -> Case a -> Case b
$cfmap :: forall a b. (a -> b) -> Case a -> Case b
Functor)
caseValue :: Case t -> t
caseValue :: forall t. Case t -> t
caseValue (Case Text
_ t
x) = t
x
instance B.Buildable t => B.Buildable (Case t) where
build :: Case t -> Builder
build (Case Text
n t
x) = forall a. Format Builder a -> a
bprint (forall r. Format r (Text -> r)
stext forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (t -> Builder) (t -> Builder)
"=" forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Buildable a => Format r (a -> r)
build) Text
n t
x
data Range b = Range
{ forall b. Range b -> b
lo :: b
, forall b. Range b -> b
hi :: b
}
instance (Ord b, Num b) => Num (Range b) where
Range b
x + :: Range b -> Range b -> Range b
+ Range b
y = Range {lo :: b
lo = forall b. Range b -> b
lo Range b
x forall a. Num a => a -> a -> a
+ forall b. Range b -> b
lo Range b
y, hi :: b
hi = forall b. Range b -> b
hi Range b
x forall a. Num a => a -> a -> a
+ forall b. Range b -> b
hi Range b
y}
Range b
x * :: Range b -> Range b -> Range b
* Range b
y =
let products :: [b]
products = [b
u forall a. Num a => a -> a -> a
* b
v | b
u <- [forall b. Range b -> b
lo Range b
x, forall b. Range b -> b
hi Range b
x], b
v <- [forall b. Range b -> b
lo Range b
y, forall b. Range b -> b
hi Range b
y]]
in Range {lo :: b
lo = forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
minimum [b]
products, hi :: b
hi = forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
maximum [b]
products}
Range b
x - :: Range b -> Range b -> Range b
- Range b
y = Range {lo :: b
lo = forall b. Range b -> b
lo Range b
x forall a. Num a => a -> a -> a
- forall b. Range b -> b
hi Range b
y, hi :: b
hi = forall b. Range b -> b
hi Range b
x forall a. Num a => a -> a -> a
- forall b. Range b -> b
lo Range b
y}
negate :: Range b -> Range b
negate Range b
x = Range {lo :: b
lo = forall a. Num a => a -> a
negate (forall b. Range b -> b
hi Range b
x), hi :: b
hi = forall a. Num a => a -> a
negate (forall b. Range b -> b
lo Range b
x)}
abs :: Range b -> Range b
abs Range b
x =
if
| forall b. Range b -> b
lo Range b
x forall a. Ord a => a -> a -> Bool
<= b
0 Bool -> Bool -> Bool
&& forall b. Range b -> b
hi Range b
x forall a. Ord a => a -> a -> Bool
>= b
0 -> Range {lo :: b
lo = b
0, hi :: b
hi = forall a. Ord a => a -> a -> a
max (forall b. Range b -> b
hi Range b
x) (forall a. Num a => a -> a
negate forall a b. (a -> b) -> a -> b
$ forall b. Range b -> b
lo Range b
x)}
| forall b. Range b -> b
lo Range b
x forall a. Ord a => a -> a -> Bool
<= b
0 Bool -> Bool -> Bool
&& forall b. Range b -> b
hi Range b
x forall a. Ord a => a -> a -> Bool
<= b
0 -> Range {lo :: b
lo = forall a. Num a => a -> a
negate (forall b. Range b -> b
hi Range b
x), hi :: b
hi = forall a. Num a => a -> a
negate (forall b. Range b -> b
lo Range b
x)}
| Bool
otherwise -> Range b
x
signum :: Range b -> Range b
signum Range b
x = Range {lo :: b
lo = forall a. Num a => a -> a
signum (forall b. Range b -> b
lo Range b
x), hi :: b
hi = forall a. Num a => a -> a
signum (forall b. Range b -> b
hi Range b
x)}
fromInteger :: Integer -> Range b
fromInteger Integer
n = Range {lo :: b
lo = forall a. Num a => Integer -> a
fromInteger Integer
n, hi :: b
hi = forall a. Num a => Integer -> a
fromInteger Integer
n}
instance B.Buildable (Range Natural) where
build :: Range Natural -> Builder
build Range Natural
r = forall a. Format Builder a -> a
bprint (forall a r. Show a => Format r (a -> r)
shown forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format (Integer -> Builder) (Integer -> Builder)
".." forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a r. Show a => Format r (a -> r)
shown) (forall a. Integral a => a -> Integer
toInteger forall a b. (a -> b) -> a -> b
$ forall b. Range b -> b
lo Range Natural
r) (forall a. Integral a => a -> Integer
toInteger forall a b. (a -> b) -> a -> b
$ forall b. Range b -> b
hi Range Natural
r)
szEval ::
(forall t. EncCBOR t => (Proxy t -> Size) -> Proxy t -> Range Natural) ->
Size ->
Range Natural
szEval :: (forall t.
EncCBOR t =>
(Proxy t -> Size) -> Proxy t -> Range Natural)
-> Size -> Range Natural
szEval forall t.
EncCBOR t =>
(Proxy t -> Size) -> Proxy t -> Range Natural
doit = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata forall a b. (a -> b) -> a -> b
$ \case
AddF Range Natural
x Range Natural
y -> Range Natural
x forall a. Num a => a -> a -> a
+ Range Natural
y
MulF Range Natural
x Range Natural
y -> Range Natural
x forall a. Num a => a -> a -> a
* Range Natural
y
SubF Range Natural
x Range Natural
y -> Range Natural
x forall a. Num a => a -> a -> a
- Range Natural
y
NegF Range Natural
x -> forall a. Num a => a -> a
negate Range Natural
x
AbsF Range Natural
x -> forall a. Num a => a -> a
abs Range Natural
x
SgnF Range Natural
x -> forall a. Num a => a -> a
signum Range Natural
x
CasesF [Case (Range Natural)]
xs ->
Range
{ lo :: Natural
lo = forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
minimum (forall a b. (a -> b) -> [a] -> [b]
map (forall b. Range b -> b
lo forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. Case t -> t
caseValue) [Case (Range Natural)]
xs)
, hi :: Natural
hi = forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
maximum (forall a b. (a -> b) -> [a] -> [b]
map (forall b. Range b -> b
hi forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. Case t -> t
caseValue) [Case (Range Natural)]
xs)
}
ValueF Natural
x -> Range {lo :: Natural
lo = Natural
x, hi :: Natural
hi = Natural
x}
ApF Text
_ Natural -> Natural
f Range Natural
x -> Range {lo :: Natural
lo = Natural -> Natural
f (forall b. Range b -> b
lo Range Natural
x), hi :: Natural
hi = Natural -> Natural
f (forall b. Range b -> b
hi Range Natural
x)}
TodoF forall t. EncCBOR t => Proxy t -> Size
f Proxy a
x -> forall t.
EncCBOR t =>
(Proxy t -> Size) -> Proxy t -> Range Natural
doit forall t. EncCBOR t => Proxy t -> Size
f Proxy a
x
szLazy :: EncCBOR a => (Proxy a -> Size)
szLazy :: forall t. EncCBOR t => Proxy t -> Size
szLazy = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
todo (forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
szLazy)
szGreedy :: EncCBOR a => (Proxy a -> Size)
szGreedy :: forall t. EncCBOR t => Proxy t -> Size
szGreedy = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
szGreedy
isTodo :: Size -> Bool
isTodo :: Size -> Bool
isTodo (Fix (TodoF forall t. EncCBOR t => Proxy t -> Size
_ Proxy a
_)) = Bool
True
isTodo Size
_ = Bool
False
todo ::
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) ->
Proxy a ->
Size
todo :: forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
todo forall t. EncCBOR t => Proxy t -> Size
f Proxy a
pxy = forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (forall t a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> SizeF t
TodoF forall t. EncCBOR t => Proxy t -> Size
f Proxy a
pxy)
apMono :: Text -> (Natural -> Natural) -> Size -> Size
apMono :: Text -> (Natural -> Natural) -> Size -> Size
apMono Text
n Natural -> Natural
f = \case
Fix (ValueF Natural
x) -> forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (forall t. Natural -> SizeF t
ValueF (Natural -> Natural
f Natural
x))
Fix (CasesF [Case Size]
cs) -> forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (forall t. [Case t] -> SizeF t
CasesF (forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> (Natural -> Natural) -> Size -> Size
apMono Text
n Natural -> Natural
f)) [Case Size]
cs))
Size
x -> forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (forall t. Text -> (Natural -> Natural) -> t -> SizeF t
ApF Text
n Natural -> Natural
f Size
x)
szWithCtx :: EncCBOR a => Map.Map TypeRep SizeOverride -> Proxy a -> Size
szWithCtx :: forall a. EncCBOR a => Map TypeRep SizeOverride -> Proxy a -> Size
szWithCtx Map TypeRep SizeOverride
ctx Proxy a
pxy = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall {k} (proxy :: k -> Type) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep Proxy a
pxy) Map TypeRep SizeOverride
ctx of
Maybe SizeOverride
Nothing -> Size
normal
Just SizeOverride
override -> case SizeOverride
override of
SizeConstant Size
sz -> Size
sz
SizeExpression (forall t. EncCBOR t => Proxy t -> Size) -> Size
f -> (forall t. EncCBOR t => Proxy t -> Size) -> Size
f (forall a. EncCBOR a => Map TypeRep SizeOverride -> Proxy a -> Size
szWithCtx Map TypeRep SizeOverride
ctx)
SelectCases [Text]
names -> forall t a. Recursive t => (Base t a -> a) -> t -> a
cata ([Text] -> SizeF Size -> Size
selectCase [Text]
names) Size
normal
where
normal :: Size
normal = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (forall a. EncCBOR a => Map TypeRep SizeOverride -> Proxy a -> Size
szWithCtx Map TypeRep SizeOverride
ctx) Proxy a
pxy
selectCase :: [Text] -> SizeF Size -> Size
selectCase :: [Text] -> SizeF Size -> Size
selectCase [Text]
names SizeF Size
orig = case SizeF Size
orig of
CasesF [Case Size]
cs -> [Text] -> [Case Size] -> Size -> Size
matchCase [Text]
names [Case Size]
cs (forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix SizeF Size
orig)
SizeF Size
_ -> forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix SizeF Size
orig
matchCase :: [Text] -> [Case Size] -> Size -> Size
matchCase :: [Text] -> [Case Size] -> Size -> Size
matchCase [Text]
names [Case Size]
cs Size
orig =
case forall a. (a -> Bool) -> [a] -> [a]
filter (\(Case Text
name Size
_) -> Text
name forall (t :: Type -> Type) a.
(Foldable t, Eq a) =>
a -> t a -> Bool
`elem` [Text]
names) [Case Size]
cs of
[] -> Size
orig
[Case Text
_ Size
x] -> Size
x
[Case Size]
cs' -> forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (forall t. [Case t] -> SizeF t
CasesF [Case Size]
cs')
data SizeOverride
=
SizeConstant Size
|
SizeExpression ((forall a. EncCBOR a => Proxy a -> Size) -> Size)
|
SelectCases [Text]
szSimplify :: Size -> Either Size (Range Natural)
szSimplify :: Size -> Either Size (Range Natural)
szSimplify = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata forall a b. (a -> b) -> a -> b
$ \case
TodoF forall t. EncCBOR t => Proxy t -> Size
f Proxy a
pxy -> forall a b. a -> Either a b
Left (forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
todo forall t. EncCBOR t => Proxy t -> Size
f Proxy a
pxy)
ValueF Natural
x -> forall a b. b -> Either a b
Right (Range {lo :: Natural
lo = Natural
x, hi :: Natural
hi = Natural
x})
CasesF [Case (Either Size (Range Natural))]
xs -> case forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall t. Case t -> t
caseValue [Case (Either Size (Range Natural))]
xs of
Right [Range Natural]
xs' ->
forall a b. b -> Either a b
Right (Range {lo :: Natural
lo = forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
minimum (forall a b. (a -> b) -> [a] -> [b]
map forall b. Range b -> b
lo [Range Natural]
xs'), hi :: Natural
hi = forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
maximum (forall a b. (a -> b) -> [a] -> [b]
map forall b. Range b -> b
hi [Range Natural]
xs')})
Left Size
_ -> forall a b. a -> Either a b
Left ([Case Size] -> Size
szCases forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Either Size (Range Natural) -> Size
toSize) [Case (Either Size (Range Natural))]
xs)
AddF Either Size (Range Natural)
x Either Size (Range Natural)
y -> (forall a. Num a => a -> a -> a)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
binOp forall a. Num a => a -> a -> a
(+) Either Size (Range Natural)
x Either Size (Range Natural)
y
MulF Either Size (Range Natural)
x Either Size (Range Natural)
y -> (forall a. Num a => a -> a -> a)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
binOp forall a. Num a => a -> a -> a
(*) Either Size (Range Natural)
x Either Size (Range Natural)
y
SubF Either Size (Range Natural)
x Either Size (Range Natural)
y -> (forall a. Num a => a -> a -> a)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
binOp (-) Either Size (Range Natural)
x Either Size (Range Natural)
y
NegF Either Size (Range Natural)
x -> (forall a. Num a => a -> a)
-> Either Size (Range Natural) -> Either Size (Range Natural)
unOp forall a. Num a => a -> a
negate Either Size (Range Natural)
x
AbsF Either Size (Range Natural)
x -> (forall a. Num a => a -> a)
-> Either Size (Range Natural) -> Either Size (Range Natural)
unOp forall a. Num a => a -> a
abs Either Size (Range Natural)
x
SgnF Either Size (Range Natural)
x -> (forall a. Num a => a -> a)
-> Either Size (Range Natural) -> Either Size (Range Natural)
unOp forall a. Num a => a -> a
signum Either Size (Range Natural)
x
ApF Text
_ Natural -> Natural
f (Right Range Natural
x) -> forall a b. b -> Either a b
Right (Range {lo :: Natural
lo = Natural -> Natural
f (forall b. Range b -> b
lo Range Natural
x), hi :: Natural
hi = Natural -> Natural
f (forall b. Range b -> b
hi Range Natural
x)})
ApF Text
n Natural -> Natural
f (Left Size
x) -> forall a b. a -> Either a b
Left (Text -> (Natural -> Natural) -> Size -> Size
apMono Text
n Natural -> Natural
f Size
x)
where
binOp ::
(forall a. Num a => a -> a -> a) ->
Either Size (Range Natural) ->
Either Size (Range Natural) ->
Either Size (Range Natural)
binOp :: (forall a. Num a => a -> a -> a)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
-> Either Size (Range Natural)
binOp forall a. Num a => a -> a -> a
op (Right Range Natural
x) (Right Range Natural
y) = forall a b. b -> Either a b
Right (forall a. Num a => a -> a -> a
op Range Natural
x Range Natural
y)
binOp forall a. Num a => a -> a -> a
op Either Size (Range Natural)
x Either Size (Range Natural)
y = forall a b. a -> Either a b
Left (forall a. Num a => a -> a -> a
op (Either Size (Range Natural) -> Size
toSize Either Size (Range Natural)
x) (Either Size (Range Natural) -> Size
toSize Either Size (Range Natural)
y))
unOp ::
(forall a. Num a => a -> a) ->
Either Size (Range Natural) ->
Either Size (Range Natural)
unOp :: (forall a. Num a => a -> a)
-> Either Size (Range Natural) -> Either Size (Range Natural)
unOp forall a. Num a => a -> a
f = \case
Right Range Natural
x -> forall a b. b -> Either a b
Right (forall a. Num a => a -> a
f Range Natural
x)
Left Size
x -> forall a b. a -> Either a b
Left (forall a. Num a => a -> a
f Size
x)
toSize :: Either Size (Range Natural) -> Size
toSize :: Either Size (Range Natural) -> Size
toSize = \case
Left Size
x -> Size
x
Right Range Natural
r ->
if forall b. Range b -> b
lo Range Natural
r forall a. Eq a => a -> a -> Bool
== forall b. Range b -> b
hi Range Natural
r
then forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall b. Range b -> b
lo Range Natural
r)
else
[Case Size] -> Size
szCases
[forall t. Text -> t -> Case t
Case Text
"lo" (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall b. Range b -> b
lo Range Natural
r), forall t. Text -> t -> Case t
Case Text
"hi" (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall b. Range b -> b
hi Range Natural
r)]
szForce :: Size -> Size
szForce :: Size -> Size
szForce = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata forall a b. (a -> b) -> a -> b
$ \case
AddF Size
x Size
y -> Size
x forall a. Num a => a -> a -> a
+ Size
y
MulF Size
x Size
y -> Size
x forall a. Num a => a -> a -> a
* Size
y
SubF Size
x Size
y -> Size
x forall a. Num a => a -> a -> a
- Size
y
NegF Size
x -> forall a. Num a => a -> a
negate Size
x
AbsF Size
x -> forall a. Num a => a -> a
abs Size
x
SgnF Size
x -> forall a. Num a => a -> a
signum Size
x
CasesF [Case Size]
xs -> forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix forall a b. (a -> b) -> a -> b
$ forall t. [Case t] -> SizeF t
CasesF [Case Size]
xs
ValueF Natural
x -> forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (forall t. Natural -> SizeF t
ValueF Natural
x)
ApF Text
n Natural -> Natural
f Size
x -> Text -> (Natural -> Natural) -> Size -> Size
apMono Text
n Natural -> Natural
f Size
x
TodoF forall t. EncCBOR t => Proxy t -> Size
f Proxy a
x -> forall t. EncCBOR t => Proxy t -> Size
f Proxy a
x
szBounds :: EncCBOR a => a -> Either Size (Range Natural)
szBounds :: forall a. EncCBOR a => a -> Either Size (Range Natural)
szBounds = Size -> Either Size (Range Natural)
szSimplify forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall t. EncCBOR t => Proxy t -> Size
szGreedy forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall (f :: Type -> Type) a. Applicative f => a -> f a
pure
withWordSize :: (Integral s, Integral a) => s -> a
withWordSize :: forall s a. (Integral s, Integral a) => s -> a
withWordSize s
x =
let s :: Integer
s = forall a b. (Integral a, Num b) => a -> b
fromIntegral s
x :: Integer
in if
| Integer
s forall a. Ord a => a -> a -> Bool
<= Integer
0x17 Bool -> Bool -> Bool
&& Integer
s forall a. Ord a => a -> a -> Bool
>= (-Integer
0x18) -> a
1
| Integer
s forall a. Ord a => a -> a -> Bool
<= Integer
0xff Bool -> Bool -> Bool
&& Integer
s forall a. Ord a => a -> a -> Bool
>= (-Integer
0x100) -> a
2
| Integer
s forall a. Ord a => a -> a -> Bool
<= Integer
0xffff Bool -> Bool -> Bool
&& Integer
s forall a. Ord a => a -> a -> Bool
>= (-Integer
0x10000) -> a
3
| Integer
s forall a. Ord a => a -> a -> Bool
<= Integer
0xffffffff Bool -> Bool -> Bool
&& Integer
s forall a. Ord a => a -> a -> Bool
>= (-Integer
0x100000000) -> a
5
| Bool
otherwise -> a
9
instance EncCBOR () where
encCBOR :: () -> Encoding
encCBOR = forall a b. a -> b -> a
const Encoding
encodeNull
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy () -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ Proxy ()
_ = Size
1
instance EncCBOR Bool where
encCBOR :: Bool -> Encoding
encCBOR = Bool -> Encoding
encodeBool
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Bool -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ Proxy Bool
_ = Size
1
instance EncCBOR Integer where
encCBOR :: Integer -> Encoding
encCBOR = Integer -> Encoding
encodeInteger
encodedSizeRange :: forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange :: forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange Proxy a
_ =
[Case Size] -> Size
szCases
[ Text -> a -> Case Size
mkCase Text
"minBound" a
0
, Text -> a -> Case Size
mkCase Text
"maxBound" forall a. Bounded a => a
maxBound
]
where
mkCase :: Text -> a -> Case Size
mkCase :: Text -> a -> Case Size
mkCase Text
n = forall t. Text -> t -> Case t
Case Text
n forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Num a => Integer -> a
fromInteger forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall s a. (Integral s, Integral a) => s -> a
withWordSize
instance EncCBOR Word where
encCBOR :: Word -> Encoding
encCBOR = Word -> Encoding
encodeWord
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Word8 where
encCBOR :: Word8 -> Encoding
encCBOR = Word8 -> Encoding
encodeWord8
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word8 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Word16 where
encCBOR :: Word16 -> Encoding
encCBOR = Word16 -> Encoding
encodeWord16
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word16 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Word32 where
encCBOR :: Word32 -> Encoding
encCBOR = Word32 -> Encoding
encodeWord32
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word32 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Word64 where
encCBOR :: Word64 -> Encoding
encCBOR = Word64 -> Encoding
encodeWord64
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word64 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Int where
encCBOR :: Int -> Encoding
encCBOR = Int -> Encoding
encodeInt
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Int -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Int8 where
encCBOR :: Int8 -> Encoding
encCBOR = Int8 -> Encoding
encodeInt8
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Int8 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Int16 where
encCBOR :: Int16 -> Encoding
encCBOR = Int16 -> Encoding
encodeInt16
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Int16 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Int32 where
encCBOR :: Int32 -> Encoding
encCBOR = Int32 -> Encoding
encodeInt32
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Int32 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Int64 where
encCBOR :: Int64 -> Encoding
encCBOR = Int64 -> Encoding
encodeInt64
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Int64 -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall a. (Integral a, Bounded a) => Proxy a -> Size
encodedSizeRange
instance EncCBOR Float where
encCBOR :: Float -> Encoding
encCBOR = Float -> Encoding
encodeFloat
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Float -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ Proxy Float
_ = Size
1 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Storable a => a -> Int
sizeOf (Float
0 :: Float))
instance EncCBOR Double where
encCBOR :: Double -> Encoding
encCBOR = Double -> Encoding
encodeDouble
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Double -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ Proxy Double
_ = Size
1 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Storable a => a -> Int
sizeOf (Float
0 :: Float))
instance EncCBOR a => EncCBOR (Ratio a) where
encCBOR :: Ratio a -> Encoding
encCBOR = forall t. (t -> Encoding) -> Ratio t -> Encoding
encodeRatio forall a. EncCBOR a => a -> Encoding
encCBOR
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Ratio a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Ratio a)
_ = Size
1 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
deriving newtype instance Typeable p => EncCBOR (Fixed p)
instance EncCBOR Natural where
encCBOR :: Natural -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> Integer
toInteger
instance EncCBOR Void where
encCBOR :: Void -> Encoding
encCBOR = forall a. Void -> a
absurd
instance EncCBOR IPv4 where
encCBOR :: IPv4 -> Encoding
encCBOR = IPv4 -> Encoding
encodeIPv4
instance EncCBOR IPv6 where
encCBOR :: IPv6 -> Encoding
encCBOR = IPv6 -> Encoding
encodeIPv6
instance EncCBOR Term where
encCBOR :: Term -> Encoding
encCBOR = Term -> Encoding
encodeTerm
instance EncCBOR Encoding where
encCBOR :: Encoding -> Encoding
encCBOR = forall a. a -> a
id
instance EncCBOR C.Encoding where
encCBOR :: Encoding -> Encoding
encCBOR = Encoding -> Encoding
fromPlainEncoding
instance EncCBOR (Tokens -> Tokens) where
encCBOR :: (Tokens -> Tokens) -> Encoding
encCBOR Tokens -> Tokens
t = Encoding -> Encoding
fromPlainEncoding ((Tokens -> Tokens) -> Encoding
C.Encoding Tokens -> Tokens
t)
instance (Typeable s, EncCBOR a) => EncCBOR (Tagged s a) where
encCBOR :: Tagged s a -> Encoding
encCBOR (Tagged a
a) = forall a. EncCBOR a => a -> Encoding
encCBOR a
a
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Tagged s a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Tagged s a)
_ = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
instance (EncCBOR a, EncCBOR b) => EncCBOR (a, b) where
encCBOR :: (a, b) -> Encoding
encCBOR (a
a, b
b) = Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
a forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR b
b
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (a, b) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (a, b)
_ = Size
1 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @b)
instance (EncCBOR a, EncCBOR b, EncCBOR c) => EncCBOR (a, b, c) where
encCBOR :: (a, b, c) -> Encoding
encCBOR (a
a, b
b, c
c) = Word -> Encoding
encodeListLen Word
3 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
a forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR b
b forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR c
c
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (a, b, c) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (a, b, c)
_ =
Size
1 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @b) forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @c)
instance (EncCBOR a, EncCBOR b, EncCBOR c, EncCBOR d) => EncCBOR (a, b, c, d) where
encCBOR :: (a, b, c, d) -> Encoding
encCBOR (a
a, b
b, c
c, d
d) =
Word -> Encoding
encodeListLen Word
4 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
a forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR b
b forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR c
c forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR d
d
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (a, b, c, d) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (a, b, c, d)
_ =
Size
1 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a) forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @b) forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @c) forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @d)
instance
(EncCBOR a, EncCBOR b, EncCBOR c, EncCBOR d, EncCBOR e) =>
EncCBOR (a, b, c, d, e)
where
encCBOR :: (a, b, c, d, e) -> Encoding
encCBOR (a
a, b
b, c
c, d
d, e
e) =
Word -> Encoding
encodeListLen Word
5
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
a
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR b
b
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR c
c
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR d
d
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR e
e
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (a, b, c, d, e) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (a, b, c, d, e)
_ =
Size
1
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @b)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @c)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @d)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @e)
instance
(EncCBOR a, EncCBOR b, EncCBOR c, EncCBOR d, EncCBOR e, EncCBOR f) =>
EncCBOR (a, b, c, d, e, f)
where
encCBOR :: (a, b, c, d, e, f) -> Encoding
encCBOR (a
a, b
b, c
c, d
d, e
e, f
f) =
Word -> Encoding
encodeListLen Word
6
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
a
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR b
b
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR c
c
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR d
d
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR e
e
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR f
f
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (a, b, c, d, e, f) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (a, b, c, d, e, f)
_ =
Size
1
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @b)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @c)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @d)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @e)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @f)
instance
(EncCBOR a, EncCBOR b, EncCBOR c, EncCBOR d, EncCBOR e, EncCBOR f, EncCBOR g) =>
EncCBOR (a, b, c, d, e, f, g)
where
encCBOR :: (a, b, c, d, e, f, g) -> Encoding
encCBOR (a
a, b
b, c
c, d
d, e
e, f
f, g
g) =
Word -> Encoding
encodeListLen Word
7
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
a
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR b
b
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR c
c
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR d
d
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR e
e
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR f
f
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR g
g
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (a, b, c, d, e, f, g) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (a, b, c, d, e, f, g)
_ =
Size
1
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @b)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @c)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @d)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @e)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @f)
forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @g)
instance EncCBOR BS.ByteString where
encCBOR :: ByteString -> Encoding
encCBOR = ByteString -> Encoding
encodeBytes
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy ByteString -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy ByteString
_ =
let len :: Size
len = forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf BS.ByteString))
in Text -> (Natural -> Natural) -> Size -> Size
apMono Text
"withWordSize@Int" (forall s a. (Integral s, Integral a) => s -> a
withWordSize @Int forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Size
len forall a. Num a => a -> a -> a
+ Size
len
instance EncCBOR Text.Text where
encCBOR :: Text -> Encoding
encCBOR = Text -> Encoding
encodeString
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Text -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy Text
_ =
let bsLength :: Size
bsLength =
forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf Text))
forall a. Num a => a -> a -> a
* [Case Size] -> Size
szCases [forall t. Text -> t -> Case t
Case Text
"minChar" Size
1, forall t. Text -> t -> Case t
Case Text
"maxChar" Size
4]
in Size
bsLength forall a. Num a => a -> a -> a
+ Text -> (Natural -> Natural) -> Size -> Size
apMono Text
"withWordSize" forall s a. (Integral s, Integral a) => s -> a
withWordSize Size
bsLength
instance EncCBOR ByteArray where
encCBOR :: ByteArray -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteArray -> ByteArray
unBA
{-# INLINE encCBOR #-}
instance EncCBOR Prim.ByteArray where
encCBOR :: ByteArray -> Encoding
encCBOR = SlicedByteArray -> Encoding
encodeByteArray forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteArray -> SlicedByteArray
fromByteArray
{-# INLINE encCBOR #-}
instance EncCBOR SlicedByteArray where
encCBOR :: SlicedByteArray -> Encoding
encCBOR = SlicedByteArray -> Encoding
encodeByteArray
{-# INLINE encCBOR #-}
instance EncCBOR ShortByteString where
encCBOR :: ShortByteString -> Encoding
encCBOR sbs :: ShortByteString
sbs@(SBS ByteArray#
ba) =
SlicedByteArray -> Encoding
encodeByteArray forall a b. (a -> b) -> a -> b
$ ByteArray -> Int -> Int -> SlicedByteArray
SBA (ByteArray# -> ByteArray
Prim.ByteArray ByteArray#
ba) Int
0 (ShortByteString -> Int
SBS.length ShortByteString
sbs)
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy ShortByteString -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy ShortByteString
_ =
let len :: Size
len = forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf ShortByteString))
in Text -> (Natural -> Natural) -> Size -> Size
apMono Text
"withWordSize@Int" (forall s a. (Integral s, Integral a) => s -> a
withWordSize @Int forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Size
len forall a. Num a => a -> a -> a
+ Size
len
instance EncCBOR BS.Lazy.ByteString where
encCBOR :: ByteString -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
BS.Lazy.toStrict
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy ByteString -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy ByteString
_ =
let len :: Size
len = forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf BS.Lazy.ByteString))
in Text -> (Natural -> Natural) -> Size -> Size
apMono Text
"withWordSize@Int" (forall s a. (Integral s, Integral a) => s -> a
withWordSize @Int forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) Size
len forall a. Num a => a -> a -> a
+ Size
len
instance EncCBOR a => EncCBOR [a] where
encCBOR :: [a] -> Encoding
encCBOR = forall a. (a -> Encoding) -> [a] -> Encoding
encodeList forall a. EncCBOR a => a -> Encoding
encCBOR
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy [a]
_ = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
encodedListSizeExpr forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @[a])
instance (EncCBOR a, EncCBOR b) => EncCBOR (Either a b) where
encCBOR :: Either a b -> Encoding
encCBOR (Left a
x) = Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> Word -> Encoding
encodeWord Word
0 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR a
x
encCBOR (Right b
x) = Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> Word -> Encoding
encodeWord Word
1 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR b
x
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Either a b) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Either a b)
_ =
[Case Size] -> Size
szCases
[forall t. Text -> t -> Case t
Case Text
"Left" (Size
2 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)), forall t. Text -> t -> Case t
Case Text
"Right" (Size
2 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @b))]
instance EncCBOR a => EncCBOR (NonEmpty a) where
encCBOR :: NonEmpty a -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall (t :: Type -> Type) a. Foldable t => t a -> [a]
toList
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (NonEmpty a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (NonEmpty a)
_ = forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @[a])
instance EncCBOR a => EncCBOR (Maybe a) where
encCBOR :: Maybe a -> Encoding
encCBOR = forall a. (a -> Encoding) -> Maybe a -> Encoding
encodeMaybe forall a. EncCBOR a => a -> Encoding
encCBOR
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Maybe a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Maybe a)
_ =
[Case Size] -> Size
szCases [forall t. Text -> t -> Case t
Case Text
"Nothing" Size
1, forall t. Text -> t -> Case t
Case Text
"Just" (Size
1 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a))]
instance EncCBOR a => EncCBOR (SMaybe.StrictMaybe a) where
encCBOR :: StrictMaybe a -> Encoding
encCBOR = forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (StrictMaybe a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (StrictMaybe a)
_ =
[Case Size] -> Size
szCases [forall t. Text -> t -> Case t
Case Text
"SNothing" Size
1, forall t. Text -> t -> Case t
Case Text
"SJust" (Size
1 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a))]
instance (Ord k, EncCBOR k, EncCBOR v) => EncCBOR (Map.Map k v) where
encCBOR :: Map k v -> Encoding
encCBOR = forall k v.
(k -> Encoding) -> (v -> Encoding) -> Map k v -> Encoding
encodeMap forall a. EncCBOR a => a -> Encoding
encCBOR forall a. EncCBOR a => a -> Encoding
encCBOR
instance (Ord a, EncCBOR a) => EncCBOR (Set.Set a) where
encCBOR :: Set a -> Encoding
encCBOR = forall a. (a -> Encoding) -> Set a -> Encoding
encodeSet forall a. EncCBOR a => a -> Encoding
encCBOR
instance EncCBOR a => EncCBOR (Seq.Seq a) where
encCBOR :: Seq a -> Encoding
encCBOR = forall a. (a -> Encoding) -> Seq a -> Encoding
encodeSeq forall a. EncCBOR a => a -> Encoding
encCBOR
instance EncCBOR a => EncCBOR (SSeq.StrictSeq a) where
encCBOR :: StrictSeq a -> Encoding
encCBOR = forall a. (a -> Encoding) -> StrictSeq a -> Encoding
encodeStrictSeq forall a. EncCBOR a => a -> Encoding
encCBOR
instance
(Ord k, EncCBOR k, EncCBOR v, VMap.Vector kv k, VMap.Vector vv v, Typeable kv, Typeable vv) =>
EncCBOR (VMap.VMap kv vv k v)
where
encCBOR :: VMap kv vv k v -> Encoding
encCBOR = forall (kv :: Type -> Type) k (vv :: Type -> Type) v.
(Vector kv k, Vector vv v) =>
(k -> Encoding) -> (v -> Encoding) -> VMap kv vv k v -> Encoding
encodeVMap forall a. EncCBOR a => a -> Encoding
encCBOR forall a. EncCBOR a => a -> Encoding
encCBOR
instance EncCBOR a => EncCBOR (V.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector forall a. EncCBOR a => a -> Encoding
encCBOR
{-# INLINE encCBOR #-}
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Vector a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Vector a)
_ =
Size
2 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf (V.Vector a))) forall a. Num a => a -> a -> a
* forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
instance (EncCBOR a, VP.Prim a) => EncCBOR (VP.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector forall a. EncCBOR a => a -> Encoding
encCBOR
{-# INLINE encCBOR #-}
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Vector a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Vector a)
_ =
Size
2 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf (VP.Vector a))) forall a. Num a => a -> a -> a
* forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
instance (EncCBOR a, VS.Storable a) => EncCBOR (VS.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector forall a. EncCBOR a => a -> Encoding
encCBOR
{-# INLINE encCBOR #-}
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Vector a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Vector a)
_ =
Size
2 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf (VS.Vector a))) forall a. Num a => a -> a -> a
* forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
instance (EncCBOR a, VU.Unbox a) => EncCBOR (VU.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector forall a. EncCBOR a => a -> Encoding
encCBOR
{-# INLINE encCBOR #-}
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Vector a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Vector a)
_ =
Size
2 forall a. Num a => a -> a -> a
+ forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @(LengthOf (VU.Vector a))) forall a. Num a => a -> a -> a
* forall t. EncCBOR t => Proxy t -> Size
size (forall {k} (t :: k). Proxy t
Proxy @a)
instance EncCBOR UTCTime where
encCBOR :: UTCTime -> Encoding
encCBOR = UTCTime -> Encoding
encodeUTCTime
encodedVerKeyDSIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr Proxy (VerKeyDSIGN v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeVerKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeVerKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
encodedSignKeyDSIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDSIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDSIGNSizeExpr Proxy (SignKeyDSIGN v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSignKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSignKeyDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
encodedSigDSIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr :: forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr Proxy (SigDSIGN v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSigDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSigDSIGN (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
encodedSignedDSIGNSizeExpr :: forall v a. DSIGNAlgorithm v => Proxy (SignedDSIGN v a) -> Size
encodedSignedDSIGNSizeExpr :: forall v a. DSIGNAlgorithm v => Proxy (SignedDSIGN v a) -> Size
encodedSignedDSIGNSizeExpr Proxy (SignedDSIGN v a)
_proxy = forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr (forall {k} (t :: k). Proxy t
Proxy :: Proxy (SigDSIGN v))
instance DSIGNAlgorithm v => EncCBOR (VerKeyDSIGN v) where
encCBOR :: VerKeyDSIGN v -> Encoding
encCBOR = forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> Encoding
encodeVerKeyDSIGN
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VerKeyDSIGN v) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr
instance DSIGNAlgorithm v => EncCBOR (SignKeyDSIGN v) where
encCBOR :: SignKeyDSIGN v -> Encoding
encCBOR = forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> Encoding
encodeSignKeyDSIGN
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (SignKeyDSIGN v) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDSIGNSizeExpr
instance DSIGNAlgorithm v => EncCBOR (SigDSIGN v) where
encCBOR :: SigDSIGN v -> Encoding
encCBOR = forall v. DSIGNAlgorithm v => SigDSIGN v -> Encoding
encodeSigDSIGN
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (SigDSIGN v) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr
instance (DSIGNAlgorithm v, Typeable a) => EncCBOR (SignedDSIGN v a) where
encCBOR :: SignedDSIGN v a -> Encoding
encCBOR = forall v a. DSIGNAlgorithm v => SignedDSIGN v a -> Encoding
encodeSignedDSIGN
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (SignedDSIGN v a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ = forall v a. DSIGNAlgorithm v => Proxy (SignedDSIGN v a) -> Size
encodedSignedDSIGNSizeExpr
instance (HashAlgorithm h, Typeable a) => EncCBOR (Hash h a) where
encCBOR :: Hash h a -> Encoding
encCBOR (UnsafeHash ShortByteString
h) = forall a. EncCBOR a => a -> Encoding
encCBOR ShortByteString
h
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Hash h a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size Proxy (Hash h a)
proxy =
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (forall a b. a -> b -> a
const Size
hashSize) (forall h a. Hash h a -> ByteString
hashToBytes forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Hash h a)
proxy)
where
hashSize :: Size
hashSize :: Size
hashSize = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall h (proxy :: Type -> Type).
HashAlgorithm h =>
proxy h -> Word
sizeHash (forall {k} (t :: k). Proxy t
Proxy :: Proxy h))
encodedVerKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (VerKeyKES v) -> Size
encodedVerKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (VerKeyKES v) -> Size
encodedVerKeyKESSizeExpr Proxy (VerKeyKES v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeVerKeyKES (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeVerKeyKES (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
encodedSignKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SignKeyKES v) -> Size
encodedSignKeyKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SignKeyKES v) -> Size
encodedSignKeyKESSizeExpr Proxy (SignKeyKES v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSignKeyKES (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSignKeyKES (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
encodedSigKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SigKES v) -> Size
encodedSigKESSizeExpr :: forall v. KESAlgorithm v => Proxy (SigKES v) -> Size
encodedSigKESSizeExpr Proxy (SigKES v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSigKES (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSigKES (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
instance KESAlgorithm k => EncCBOR (VerKeyKES k) where
encCBOR :: VerKeyKES k -> Encoding
encCBOR = forall k. KESAlgorithm k => VerKeyKES k -> Encoding
encodeVerKeyKES
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VerKeyKES k) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. KESAlgorithm v => Proxy (VerKeyKES v) -> Size
encodedVerKeyKESSizeExpr
instance KESAlgorithm k => EncCBOR (SigKES k) where
encCBOR :: SigKES k -> Encoding
encCBOR = forall k. KESAlgorithm k => SigKES k -> Encoding
encodeSigKES
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (SigKES k) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. KESAlgorithm v => Proxy (SigKES v) -> Size
encodedSigKESSizeExpr
encodedVerKeyVRFSizeExpr :: forall v. VRFAlgorithm v => Proxy (VerKeyVRF v) -> Size
encodedVerKeyVRFSizeExpr :: forall v. VRFAlgorithm v => Proxy (VerKeyVRF v) -> Size
encodedVerKeyVRFSizeExpr Proxy (VerKeyVRF v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeVerKeyVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeVerKeyVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
encodedSignKeyVRFSizeExpr :: forall v. VRFAlgorithm v => Proxy (SignKeyVRF v) -> Size
encodedSignKeyVRFSizeExpr :: forall v. VRFAlgorithm v => Proxy (SignKeyVRF v) -> Size
encodedSignKeyVRFSizeExpr Proxy (SignKeyVRF v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeSignKeyVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeSignKeyVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
encodedCertVRFSizeExpr :: forall v. VRFAlgorithm v => Proxy (CertVRF v) -> Size
encodedCertVRFSizeExpr :: forall v. VRFAlgorithm v => Proxy (CertVRF v) -> Size
encodedCertVRFSizeExpr Proxy (CertVRF v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeCertVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeCertVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
instance EncCBOR (VerKeyVRF SimpleVRF) where
encCBOR :: VerKeyVRF SimpleVRF -> Encoding
encCBOR = forall v. VRFAlgorithm v => VerKeyVRF v -> Encoding
encodeVerKeyVRF
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VerKeyVRF SimpleVRF) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. VRFAlgorithm v => Proxy (VerKeyVRF v) -> Size
encodedVerKeyVRFSizeExpr
instance EncCBOR (SignKeyVRF SimpleVRF) where
encCBOR :: SignKeyVRF SimpleVRF -> Encoding
encCBOR = forall v. VRFAlgorithm v => SignKeyVRF v -> Encoding
encodeSignKeyVRF
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (SignKeyVRF SimpleVRF) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. VRFAlgorithm v => Proxy (SignKeyVRF v) -> Size
encodedSignKeyVRFSizeExpr
instance EncCBOR (CertVRF SimpleVRF) where
encCBOR :: CertVRF SimpleVRF -> Encoding
encCBOR = forall v. VRFAlgorithm v => CertVRF v -> Encoding
encodeCertVRF
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (CertVRF SimpleVRF) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. VRFAlgorithm v => Proxy (CertVRF v) -> Size
encodedCertVRFSizeExpr
instance EncCBOR (VerKeyVRF MockVRF) where
encCBOR :: VerKeyVRF MockVRF -> Encoding
encCBOR = forall v. VRFAlgorithm v => VerKeyVRF v -> Encoding
encodeVerKeyVRF
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VerKeyVRF MockVRF) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. VRFAlgorithm v => Proxy (VerKeyVRF v) -> Size
encodedVerKeyVRFSizeExpr
instance EncCBOR (SignKeyVRF MockVRF) where
encCBOR :: SignKeyVRF MockVRF -> Encoding
encCBOR = forall v. VRFAlgorithm v => SignKeyVRF v -> Encoding
encodeSignKeyVRF
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (SignKeyVRF MockVRF) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. VRFAlgorithm v => Proxy (SignKeyVRF v) -> Size
encodedSignKeyVRFSizeExpr
instance EncCBOR (CertVRF MockVRF) where
encCBOR :: CertVRF MockVRF -> Encoding
encCBOR = forall v. VRFAlgorithm v => CertVRF v -> Encoding
encodeCertVRF
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (CertVRF MockVRF) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size = forall v. VRFAlgorithm v => Proxy (CertVRF v) -> Size
encodedCertVRFSizeExpr
deriving instance Typeable v => EncCBOR (OutputVRF v)
instance (VRFAlgorithm v, Typeable a) => EncCBOR (CertifiedVRF v a) where
encCBOR :: CertifiedVRF v a -> Encoding
encCBOR CertifiedVRF v a
cvrf =
Word -> Encoding
encodeListLen Word
2
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR (forall v a. CertifiedVRF v a -> OutputVRF v
certifiedOutput CertifiedVRF v a
cvrf)
forall a. Semigroup a => a -> a -> a
<> forall v. VRFAlgorithm v => CertVRF v -> Encoding
encodeCertVRF (forall v a. CertifiedVRF v a -> CertVRF v
certifiedProof CertifiedVRF v a
cvrf)
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (CertifiedVRF v a) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_size Proxy (CertifiedVRF v a)
proxy =
Size
1
forall a. Num a => a -> a -> a
+ Proxy (OutputVRF v) -> Size
certifiedOutputSize (forall v a. CertifiedVRF v a -> OutputVRF v
certifiedOutput forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (CertifiedVRF v a)
proxy)
forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeCertVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
where
certifiedOutputSize :: Proxy (OutputVRF v) -> Size
certifiedOutputSize :: Proxy (OutputVRF v) -> Size
certifiedOutputSize Proxy (OutputVRF v)
_proxy =
forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
sizeOutputVRF (forall {k} (t :: k). Proxy t
Proxy :: Proxy v)
instance EncCBOR Praos.Proof where
encCBOR :: Proof -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Proof -> ByteString
Praos.proofBytes
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Proof -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ Proxy Proof
_ =
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (\Proxy t
_ -> forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Praos.certSizeVRF) (forall {k} (t :: k). Proxy t
Proxy :: Proxy BS.ByteString)
instance EncCBOR Praos.SignKey where
encCBOR :: SignKey -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SignKey -> ByteString
Praos.skBytes
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SignKey -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ Proxy SignKey
_ =
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (\Proxy t
_ -> forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Praos.signKeySizeVRF) (forall {k} (t :: k). Proxy t
Proxy :: Proxy BS.ByteString)
instance EncCBOR Praos.VerKey where
encCBOR :: VerKey -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. VerKey -> ByteString
Praos.vkBytes
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy VerKey -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
_ Proxy VerKey
_ =
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (\Proxy t
_ -> forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Praos.verKeySizeVRF) (forall {k} (t :: k). Proxy t
Proxy :: Proxy BS.ByteString)
deriving instance EncCBOR (VerKeyVRF Praos.PraosVRF)
deriving instance EncCBOR (SignKeyVRF Praos.PraosVRF)
deriving instance EncCBOR (CertVRF Praos.PraosVRF)
instance EncCBOR SlotNo where
encCBOR :: SlotNo -> Encoding
encCBOR = Encoding -> Encoding
fromPlainEncoding forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Serialise a => a -> Encoding
Serialise.encode
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SlotNo -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap SlotNo -> Word64
unSlotNo
instance (Serialise.Serialise t, Typeable t) => EncCBOR (WithOrigin t) where
encCBOR :: WithOrigin t -> Encoding
encCBOR = Encoding -> Encoding
fromPlainEncoding forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Serialise a => a -> Encoding
Serialise.encode
deriving instance EncCBOR EpochNo
deriving instance EncCBOR EpochSize
deriving instance EncCBOR SystemStart
instance EncCBOR BlockNo where
encCBOR :: BlockNo -> Encoding
encCBOR = Encoding -> Encoding
fromPlainEncoding forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Serialise a => a -> Encoding
Serialise.encode
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy BlockNo -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size = forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap BlockNo -> Word64
unBlockNo
deriving instance EncCBOR EpochInterval
instance EncCBOR PV1.Data where
encCBOR :: Data -> Encoding
encCBOR = Encoding -> Encoding
fromPlainEncoding forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Serialise a => a -> Encoding
Serialise.encode
instance EncCBOR PV1.ScriptContext where
encCBOR :: ScriptContext -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. ToData a => a -> Data
PV3.toData
instance EncCBOR PV2.ScriptContext where
encCBOR :: ScriptContext -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. ToData a => a -> Data
PV3.toData
instance EncCBOR PV3.ScriptContext where
encCBOR :: ScriptContext -> Encoding
encCBOR = forall a. EncCBOR a => a -> Encoding
encCBOR forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. ToData a => a -> Data
PV3.toData