{-# 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 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
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 (Encoding -> Encoding) -> (a -> Encoding) -> a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Encoding
forall a. ToCBOR a => a -> Encoding
Plain.toCBOR
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr = (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
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 t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
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 = [Char] -> LengthOf xs -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy (LengthOf [a]) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(LengthOf [a])) Size -> Size -> Size
forall a. Num a => a -> a -> a
* Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 (ByteString -> Encoding)
-> (PreEncoded -> ByteString) -> PreEncoded -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
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 = Proxy Word64 -> Size
forall t. EncCBOR t => Proxy t -> Size
f (Version -> Word64
getVersion64 (Version -> Word64) -> Proxy Version -> Proxy Word64
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 (Encoding -> Encoding) -> (a -> Encoding) -> a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Encoding
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 -> b -> b -> SizeF b
forall t. t -> t -> SizeF t
AddF (a -> b
f a
x) (a -> b
f a
y)
MulF a
x a
y -> b -> b -> SizeF b
forall t. t -> t -> SizeF t
MulF (a -> b
f a
x) (a -> b
f a
y)
SubF a
x a
y -> b -> b -> SizeF b
forall t. t -> t -> SizeF t
SubF (a -> b
f a
x) (a -> b
f a
y)
AbsF a
x -> b -> SizeF b
forall t. t -> SizeF t
AbsF (a -> b
f a
x)
NegF a
x -> b -> SizeF b
forall t. t -> SizeF t
NegF (a -> b
f a
x)
SgnF a
x -> b -> SizeF b
forall t. t -> SizeF t
SgnF (a -> b
f a
x)
CasesF [Case a]
xs -> [Case b] -> SizeF b
forall t. [Case t] -> SizeF t
CasesF ((Case a -> Case b) -> [Case a] -> [Case b]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> Case a -> Case b
forall a b. (a -> b) -> Case a -> Case b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) [Case a]
xs)
ValueF Natural
x -> Natural -> SizeF b
forall t. Natural -> SizeF t
ValueF Natural
x
ApF Text
n Natural -> Natural
g a
x -> Text -> (Natural -> Natural) -> b -> SizeF b
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. EncCBOR t => Proxy t -> Size) -> Proxy a -> SizeF b
forall t a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> SizeF t
TodoF Proxy x -> Size
forall t. EncCBOR t => Proxy t -> Size
g Proxy a
x
instance Num (Fix SizeF) where
+ :: Size -> Size -> Size
(+) = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size)
-> (Size -> Size -> SizeF Size) -> Size -> Size -> Size
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: Size -> Size -> SizeF Size
forall t. t -> t -> SizeF t
AddF
* :: Size -> Size -> Size
(*) = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size)
-> (Size -> Size -> SizeF Size) -> Size -> Size -> Size
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: Size -> Size -> SizeF Size
forall t. t -> t -> SizeF t
MulF
(-) = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size)
-> (Size -> Size -> SizeF Size) -> Size -> Size -> Size
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.: Size -> Size -> SizeF Size
forall t. t -> t -> SizeF t
SubF
negate :: Size -> Size
negate = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size) -> (Size -> SizeF Size) -> Size -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Size -> SizeF Size
forall t. t -> SizeF t
NegF
abs :: Size -> Size
abs = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size) -> (Size -> SizeF Size) -> Size -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Size -> SizeF Size
forall t. t -> SizeF t
AbsF
signum :: Size -> Size
signum = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size) -> (Size -> SizeF Size) -> Size -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Size -> SizeF Size
forall t. t -> SizeF t
SgnF
fromInteger :: Integer -> Size
fromInteger = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size) -> (Integer -> SizeF Size) -> Integer -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Natural -> SizeF Size
forall t. Natural -> SizeF t
ValueF (Natural -> SizeF Size)
-> (Integer -> Natural) -> Integer -> SizeF Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> Natural
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 = Format Builder (a -> Text -> b -> Builder)
-> a -> Text -> b -> Builder
forall a. Format Builder a -> a
bprint (Format (a -> Text -> b -> Builder) (a -> Text -> b -> Builder)
"(" Format (a -> Text -> b -> Builder) (a -> Text -> b -> Builder)
-> Format Builder (a -> Text -> b -> Builder)
-> Format Builder (a -> Text -> b -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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) (a -> Text -> b -> Builder)
forall a r. Buildable a => Format r (a -> r)
build Format (Text -> b -> Builder) (a -> Text -> b -> Builder)
-> Format Builder (Text -> b -> Builder)
-> Format Builder (a -> Text -> b -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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)
" " Format (Text -> b -> Builder) (Text -> b -> Builder)
-> Format Builder (Text -> b -> Builder)
-> Format Builder (Text -> b -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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) (Text -> b -> Builder)
forall r. Format r (Text -> r)
stext Format (b -> Builder) (Text -> b -> Builder)
-> Format Builder (b -> Builder)
-> Format Builder (Text -> b -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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)
" " Format (b -> Builder) (b -> Builder)
-> Format Builder (b -> Builder) -> Format Builder (b -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (b -> Builder)
forall a r. Buildable a => Format r (a -> r)
build Format Builder (b -> Builder)
-> Format Builder Builder -> Format Builder (b -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 -> t -> Text -> t -> Builder
forall a b. (Buildable a, Buildable b) => a -> Text -> b -> Builder
showp2 t
x Text
"+" t
y
MulF t
x t
y -> t -> Text -> t -> Builder
forall a b. (Buildable a, Buildable b) => a -> Text -> b -> Builder
showp2 t
x Text
"*" t
y
SubF t
x t
y -> t -> Text -> t -> Builder
forall a b. (Buildable a, Buildable b) => a -> Text -> b -> Builder
showp2 t
x Text
"-" t
y
NegF t
x -> Format Builder (t -> Builder) -> t -> Builder
forall a. Format Builder a -> a
bprint (Format (t -> Builder) (t -> Builder)
"-" Format (t -> Builder) (t -> Builder)
-> Format Builder (t -> Builder) -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (t -> Builder)
forall a r. Buildable a => Format r (a -> r)
build) t
x
AbsF t
x -> Format Builder (t -> Builder) -> t -> Builder
forall a. Format Builder a -> a
bprint (Format (t -> Builder) (t -> Builder)
"|" Format (t -> Builder) (t -> Builder)
-> Format Builder (t -> Builder) -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (t -> Builder)
forall a r. Buildable a => Format r (a -> r)
build Format Builder (t -> Builder)
-> Format Builder Builder -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 -> Format Builder (t -> Builder) -> t -> Builder
forall a. Format Builder a -> a
bprint (Format (t -> Builder) (t -> Builder)
"sgn(" Format (t -> Builder) (t -> Builder)
-> Format Builder (t -> Builder) -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (t -> Builder)
forall a r. Buildable a => Format r (a -> r)
build Format Builder (t -> Builder)
-> Format Builder Builder -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 ->
Format Builder (Builder -> Builder) -> Builder -> Builder
forall a. Format Builder a -> a
bprint (Format (Builder -> Builder) (Builder -> Builder)
"{ " Format (Builder -> Builder) (Builder -> Builder)
-> Format Builder (Builder -> Builder)
-> Format Builder (Builder -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 -> Builder)
forall a r. Buildable a => Format r (a -> r)
build Format Builder (Builder -> Builder)
-> Format Builder Builder -> Format Builder (Builder -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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
"}") (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ (Case t -> Builder) -> [Case t] -> Builder
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: Type -> Type) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Format Builder (Case t -> Builder) -> Case t -> Builder
forall a. Format Builder a -> a
bprint (Format Builder (Case t -> Builder)
forall a r. Buildable a => Format r (a -> r)
build Format Builder (Case t -> Builder)
-> Format Builder Builder -> Format Builder (Case t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 -> Format Builder (Integer -> Builder) -> Integer -> Builder
forall a. Format Builder a -> a
bprint Format Builder (Integer -> Builder)
forall a r. Show a => Format r (a -> r)
shown (Natural -> Integer
forall a. Integral a => a -> Integer
toInteger Natural
x)
ApF Text
n Natural -> Natural
_ t
x -> Format Builder (Text -> t -> Builder) -> Text -> t -> Builder
forall a. Format Builder a -> a
bprint (Format (t -> Builder) (Text -> t -> Builder)
forall r. Format r (Text -> r)
stext Format (t -> Builder) (Text -> t -> Builder)
-> Format Builder (t -> Builder)
-> Format Builder (Text -> t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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)
"(" Format (t -> Builder) (t -> Builder)
-> Format Builder (t -> Builder) -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (t -> Builder)
forall a r. Buildable a => Format r (a -> r)
build Format Builder (t -> Builder)
-> Format Builder Builder -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 -> Format Builder (TypeRep -> Builder) -> TypeRep -> Builder
forall a. Format Builder a -> a
bprint (Format (TypeRep -> Builder) (TypeRep -> Builder)
"(_ :: " Format (TypeRep -> Builder) (TypeRep -> Builder)
-> Format Builder (TypeRep -> Builder)
-> Format Builder (TypeRep -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (TypeRep -> Builder)
forall a r. Show a => Format r (a -> r)
shown Format Builder (TypeRep -> Builder)
-> Format Builder Builder -> Format Builder (TypeRep -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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
")") (Proxy a -> TypeRep
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 = Format Builder (SizeF Size -> Builder) -> SizeF Size -> Builder
forall a. Format Builder a -> a
bprint Format Builder (SizeF Size -> Builder)
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 = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size)
-> ([Case Size] -> SizeF Size) -> [Case Size] -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. [Case Size] -> SizeF Size
forall t. [Case t] -> SizeF t
CasesF
data Case t
= Case Text t
deriving ((forall a b. (a -> b) -> Case a -> Case b)
-> (forall a b. a -> Case b -> Case a) -> Functor Case
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
$cfmap :: forall a b. (a -> b) -> Case a -> Case b
fmap :: forall a b. (a -> b) -> Case a -> Case b
$c<$ :: forall a b. a -> Case b -> Case a
<$ :: forall a b. a -> Case b -> Case a
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) = Format Builder (Text -> t -> Builder) -> Text -> t -> Builder
forall a. Format Builder a -> a
bprint (Format (t -> Builder) (Text -> t -> Builder)
forall r. Format r (Text -> r)
stext Format (t -> Builder) (Text -> t -> Builder)
-> Format Builder (t -> Builder)
-> Format Builder (Text -> t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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)
"=" Format (t -> Builder) (t -> Builder)
-> Format Builder (t -> Builder) -> Format Builder (t -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (t -> Builder)
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 = Range b -> b
forall b. Range b -> b
lo Range b
x b -> b -> b
forall a. Num a => a -> a -> a
+ Range b -> b
forall b. Range b -> b
lo Range b
y, hi :: b
hi = Range b -> b
forall b. Range b -> b
hi Range b
x b -> b -> b
forall a. Num a => a -> a -> a
+ Range b -> b
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 b -> b -> b
forall a. Num a => a -> a -> a
* b
v | b
u <- [Range b -> b
forall b. Range b -> b
lo Range b
x, Range b -> b
forall b. Range b -> b
hi Range b
x], b
v <- [Range b -> b
forall b. Range b -> b
lo Range b
y, Range b -> b
forall b. Range b -> b
hi Range b
y]]
in Range {lo :: b
lo = [b] -> b
forall a. Ord a => [a] -> a
forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
minimum [b]
products, hi :: b
hi = [b] -> b
forall a. Ord a => [a] -> a
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 = Range b -> b
forall b. Range b -> b
lo Range b
x b -> b -> b
forall a. Num a => a -> a -> a
- Range b -> b
forall b. Range b -> b
hi Range b
y, hi :: b
hi = Range b -> b
forall b. Range b -> b
hi Range b
x b -> b -> b
forall a. Num a => a -> a -> a
- Range b -> b
forall b. Range b -> b
lo Range b
y}
negate :: Range b -> Range b
negate Range b
x = Range {lo :: b
lo = b -> b
forall a. Num a => a -> a
negate (Range b -> b
forall b. Range b -> b
hi Range b
x), hi :: b
hi = b -> b
forall a. Num a => a -> a
negate (Range b -> b
forall b. Range b -> b
lo Range b
x)}
abs :: Range b -> Range b
abs Range b
x =
if
| Range b -> b
forall b. Range b -> b
lo Range b
x b -> b -> Bool
forall a. Ord a => a -> a -> Bool
<= b
0 Bool -> Bool -> Bool
&& Range b -> b
forall b. Range b -> b
hi Range b
x b -> b -> Bool
forall a. Ord a => a -> a -> Bool
>= b
0 -> Range {lo :: b
lo = b
0, hi :: b
hi = b -> b -> b
forall a. Ord a => a -> a -> a
max (Range b -> b
forall b. Range b -> b
hi Range b
x) (b -> b
forall a. Num a => a -> a
negate (b -> b) -> b -> b
forall a b. (a -> b) -> a -> b
$ Range b -> b
forall b. Range b -> b
lo Range b
x)}
| Range b -> b
forall b. Range b -> b
lo Range b
x b -> b -> Bool
forall a. Ord a => a -> a -> Bool
<= b
0 Bool -> Bool -> Bool
&& Range b -> b
forall b. Range b -> b
hi Range b
x b -> b -> Bool
forall a. Ord a => a -> a -> Bool
<= b
0 -> Range {lo :: b
lo = b -> b
forall a. Num a => a -> a
negate (Range b -> b
forall b. Range b -> b
hi Range b
x), hi :: b
hi = b -> b
forall a. Num a => a -> a
negate (Range b -> b
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 = b -> b
forall a. Num a => a -> a
signum (Range b -> b
forall b. Range b -> b
lo Range b
x), hi :: b
hi = b -> b
forall a. Num a => a -> a
signum (Range b -> b
forall b. Range b -> b
hi Range b
x)}
fromInteger :: Integer -> Range b
fromInteger Integer
n = Range {lo :: b
lo = Integer -> b
forall a. Num a => Integer -> a
fromInteger Integer
n, hi :: b
hi = Integer -> b
forall a. Num a => Integer -> a
fromInteger Integer
n}
instance B.Buildable (Range Natural) where
build :: Range Natural -> Builder
build Range Natural
r = Format Builder (Integer -> Integer -> Builder)
-> Integer -> Integer -> Builder
forall a. Format Builder a -> a
bprint (Format (Integer -> Builder) (Integer -> Integer -> Builder)
forall a r. Show a => Format r (a -> r)
shown Format (Integer -> Builder) (Integer -> Integer -> Builder)
-> Format Builder (Integer -> Builder)
-> Format Builder (Integer -> Integer -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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)
".." Format (Integer -> Builder) (Integer -> Builder)
-> Format Builder (Integer -> Builder)
-> Format Builder (Integer -> Builder)
forall b c a. Format b c -> Format a b -> Format a c
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 (Integer -> Builder)
forall a r. Show a => Format r (a -> r)
shown) (Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Natural -> Integer) -> Natural -> Integer
forall a b. (a -> b) -> a -> b
$ Range Natural -> Natural
forall b. Range b -> b
lo Range Natural
r) (Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Natural -> Integer) -> Natural -> Integer
forall a b. (a -> b) -> a -> b
$ Range Natural -> Natural
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 = (Base Size (Range Natural) -> Range Natural)
-> Size -> Range Natural
forall t a. Recursive t => (Base t a -> a) -> t -> a
forall a. (Base Size a -> a) -> Size -> a
cata ((Base Size (Range Natural) -> Range Natural)
-> Size -> Range Natural)
-> (Base Size (Range Natural) -> Range Natural)
-> Size
-> Range Natural
forall a b. (a -> b) -> a -> b
$ \case
AddF Range Natural
x Range Natural
y -> Range Natural
x Range Natural -> Range Natural -> Range Natural
forall a. Num a => a -> a -> a
+ Range Natural
y
MulF Range Natural
x Range Natural
y -> Range Natural
x Range Natural -> Range Natural -> Range Natural
forall a. Num a => a -> a -> a
* Range Natural
y
SubF Range Natural
x Range Natural
y -> Range Natural
x Range Natural -> Range Natural -> Range Natural
forall a. Num a => a -> a -> a
- Range Natural
y
NegF Range Natural
x -> Range Natural -> Range Natural
forall a. Num a => a -> a
negate Range Natural
x
AbsF Range Natural
x -> Range Natural -> Range Natural
forall a. Num a => a -> a
abs Range Natural
x
SgnF Range Natural
x -> Range Natural -> Range Natural
forall a. Num a => a -> a
signum Range Natural
x
CasesF [Case (Range Natural)]
xs ->
Range
{ lo :: Natural
lo = [Natural] -> Natural
forall a. Ord a => [a] -> a
forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
minimum ((Case (Range Natural) -> Natural)
-> [Case (Range Natural)] -> [Natural]
forall a b. (a -> b) -> [a] -> [b]
map (Range Natural -> Natural
forall b. Range b -> b
lo (Range Natural -> Natural)
-> (Case (Range Natural) -> Range Natural)
-> Case (Range Natural)
-> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Case (Range Natural) -> Range Natural
forall t. Case t -> t
caseValue) [Case (Range Natural)]
xs)
, hi :: Natural
hi = [Natural] -> Natural
forall a. Ord a => [a] -> a
forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
maximum ((Case (Range Natural) -> Natural)
-> [Case (Range Natural)] -> [Natural]
forall a b. (a -> b) -> [a] -> [b]
map (Range Natural -> Natural
forall b. Range b -> b
hi (Range Natural -> Natural)
-> (Case (Range Natural) -> Range Natural)
-> Case (Range Natural)
-> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Case (Range Natural) -> Range Natural
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 (Range Natural -> Natural
forall b. Range b -> b
lo Range Natural
x), hi :: Natural
hi = Natural -> Natural
f (Range Natural -> Natural
forall b. Range b -> b
hi Range Natural
x)}
TodoF forall t. EncCBOR t => Proxy t -> Size
f Proxy a
x -> (Proxy a -> Size) -> Proxy a -> Range Natural
forall t.
EncCBOR t =>
(Proxy t -> Size) -> Proxy t -> Range Natural
doit Proxy a -> Size
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 t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
todo ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy t -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
szLazy)
szGreedy :: EncCBOR a => (Proxy a -> Size)
szGreedy :: forall t. EncCBOR t => Proxy t -> Size
szGreedy = (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
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 = SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> SizeF Size
forall t a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> SizeF t
TodoF Proxy x -> Size
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) -> SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (Natural -> SizeF Size
forall t. Natural -> SizeF t
ValueF (Natural -> Natural
f Natural
x))
Fix (CasesF [Case Size]
cs) -> SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix ([Case Size] -> SizeF Size
forall t. [Case t] -> SizeF t
CasesF ((Case Size -> Case Size) -> [Case Size] -> [Case Size]
forall a b. (a -> b) -> [a] -> [b]
map ((Size -> Size) -> Case Size -> Case Size
forall a b. (a -> b) -> Case a -> Case b
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 -> SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (Text -> (Natural -> Natural) -> Size -> SizeF Size
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 TypeRep -> Map TypeRep SizeOverride -> Maybe SizeOverride
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Proxy a -> TypeRep
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 (Map TypeRep SizeOverride -> Proxy a -> Size
forall a. EncCBOR a => Map TypeRep SizeOverride -> Proxy a -> Size
szWithCtx Map TypeRep SizeOverride
ctx)
SelectCases [Text]
names -> (Base Size Size -> Size) -> Size -> Size
forall t a. Recursive t => (Base t a -> a) -> t -> a
forall a. (Base Size a -> a) -> Size -> a
cata ([Text] -> SizeF Size -> Size
selectCase [Text]
names) Size
normal
where
normal :: Size
normal = (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (Map TypeRep SizeOverride -> Proxy t -> Size
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 (SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix SizeF Size
orig)
SizeF Size
_ -> SizeF Size -> 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 (Case Size -> Bool) -> [Case Size] -> [Case Size]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Case Text
name Size
_) -> Text
name Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
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' -> SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix ([Case Size] -> SizeF Size
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 = (Base Size (Either Size (Range Natural))
-> Either Size (Range Natural))
-> Size -> Either Size (Range Natural)
forall t a. Recursive t => (Base t a -> a) -> t -> a
forall a. (Base Size a -> a) -> Size -> a
cata ((Base Size (Either Size (Range Natural))
-> Either Size (Range Natural))
-> Size -> Either Size (Range Natural))
-> (Base Size (Either Size (Range Natural))
-> Either Size (Range Natural))
-> Size
-> Either Size (Range Natural)
forall a b. (a -> b) -> a -> b
$ \case
TodoF forall t. EncCBOR t => Proxy t -> Size
f Proxy a
pxy -> Size -> Either Size (Range Natural)
forall a b. a -> Either a b
Left ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
todo Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
f Proxy a
pxy)
ValueF Natural
x -> Range Natural -> Either Size (Range Natural)
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 (Case (Either Size (Range Natural)) -> Either Size (Range Natural))
-> [Case (Either Size (Range Natural))]
-> Either Size [Range Natural]
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: Type -> Type) a b.
Monad m =>
(a -> m b) -> [a] -> m [b]
mapM Case (Either Size (Range Natural)) -> Either Size (Range Natural)
forall t. Case t -> t
caseValue [Case (Either Size (Range Natural))]
xs of
Right [Range Natural]
xs' ->
Range Natural -> Either Size (Range Natural)
forall a b. b -> Either a b
Right (Range {lo :: Natural
lo = [Natural] -> Natural
forall a. Ord a => [a] -> a
forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
minimum ((Range Natural -> Natural) -> [Range Natural] -> [Natural]
forall a b. (a -> b) -> [a] -> [b]
map Range Natural -> Natural
forall b. Range b -> b
lo [Range Natural]
xs'), hi :: Natural
hi = [Natural] -> Natural
forall a. Ord a => [a] -> a
forall (t :: Type -> Type) a. (Foldable t, Ord a) => t a -> a
maximum ((Range Natural -> Natural) -> [Range Natural] -> [Natural]
forall a b. (a -> b) -> [a] -> [b]
map Range Natural -> Natural
forall b. Range b -> b
hi [Range Natural]
xs')})
Left Size
_ -> Size -> Either Size (Range Natural)
forall a b. a -> Either a b
Left ([Case Size] -> Size
szCases ([Case Size] -> Size) -> [Case Size] -> Size
forall a b. (a -> b) -> a -> b
$ (Case (Either Size (Range Natural)) -> Case Size)
-> [Case (Either Size (Range Natural))] -> [Case Size]
forall a b. (a -> b) -> [a] -> [b]
map ((Either Size (Range Natural) -> Size)
-> Case (Either Size (Range Natural)) -> Case Size
forall a b. (a -> b) -> Case a -> Case b
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 a -> a -> a
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 a -> a -> a
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 a -> a
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 a -> a
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 a -> a
forall a. Num a => a -> a
signum Either Size (Range Natural)
x
ApF Text
_ Natural -> Natural
f (Right Range Natural
x) -> Range Natural -> Either Size (Range Natural)
forall a b. b -> Either a b
Right (Range {lo :: Natural
lo = Natural -> Natural
f (Range Natural -> Natural
forall b. Range b -> b
lo Range Natural
x), hi :: Natural
hi = Natural -> Natural
f (Range Natural -> Natural
forall b. Range b -> b
hi Range Natural
x)})
ApF Text
n Natural -> Natural
f (Left Size
x) -> Size -> Either Size (Range Natural)
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) = Range Natural -> Either Size (Range Natural)
forall a b. b -> Either a b
Right (Range Natural -> Range Natural -> Range Natural
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 = Size -> Either Size (Range Natural)
forall a b. a -> Either a b
Left (Size -> Size -> Size
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 -> Range Natural -> Either Size (Range Natural)
forall a b. b -> Either a b
Right (Range Natural -> Range Natural
forall a. Num a => a -> a
f Range Natural
x)
Left Size
x -> Size -> Either Size (Range Natural)
forall a b. a -> Either a b
Left (Size -> Size
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 Range Natural -> Natural
forall b. Range b -> b
lo Range Natural
r Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Range Natural -> Natural
forall b. Range b -> b
hi Range Natural
r
then Natural -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Range Natural -> Natural
forall b. Range b -> b
lo Range Natural
r)
else
[Case Size] -> Size
szCases
[Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"lo" (Natural -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Natural -> Size) -> Natural -> Size
forall a b. (a -> b) -> a -> b
$ Range Natural -> Natural
forall b. Range b -> b
lo Range Natural
r), Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"hi" (Natural -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Natural -> Size) -> Natural -> Size
forall a b. (a -> b) -> a -> b
$ Range Natural -> Natural
forall b. Range b -> b
hi Range Natural
r)]
szForce :: Size -> Size
szForce :: Size -> Size
szForce = (Base Size Size -> Size) -> Size -> Size
forall t a. Recursive t => (Base t a -> a) -> t -> a
forall a. (Base Size a -> a) -> Size -> a
cata ((Base Size Size -> Size) -> Size -> Size)
-> (Base Size Size -> Size) -> Size -> Size
forall a b. (a -> b) -> a -> b
$ \case
AddF Size
x Size
y -> Size
x Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
y
MulF Size
x Size
y -> Size
x Size -> Size -> Size
forall a. Num a => a -> a -> a
* Size
y
SubF Size
x Size
y -> Size
x Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
y
NegF Size
x -> Size -> Size
forall a. Num a => a -> a
negate Size
x
AbsF Size
x -> Size -> Size
forall a. Num a => a -> a
abs Size
x
SgnF Size
x -> Size -> Size
forall a. Num a => a -> a
signum Size
x
CasesF [Case Size]
xs -> SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (SizeF Size -> Size) -> SizeF Size -> Size
forall a b. (a -> b) -> a -> b
$ [Case Size] -> SizeF Size
forall t. [Case t] -> SizeF t
CasesF [Case Size]
xs
ValueF Natural
x -> SizeF Size -> Size
forall (f :: Type -> Type). f (Fix f) -> Fix f
Fix (Natural -> SizeF Size
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 -> Proxy a -> Size
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 (Size -> Either Size (Range Natural))
-> (a -> Size) -> a -> Either Size (Range Natural)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
szGreedy (Proxy a -> Size) -> (a -> Proxy a) -> a -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Proxy a
forall a. a -> Proxy a
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 = s -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral s
x :: Integer
in if
| Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0x17 Bool -> Bool -> Bool
&& Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= (-Integer
0x18) -> a
1
| Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0xff Bool -> Bool -> Bool
&& Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= (-Integer
0x100) -> a
2
| Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0xffff Bool -> Bool -> Bool
&& Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= (-Integer
0x10000) -> a
3
| Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0xffffffff Bool -> Bool -> Bool
&& Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= (-Integer
0x100000000) -> a
5
| Bool
otherwise -> a
9
instance EncCBOR () where
encCBOR :: () -> Encoding
encCBOR = Encoding -> () -> Encoding
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" a
forall a. Bounded a => a
maxBound
]
where
mkCase :: Text -> a -> Case Size
mkCase :: Text -> a -> Case Size
mkCase Text
n = Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
n (Size -> Case Size) -> (a -> Size) -> a -> Case Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> Size
forall a. Num a => Integer -> a
fromInteger (Integer -> Size) -> (a -> Integer) -> a -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Integer
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
_ = Proxy Word -> 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
_ = Proxy Word8 -> 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
_ = Proxy Word16 -> 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
_ = Proxy Word32 -> 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
_ = Proxy Word64 -> 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
_ = Proxy Int -> 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
_ = Proxy Int8 -> 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
_ = Proxy Int16 -> 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
_ = Proxy Int32 -> 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
_ = Proxy Int64 -> 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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Int -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Float -> Int
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Int -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Float -> Int
forall a. Storable a => a -> Int
sizeOf (Float
0 :: Float))
instance EncCBOR a => EncCBOR (Ratio a) where
encCBOR :: Ratio a -> Encoding
encCBOR = (a -> Encoding) -> Ratio a -> Encoding
forall t. (t -> Encoding) -> Ratio t -> Encoding
encodeRatio a -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
deriving newtype instance Typeable p => EncCBOR (Fixed p)
instance EncCBOR Natural where
encCBOR :: Natural -> Encoding
encCBOR = Integer -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (Integer -> Encoding)
-> (Natural -> Integer) -> Natural -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Natural -> Integer
forall a. Integral a => a -> Integer
toInteger
instance EncCBOR Void where
encCBOR :: Void -> Encoding
encCBOR = Void -> Encoding
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 = Encoding -> Encoding
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) = a -> Encoding
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 t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
a Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> b -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy b -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
a Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> b -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR b
b Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> c -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy b -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b) Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy c -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
a Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> b -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR b
b Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> c -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR c
c Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> d -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy b -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b) Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy c -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c) Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy d -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
a
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> b -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR b
b
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> c -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR c
c
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> d -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR d
d
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> e -> Encoding
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
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy b -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy c -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy d -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @d)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy e -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
a
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> b -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR b
b
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> c -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR c
c
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> d -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR d
d
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> e -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR e
e
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> f -> Encoding
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
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy b -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy c -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy d -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @d)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy e -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @e)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy f -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
a
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> b -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR b
b
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> c -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR c
c
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> d -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR d
d
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> e -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR e
e
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> f -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR f
f
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> g -> Encoding
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
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy b -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy c -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy d -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @d)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy e -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @e)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy f -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @f)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy g -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 = Proxy (LengthOf ByteString) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 (Int -> Natural) -> (Natural -> Int) -> Natural -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Size
len Size -> Size -> Size
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 =
Proxy (LengthOf Text) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(LengthOf Text))
Size -> Size -> Size
forall a. Num a => a -> a -> a
* [Case Size] -> Size
szCases [Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"minChar" Size
1, Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"maxChar" Size
4]
in Size
bsLength Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Text -> (Natural -> Natural) -> Size -> Size
apMono Text
"withWordSize" Natural -> Natural
forall s a. (Integral s, Integral a) => s -> a
withWordSize Size
bsLength
instance EncCBOR ByteArray where
encCBOR :: ByteArray -> Encoding
encCBOR = ByteArray -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (ByteArray -> Encoding)
-> (ByteArray -> ByteArray) -> ByteArray -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
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 (SlicedByteArray -> Encoding)
-> (ByteArray -> SlicedByteArray) -> ByteArray -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
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 (SlicedByteArray -> Encoding) -> SlicedByteArray -> Encoding
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 = Proxy (LengthOf ShortByteString) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 (Int -> Natural) -> (Natural -> Int) -> Natural -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Size
len Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
len
instance EncCBOR BS.Lazy.ByteString where
encCBOR :: ByteString -> Encoding
encCBOR = ByteString -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (ByteString -> Encoding)
-> (ByteString -> ByteString) -> ByteString -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
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 = Proxy (LengthOf ByteString) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 (Int -> Natural) -> (Natural -> Int) -> Natural -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Size
len Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
len
instance EncCBOR a => EncCBOR [a] where
encCBOR :: [a] -> Encoding
encCBOR = (a -> Encoding) -> [a] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
encodeList a -> Encoding
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 t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size
encodedListSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word -> Encoding
encodeWord Word
0 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR a
x
encCBOR (Right b
x) = Word -> Encoding
encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word -> Encoding
encodeWord Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> b -> Encoding
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
[Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"Left" (Size
2 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)), Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"Right" (Size
2 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy b -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b))]
instance EncCBOR a => EncCBOR (NonEmpty a) where
encCBOR :: NonEmpty a -> Encoding
encCBOR = [a] -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR ([a] -> Encoding) -> (NonEmpty a -> [a]) -> NonEmpty a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. NonEmpty a -> [a]
forall a. NonEmpty a -> [a]
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)
_ = Proxy [a] -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @[a])
instance EncCBOR a => EncCBOR (Maybe a) where
encCBOR :: Maybe a -> Encoding
encCBOR = (a -> Encoding) -> Maybe a -> Encoding
forall a. (a -> Encoding) -> Maybe a -> Encoding
encodeMaybe a -> Encoding
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 [Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"Nothing" Size
1, Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"Just" (Size
1 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a))]
instance EncCBOR a => EncCBOR (SMaybe.StrictMaybe a) where
encCBOR :: StrictMaybe a -> Encoding
encCBOR = (a -> Encoding) -> StrictMaybe a -> Encoding
forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeStrictMaybe a -> Encoding
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 [Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"SNothing" Size
1, Text -> Size -> Case Size
forall t. Text -> t -> Case t
Case Text
"SJust" (Size
1 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 = (k -> Encoding) -> (v -> Encoding) -> Map k v -> Encoding
forall k v.
(k -> Encoding) -> (v -> Encoding) -> Map k v -> Encoding
encodeMap k -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR v -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR
instance (Ord a, EncCBOR a) => EncCBOR (Set.Set a) where
encCBOR :: Set a -> Encoding
encCBOR = (a -> Encoding) -> Set a -> Encoding
forall a. (a -> Encoding) -> Set a -> Encoding
encodeSet a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR
instance EncCBOR a => EncCBOR (Seq.Seq a) where
encCBOR :: Seq a -> Encoding
encCBOR = (a -> Encoding) -> Seq a -> Encoding
forall a. (a -> Encoding) -> Seq a -> Encoding
encodeSeq a -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR
instance EncCBOR a => EncCBOR (SSeq.StrictSeq a) where
encCBOR :: StrictSeq a -> Encoding
encCBOR = (a -> Encoding) -> StrictSeq a -> Encoding
forall a. (a -> Encoding) -> StrictSeq a -> Encoding
encodeStrictSeq a -> Encoding
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 = (k -> Encoding) -> (v -> Encoding) -> VMap kv vv k v -> Encoding
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 k -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR v -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR
instance EncCBOR a => EncCBOR (V.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = (a -> Encoding) -> Vector a -> Encoding
forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector a -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy (LengthOf (Vector a)) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(LengthOf (V.Vector a))) Size -> Size -> Size
forall a. Num a => a -> a -> a
* Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
instance (EncCBOR a, VP.Prim a) => EncCBOR (VP.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = (a -> Encoding) -> Vector a -> Encoding
forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector a -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy (LengthOf (Vector a)) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(LengthOf (VP.Vector a))) Size -> Size -> Size
forall a. Num a => a -> a -> a
* Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
instance (EncCBOR a, VS.Storable a) => EncCBOR (VS.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = (a -> Encoding) -> Vector a -> Encoding
forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector a -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy (LengthOf (Vector a)) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(LengthOf (VS.Vector a))) Size -> Size -> Size
forall a. Num a => a -> a -> a
* Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
instance (EncCBOR a, VU.Unbox a) => EncCBOR (VU.Vector a) where
encCBOR :: Vector a -> Encoding
encCBOR = (a -> Encoding) -> Vector a -> Encoding
forall (v :: Type -> Type) a.
Vector v a =>
(a -> Encoding) -> v a -> Encoding
encodeVector a -> Encoding
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 Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy (LengthOf (Vector a)) -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(LengthOf (VU.Vector a))) Size -> Size -> Size
forall a. Num a => a -> a -> a
* Proxy a -> Size
forall t. EncCBOR t => Proxy t -> Size
size (forall t. Proxy t
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeVerKeyDSIGN (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeVerKeyDSIGN (Proxy v
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSignKeyDSIGN (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSignKeyDSIGN (Proxy v
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSigDSIGN (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type).
DSIGNAlgorithm v =>
proxy v -> Word
sizeSigDSIGN (Proxy v
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 = Proxy (SigDSIGN v) -> Size
forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr (Proxy (SigDSIGN v)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (SigDSIGN v))
instance DSIGNAlgorithm v => EncCBOR (VerKeyDSIGN v) where
encCBOR :: VerKeyDSIGN v -> Encoding
encCBOR = VerKeyDSIGN v -> Encoding
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
_ = Proxy (VerKeyDSIGN v) -> Size
forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr
instance DSIGNAlgorithm v => EncCBOR (SignKeyDSIGN v) where
encCBOR :: SignKeyDSIGN v -> Encoding
encCBOR = SignKeyDSIGN v -> Encoding
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
_ = Proxy (SignKeyDSIGN v) -> Size
forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDSIGNSizeExpr
instance DSIGNAlgorithm v => EncCBOR (SigDSIGN v) where
encCBOR :: SigDSIGN v -> Encoding
encCBOR = SigDSIGN v -> Encoding
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
_ = Proxy (SigDSIGN v) -> 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 = SignedDSIGN v a -> Encoding
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
_ = Proxy (SignedDSIGN v a) -> 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) = ShortByteString -> Encoding
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 t. EncCBOR t => Proxy t -> Size)
-> Proxy ByteString -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (Size -> Proxy t -> Size
forall a b. a -> b -> a
const Size
hashSize) (Hash h a -> ByteString
forall h a. Hash h a -> ByteString
hashToBytes (Hash h a -> ByteString) -> Proxy (Hash h a) -> Proxy ByteString
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 = Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy h -> Word
forall h (proxy :: Type -> Type).
HashAlgorithm h =>
proxy h -> Word
sizeHash (Proxy h
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeVerKeyKES (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeVerKeyKES (Proxy v
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSignKeyKES (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSignKeyKES (Proxy v
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSigKES (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type). KESAlgorithm v => proxy v -> Word
sizeSigKES (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
instance KESAlgorithm k => EncCBOR (VerKeyKES k) where
encCBOR :: VerKeyKES k -> Encoding
encCBOR = VerKeyKES k -> Encoding
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 = Proxy (VerKeyKES k) -> Size
forall v. KESAlgorithm v => Proxy (VerKeyKES v) -> Size
encodedVerKeyKESSizeExpr
instance KESAlgorithm k => EncCBOR (SigKES k) where
encCBOR :: SigKES k -> Encoding
encCBOR = SigKES k -> Encoding
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 = Proxy (SigKES k) -> 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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeVerKeyVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeVerKeyVRF (Proxy v
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeSignKeyVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeSignKeyVRF (Proxy v
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 =
Integer -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word -> Integer
forall s a. (Integral s, Integral a) => s -> a
withWordSize :: Word -> Integer) (Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeCertVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)))
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeCertVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
instance EncCBOR (VerKeyVRF SimpleVRF) where
encCBOR :: VerKeyVRF SimpleVRF -> Encoding
encCBOR = VerKeyVRF SimpleVRF -> Encoding
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 = Proxy (VerKeyVRF SimpleVRF) -> Size
forall v. VRFAlgorithm v => Proxy (VerKeyVRF v) -> Size
encodedVerKeyVRFSizeExpr
instance EncCBOR (SignKeyVRF SimpleVRF) where
encCBOR :: SignKeyVRF SimpleVRF -> Encoding
encCBOR = SignKeyVRF SimpleVRF -> Encoding
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 = Proxy (SignKeyVRF SimpleVRF) -> Size
forall v. VRFAlgorithm v => Proxy (SignKeyVRF v) -> Size
encodedSignKeyVRFSizeExpr
instance EncCBOR (CertVRF SimpleVRF) where
encCBOR :: CertVRF SimpleVRF -> Encoding
encCBOR = CertVRF SimpleVRF -> Encoding
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 = Proxy (CertVRF SimpleVRF) -> Size
forall v. VRFAlgorithm v => Proxy (CertVRF v) -> Size
encodedCertVRFSizeExpr
instance EncCBOR (VerKeyVRF MockVRF) where
encCBOR :: VerKeyVRF MockVRF -> Encoding
encCBOR = VerKeyVRF MockVRF -> Encoding
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 = Proxy (VerKeyVRF MockVRF) -> Size
forall v. VRFAlgorithm v => Proxy (VerKeyVRF v) -> Size
encodedVerKeyVRFSizeExpr
instance EncCBOR (SignKeyVRF MockVRF) where
encCBOR :: SignKeyVRF MockVRF -> Encoding
encCBOR = SignKeyVRF MockVRF -> Encoding
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 = Proxy (SignKeyVRF MockVRF) -> Size
forall v. VRFAlgorithm v => Proxy (SignKeyVRF v) -> Size
encodedSignKeyVRFSizeExpr
instance EncCBOR (CertVRF MockVRF) where
encCBOR :: CertVRF MockVRF -> Encoding
encCBOR = CertVRF MockVRF -> Encoding
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 = Proxy (CertVRF MockVRF) -> 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
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> OutputVRF v -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (CertifiedVRF v a -> OutputVRF v
forall v a. CertifiedVRF v a -> OutputVRF v
certifiedOutput CertifiedVRF v a
cvrf)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> CertVRF v -> Encoding
forall v. VRFAlgorithm v => CertVRF v -> Encoding
encodeCertVRF (CertifiedVRF v a -> CertVRF v
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
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy (OutputVRF v) -> Size
certifiedOutputSize (CertifiedVRF v a -> OutputVRF v
forall v a. CertifiedVRF v a -> OutputVRF v
certifiedOutput (CertifiedVRF v a -> OutputVRF v)
-> Proxy (CertifiedVRF v a) -> Proxy (OutputVRF v)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (CertifiedVRF v a)
proxy)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeCertVRF (Proxy v
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 =
Word -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> Size) -> Word -> Size
forall a b. (a -> b) -> a -> b
$ Proxy v -> Word
forall v (proxy :: Type -> Type). VRFAlgorithm v => proxy v -> Word
forall (proxy :: Type -> Type). proxy v -> Word
sizeOutputVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)
instance EncCBOR Praos.Proof where
encCBOR :: Proof -> Encoding
encCBOR = ByteString -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (ByteString -> Encoding)
-> (Proof -> ByteString) -> Proof -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
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 t. EncCBOR t => Proxy t -> Size)
-> Proxy ByteString -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (\Proxy t
_ -> Int -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Praos.certSizeVRF) (Proxy ByteString
forall {k} (t :: k). Proxy t
Proxy :: Proxy BS.ByteString)
instance EncCBOR Praos.SignKey where
encCBOR :: SignKey -> Encoding
encCBOR = ByteString -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (ByteString -> Encoding)
-> (SignKey -> ByteString) -> SignKey -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
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 t. EncCBOR t => Proxy t -> Size)
-> Proxy ByteString -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (\Proxy t
_ -> Int -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Praos.signKeySizeVRF) (Proxy ByteString
forall {k} (t :: k). Proxy t
Proxy :: Proxy BS.ByteString)
instance EncCBOR Praos.VerKey where
encCBOR :: VerKey -> Encoding
encCBOR = ByteString -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (ByteString -> Encoding)
-> (VerKey -> ByteString) -> VerKey -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
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 t. EncCBOR t => Proxy t -> Size)
-> Proxy ByteString -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr (\Proxy t
_ -> Int -> Size
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
Praos.verKeySizeVRF) (Proxy ByteString
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 (Encoding -> Encoding)
-> (SlotNo -> Encoding) -> SlotNo -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SlotNo -> Encoding
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 t. EncCBOR t => Proxy t -> Size) -> Proxy Word64 -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
size (Proxy Word64 -> Size)
-> (Proxy SlotNo -> Proxy Word64) -> Proxy SlotNo -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (SlotNo -> Word64) -> Proxy SlotNo -> Proxy Word64
forall a b. (a -> b) -> Proxy a -> Proxy b
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 (Encoding -> Encoding)
-> (WithOrigin t -> Encoding) -> WithOrigin t -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WithOrigin t -> Encoding
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 (Encoding -> Encoding)
-> (BlockNo -> Encoding) -> BlockNo -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. BlockNo -> Encoding
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 t. EncCBOR t => Proxy t -> Size) -> Proxy Word64 -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
size (Proxy Word64 -> Size)
-> (Proxy BlockNo -> Proxy Word64) -> Proxy BlockNo -> Size
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (BlockNo -> Word64) -> Proxy BlockNo -> Proxy Word64
forall a b. (a -> b) -> Proxy a -> Proxy b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap BlockNo -> Word64
unBlockNo
deriving instance EncCBOR EpochInterval
instance Plain.ToCBOR PV1.Data where
toCBOR :: Data -> Encoding
toCBOR = Data -> Encoding
forall a. Serialise a => a -> Encoding
Serialise.encode
instance EncCBOR PV1.Data
instance EncCBOR PV1.ScriptContext where
encCBOR :: ScriptContext -> Encoding
encCBOR = Data -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (Data -> Encoding)
-> (ScriptContext -> Data) -> ScriptContext -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ScriptContext -> Data
forall a. ToData a => a -> Data
PV3.toData
instance EncCBOR PV2.ScriptContext where
encCBOR :: ScriptContext -> Encoding
encCBOR = Data -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (Data -> Encoding)
-> (ScriptContext -> Data) -> ScriptContext -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ScriptContext -> Data
forall a. ToData a => a -> Data
PV3.toData
instance EncCBOR PV3.ScriptContext where
encCBOR :: ScriptContext -> Encoding
encCBOR = Data -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (Data -> Encoding)
-> (ScriptContext -> Data) -> ScriptContext -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ScriptContext -> Data
forall a. ToData a => a -> Data
PV3.toData