{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoStarIsType #-}
module Cardano.Ledger.Binary.Decoding.DecCBOR (
DecCBOR (..),
fromByronCBOR,
decodeScriptContextFromData,
) where
import qualified Cardano.Binary as Plain (Decoder, FromCBOR (..))
import Cardano.Crypto.DSIGN.Class (
DSIGNAlgorithm,
SigDSIGN,
SignKeyDSIGN,
SignedDSIGN,
VerKeyDSIGN,
)
import Cardano.Crypto.Hash.Class (Hash, HashAlgorithm)
import Cardano.Crypto.KES.Class (KESAlgorithm, SigKES, VerKeyKES)
import Cardano.Crypto.VRF.Class (
CertVRF,
CertifiedVRF (..),
OutputVRF (..),
SignKeyVRF,
VRFAlgorithm,
VerKeyVRF,
)
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.Decoding.Decoder
import Cardano.Ledger.Binary.Version (Version, byronProtVer)
import Cardano.Slotting.Block (BlockNo (..))
import Cardano.Slotting.Slot (
EpochInterval (..),
EpochNo (..),
EpochSize (..),
SlotNo (..),
WithOrigin (..),
)
import Cardano.Slotting.Time (SystemStart (..))
import Codec.CBOR.ByteArray.Sliced (SlicedByteArray, fromByteArray)
import Codec.CBOR.Term (Term (..))
import Codec.Serialise as Serialise (Serialise (decode))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
#if MIN_VERSION_bytestring(0,11,1)
import Data.ByteString.Short (ShortByteString(SBS))
#else
import Data.ByteString.Short.Internal (ShortByteString(SBS))
#endif
import Data.Fixed (Fixed (..))
import Data.IP (IPv4, IPv6)
import Data.Int (Int16, Int32, Int64, Int8)
import qualified Data.IntMap as IntMap
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
import qualified Data.Sequence as Seq
import qualified Data.Sequence.Strict as SSeq
import qualified Data.Set as Set
import Data.Tagged (Tagged (Tagged))
import qualified Data.Text as T
import Data.Time.Clock (UTCTime (..))
import Data.Typeable (Proxy (..), 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)
import Data.Word (Word16, Word32, Word64, Word8)
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 (decodeFloat)
class Typeable a => DecCBOR a where
decCBOR :: Decoder s a
default decCBOR :: Plain.FromCBOR a => Decoder s a
decCBOR = Decoder s a -> Decoder s a
forall s a. Decoder s a -> Decoder s a
fromPlainDecoder Decoder s a
forall s. Decoder s a
forall a s. FromCBOR a => Decoder s a
Plain.fromCBOR
{-# INLINE decCBOR #-}
dropCBOR :: Proxy a -> Decoder s ()
dropCBOR Proxy a
_ = () () -> Decoder s a -> Decoder s ()
forall a b. a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ forall a s. DecCBOR a => Decoder s a
decCBOR @a
label :: Proxy a -> T.Text
label = String -> Text
T.pack (String -> Text) -> (Proxy a -> String) -> Proxy a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> (Proxy a -> TypeRep) -> Proxy a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy a -> TypeRep
forall {k} (proxy :: k -> Type) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep
instance DecCBOR Version where
decCBOR :: forall s. Decoder s Version
decCBOR = Decoder s Version
forall s. Decoder s Version
decodeVersion
{-# INLINE decCBOR #-}
fromByronCBOR :: DecCBOR a => Plain.Decoder s a
fromByronCBOR :: forall a s. DecCBOR a => Decoder s a
fromByronCBOR = Maybe ByteString -> Version -> Decoder s a -> Decoder s a
forall s a.
Maybe ByteString -> Version -> Decoder s a -> Decoder s a
toPlainDecoder Maybe ByteString
forall a. Maybe a
Nothing Version
byronProtVer Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE fromByronCBOR #-}
instance DecCBOR () where
decCBOR :: forall s. Decoder s ()
decCBOR = Decoder s ()
forall s. Decoder s ()
decodeNull
{-# INLINE decCBOR #-}
instance DecCBOR Bool where
decCBOR :: forall s. Decoder s Bool
decCBOR = Decoder s Bool
forall s. Decoder s Bool
decodeBool
{-# INLINE decCBOR #-}
instance DecCBOR Integer where
decCBOR :: forall s. Decoder s Integer
decCBOR = Decoder s Integer
forall s. Decoder s Integer
decodeInteger
{-# INLINE decCBOR #-}
instance DecCBOR Natural where
decCBOR :: forall s. Decoder s Natural
decCBOR = Decoder s Natural
forall s. Decoder s Natural
decodeNatural
{-# INLINE decCBOR #-}
instance DecCBOR Word where
decCBOR :: forall s. Decoder s Word
decCBOR = Decoder s Word
forall s. Decoder s Word
decodeWord
{-# INLINE decCBOR #-}
instance DecCBOR Word8 where
decCBOR :: forall s. Decoder s Word8
decCBOR = Decoder s Word8
forall s. Decoder s Word8
decodeWord8
{-# INLINE decCBOR #-}
instance DecCBOR Word16 where
decCBOR :: forall s. Decoder s Word16
decCBOR = Decoder s Word16
forall s. Decoder s Word16
decodeWord16
{-# INLINE decCBOR #-}
instance DecCBOR Word32 where
decCBOR :: forall s. Decoder s Word32
decCBOR = Decoder s Word32
forall s. Decoder s Word32
decodeWord32
{-# INLINE decCBOR #-}
instance DecCBOR Word64 where
decCBOR :: forall s. Decoder s Word64
decCBOR = Decoder s Word64
forall s. Decoder s Word64
decodeWord64
{-# INLINE decCBOR #-}
instance DecCBOR Int where
decCBOR :: forall s. Decoder s Int
decCBOR = Decoder s Int
forall s. Decoder s Int
decodeInt
{-# INLINE decCBOR #-}
instance DecCBOR Int8 where
decCBOR :: forall s. Decoder s Int8
decCBOR = Decoder s Int8
forall s. Decoder s Int8
decodeInt8
{-# INLINE decCBOR #-}
instance DecCBOR Int16 where
decCBOR :: forall s. Decoder s Int16
decCBOR = Decoder s Int16
forall s. Decoder s Int16
decodeInt16
{-# INLINE decCBOR #-}
instance DecCBOR Int32 where
decCBOR :: forall s. Decoder s Int32
decCBOR = Decoder s Int32
forall s. Decoder s Int32
decodeInt32
{-# INLINE decCBOR #-}
instance DecCBOR Int64 where
decCBOR :: forall s. Decoder s Int64
decCBOR = Decoder s Int64
forall s. Decoder s Int64
decodeInt64
{-# INLINE decCBOR #-}
instance DecCBOR Float where
decCBOR :: forall s. Decoder s Float
decCBOR = Decoder s Float
forall s. Decoder s Float
decodeFloat
{-# INLINE decCBOR #-}
instance DecCBOR Double where
decCBOR :: forall s. Decoder s Double
decCBOR = Decoder s Double
forall s. Decoder s Double
decodeDouble
{-# INLINE decCBOR #-}
instance DecCBOR Rational where
decCBOR :: forall s. Decoder s Rational
decCBOR = Decoder s Rational
forall s. Decoder s Rational
decodeRational
{-# INLINE decCBOR #-}
deriving newtype instance Typeable p => DecCBOR (Fixed p)
instance DecCBOR Void where
decCBOR :: forall s. Decoder s Void
decCBOR = DecoderError -> Decoder s Void
forall (m :: Type -> Type) e a.
(MonadFail m, Buildable e) =>
e -> m a
cborError DecoderError
DecoderErrorVoid
instance DecCBOR Term where
decCBOR :: forall s. Decoder s Term
decCBOR = Decoder s Term
forall s. Decoder s Term
decodeTerm
{-# INLINE decCBOR #-}
instance DecCBOR IPv4 where
decCBOR :: forall s. Decoder s IPv4
decCBOR = Decoder s IPv4
forall s. Decoder s IPv4
decodeIPv4
{-# INLINE decCBOR #-}
instance DecCBOR IPv6 where
decCBOR :: forall s. Decoder s IPv6
decCBOR = Decoder s IPv6
forall s. Decoder s IPv6
decodeIPv6
{-# INLINE decCBOR #-}
instance (Typeable s, DecCBOR a) => DecCBOR (Tagged s a) where
decCBOR :: forall s. Decoder s (Tagged s a)
decCBOR = a -> Tagged s a
forall {k} (s :: k) b. b -> Tagged s b
Tagged (a -> Tagged s a) -> Decoder s a -> Decoder s (Tagged s a)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
dropCBOR :: forall s. Proxy (Tagged s a) -> Decoder s ()
dropCBOR Proxy (Tagged s a)
_ = Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
instance (DecCBOR a, DecCBOR b) => DecCBOR (a, b) where
decCBOR :: forall s. Decoder s (a, b)
decCBOR = do
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
2
!a
x <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
!b
y <- Decoder s b
forall s. Decoder s b
forall a s. DecCBOR a => Decoder s a
decCBOR
(a, b) -> Decoder s (a, b)
forall a. a -> Decoder s a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (a
x, b
y)
dropCBOR :: forall s. Proxy (a, b) -> Decoder s ()
dropCBOR Proxy (a, b)
_ = Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
2 Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy b -> Decoder s ()
forall s. Proxy b -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
{-# INLINE decCBOR #-}
instance (DecCBOR a, DecCBOR b, DecCBOR c) => DecCBOR (a, b, c) where
decCBOR :: forall s. Decoder s (a, b, c)
decCBOR = do
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
3
!a
x <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
!b
y <- Decoder s b
forall s. Decoder s b
forall a s. DecCBOR a => Decoder s a
decCBOR
!c
z <- Decoder s c
forall s. Decoder s c
forall a s. DecCBOR a => Decoder s a
decCBOR
(a, b, c) -> Decoder s (a, b, c)
forall a. a -> Decoder s a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (a
x, b
y, c
z)
dropCBOR :: forall s. Proxy (a, b, c) -> Decoder s ()
dropCBOR Proxy (a, b, c)
_ =
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
3
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy b -> Decoder s ()
forall s. Proxy b -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy c -> Decoder s ()
forall s. Proxy c -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
{-# INLINE decCBOR #-}
instance (DecCBOR a, DecCBOR b, DecCBOR c, DecCBOR d) => DecCBOR (a, b, c, d) where
decCBOR :: forall s. Decoder s (a, b, c, d)
decCBOR = do
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
4
!a
a <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
!b
b <- Decoder s b
forall s. Decoder s b
forall a s. DecCBOR a => Decoder s a
decCBOR
!c
c <- Decoder s c
forall s. Decoder s c
forall a s. DecCBOR a => Decoder s a
decCBOR
!d
d <- Decoder s d
forall s. Decoder s d
forall a s. DecCBOR a => Decoder s a
decCBOR
(a, b, c, d) -> Decoder s (a, b, c, d)
forall a. a -> Decoder s a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (a
a, b
b, c
c, d
d)
dropCBOR :: forall s. Proxy (a, b, c, d) -> Decoder s ()
dropCBOR Proxy (a, b, c, d)
_ =
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
4
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy b -> Decoder s ()
forall s. Proxy b -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy c -> Decoder s ()
forall s. Proxy c -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy d -> Decoder s ()
forall s. Proxy d -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @d)
{-# INLINE decCBOR #-}
instance
(DecCBOR a, DecCBOR b, DecCBOR c, DecCBOR d, DecCBOR e) =>
DecCBOR (a, b, c, d, e)
where
decCBOR :: forall s. Decoder s (a, b, c, d, e)
decCBOR = do
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
5
!a
a <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
!b
b <- Decoder s b
forall s. Decoder s b
forall a s. DecCBOR a => Decoder s a
decCBOR
!c
c <- Decoder s c
forall s. Decoder s c
forall a s. DecCBOR a => Decoder s a
decCBOR
!d
d <- Decoder s d
forall s. Decoder s d
forall a s. DecCBOR a => Decoder s a
decCBOR
!e
e <- Decoder s e
forall s. Decoder s e
forall a s. DecCBOR a => Decoder s a
decCBOR
(a, b, c, d, e) -> Decoder s (a, b, c, d, e)
forall a. a -> Decoder s a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (a
a, b
b, c
c, d
d, e
e)
dropCBOR :: forall s. Proxy (a, b, c, d, e) -> Decoder s ()
dropCBOR Proxy (a, b, c, d, e)
_ =
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
5
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy b -> Decoder s ()
forall s. Proxy b -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy c -> Decoder s ()
forall s. Proxy c -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy d -> Decoder s ()
forall s. Proxy d -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @d)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy e -> Decoder s ()
forall s. Proxy e -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @e)
{-# INLINE decCBOR #-}
instance
(DecCBOR a, DecCBOR b, DecCBOR c, DecCBOR d, DecCBOR e, DecCBOR f) =>
DecCBOR (a, b, c, d, e, f)
where
decCBOR :: forall s. Decoder s (a, b, c, d, e, f)
decCBOR = do
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
6
!a
a <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
!b
b <- Decoder s b
forall s. Decoder s b
forall a s. DecCBOR a => Decoder s a
decCBOR
!c
c <- Decoder s c
forall s. Decoder s c
forall a s. DecCBOR a => Decoder s a
decCBOR
!d
d <- Decoder s d
forall s. Decoder s d
forall a s. DecCBOR a => Decoder s a
decCBOR
!e
e <- Decoder s e
forall s. Decoder s e
forall a s. DecCBOR a => Decoder s a
decCBOR
!f
f <- Decoder s f
forall s. Decoder s f
forall a s. DecCBOR a => Decoder s a
decCBOR
(a, b, c, d, e, f) -> Decoder s (a, b, c, d, e, f)
forall a. a -> Decoder s a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (a
a, b
b, c
c, d
d, e
e, f
f)
dropCBOR :: forall s. Proxy (a, b, c, d, e, f) -> Decoder s ()
dropCBOR Proxy (a, b, c, d, e, f)
_ =
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
6
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy b -> Decoder s ()
forall s. Proxy b -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy c -> Decoder s ()
forall s. Proxy c -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy d -> Decoder s ()
forall s. Proxy d -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @d)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy e -> Decoder s ()
forall s. Proxy e -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @e)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy f -> Decoder s ()
forall s. Proxy f -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @f)
{-# INLINE decCBOR #-}
instance
( DecCBOR a
, DecCBOR b
, DecCBOR c
, DecCBOR d
, DecCBOR e
, DecCBOR f
, DecCBOR g
) =>
DecCBOR (a, b, c, d, e, f, g)
where
decCBOR :: forall s. Decoder s (a, b, c, d, e, f, g)
decCBOR = do
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
7
!a
a <- Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
!b
b <- Decoder s b
forall s. Decoder s b
forall a s. DecCBOR a => Decoder s a
decCBOR
!c
c <- Decoder s c
forall s. Decoder s c
forall a s. DecCBOR a => Decoder s a
decCBOR
!d
d <- Decoder s d
forall s. Decoder s d
forall a s. DecCBOR a => Decoder s a
decCBOR
!e
e <- Decoder s e
forall s. Decoder s e
forall a s. DecCBOR a => Decoder s a
decCBOR
!f
f <- Decoder s f
forall s. Decoder s f
forall a s. DecCBOR a => Decoder s a
decCBOR
!g
g <- Decoder s g
forall s. Decoder s g
forall a s. DecCBOR a => Decoder s a
decCBOR
(a, b, c, d, e, f, g) -> Decoder s (a, b, c, d, e, f, g)
forall a. a -> Decoder s a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (a
a, b
b, c
c, d
d, e
e, f
f, g
g)
dropCBOR :: forall s. Proxy (a, b, c, d, e, f, g) -> Decoder s ()
dropCBOR Proxy (a, b, c, d, e, f, g)
_ =
Int -> Decoder s ()
forall s. Int -> Decoder s ()
decodeListLenOf Int
7
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy b -> Decoder s ()
forall s. Proxy b -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @b)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy c -> Decoder s ()
forall s. Proxy c -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy d -> Decoder s ()
forall s. Proxy d -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @d)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy e -> Decoder s ()
forall s. Proxy e -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @e)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy f -> Decoder s ()
forall s. Proxy f -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @f)
Decoder s () -> Decoder s () -> Decoder s ()
forall a b. Decoder s a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* Proxy g -> Decoder s ()
forall s. Proxy g -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @g)
{-# INLINE decCBOR #-}
instance DecCBOR BS.ByteString where
decCBOR :: forall s. Decoder s ByteString
decCBOR = Decoder s ByteString
forall s. Decoder s ByteString
decodeBytes
{-# INLINE decCBOR #-}
instance DecCBOR T.Text where
decCBOR :: forall s. Decoder s Text
decCBOR = Decoder s Text
forall s. Decoder s Text
decodeString
{-# INLINE decCBOR #-}
instance DecCBOR BSL.ByteString where
decCBOR :: forall s. Decoder s ByteString
decCBOR = ByteString -> ByteString
BSL.fromStrict (ByteString -> ByteString)
-> Decoder s ByteString -> Decoder s ByteString
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s ByteString
forall s. Decoder s ByteString
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance DecCBOR ShortByteString where
decCBOR :: forall s. Decoder s ShortByteString
decCBOR = do
BA (Prim.ByteArray ByteArray#
ba) <- Decoder s ByteArray
forall s. Decoder s ByteArray
decodeByteArray
ShortByteString -> Decoder s ShortByteString
forall a. a -> Decoder s a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (ShortByteString -> Decoder s ShortByteString)
-> ShortByteString -> Decoder s ShortByteString
forall a b. (a -> b) -> a -> b
$ ByteArray# -> ShortByteString
SBS ByteArray#
ba
{-# INLINE decCBOR #-}
instance DecCBOR ByteArray where
decCBOR :: forall s. Decoder s ByteArray
decCBOR = Decoder s ByteArray
forall s. Decoder s ByteArray
decodeByteArray
{-# INLINE decCBOR #-}
instance DecCBOR Prim.ByteArray where
decCBOR :: forall s. Decoder s ByteArray
decCBOR = ByteArray -> ByteArray
unBA (ByteArray -> ByteArray)
-> Decoder s ByteArray -> Decoder s ByteArray
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s ByteArray
forall s. Decoder s ByteArray
decodeByteArray
{-# INLINE decCBOR #-}
instance DecCBOR SlicedByteArray where
decCBOR :: forall s. Decoder s SlicedByteArray
decCBOR = ByteArray -> SlicedByteArray
fromByteArray (ByteArray -> SlicedByteArray)
-> (ByteArray -> ByteArray) -> ByteArray -> SlicedByteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> ByteArray
unBA (ByteArray -> SlicedByteArray)
-> Decoder s ByteArray -> Decoder s SlicedByteArray
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s ByteArray
forall s. Decoder s ByteArray
decodeByteArray
{-# INLINE decCBOR #-}
instance DecCBOR a => DecCBOR [a] where
decCBOR :: forall s. Decoder s [a]
decCBOR = Decoder s a -> Decoder s [a]
forall s a. Decoder s a -> Decoder s [a]
decodeList Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance (DecCBOR a, DecCBOR b) => DecCBOR (Either a b) where
decCBOR :: forall s. Decoder s (Either a b)
decCBOR = Decoder s a -> Decoder s b -> Decoder s (Either a b)
forall s a b. Decoder s a -> Decoder s b -> Decoder s (Either a b)
decodeEither (Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s a -> (a -> Decoder s a) -> Decoder s a
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a -> a
a a -> Decoder s a -> Decoder s a
forall a b. a -> b -> b
`seq` a -> Decoder s a
forall a. a -> Decoder s a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure a
a) (Decoder s b
forall s. Decoder s b
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s b -> (b -> Decoder s b) -> Decoder s b
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= \b
a -> b
a b -> Decoder s b -> Decoder s b
forall a b. a -> b -> b
`seq` b -> Decoder s b
forall a. a -> Decoder s a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure b
a)
{-# INLINE decCBOR #-}
dropCBOR :: forall s. Proxy (Either a b) -> Decoder s ()
dropCBOR Proxy (Either a b)
_ = () () -> Decoder s (Either () ()) -> Decoder s ()
forall a b. a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ Decoder s () -> Decoder s () -> Decoder s (Either () ())
forall s a b. Decoder s a -> Decoder s b -> Decoder s (Either a b)
decodeEither (Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) (Proxy b -> Decoder s ()
forall s. Proxy b -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b))
instance DecCBOR a => DecCBOR (NonEmpty a) where
decCBOR :: forall s. Decoder s (NonEmpty a)
decCBOR = Decoder s a -> Decoder s (NonEmpty a)
forall s a. Decoder s a -> Decoder s (NonEmpty a)
decodeNonEmptyList Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance DecCBOR a => DecCBOR (Maybe a) where
decCBOR :: forall s. Decoder s (Maybe a)
decCBOR = Decoder s a -> Decoder s (Maybe a)
forall s a. Decoder s a -> Decoder s (Maybe a)
decodeMaybe Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
dropCBOR :: forall s. Proxy (Maybe a) -> Decoder s ()
dropCBOR Proxy (Maybe a)
_ = () () -> Decoder s (Maybe ()) -> Decoder s ()
forall a b. a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ Decoder s () -> Decoder s (Maybe ())
forall s a. Decoder s a -> Decoder s (Maybe a)
decodeMaybe (Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a))
instance DecCBOR a => DecCBOR (SMaybe.StrictMaybe a) where
decCBOR :: forall s. Decoder s (StrictMaybe a)
decCBOR = Decoder s a -> Decoder s (StrictMaybe a)
forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeStrictMaybe Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
dropCBOR :: forall s. Proxy (StrictMaybe a) -> Decoder s ()
dropCBOR Proxy (StrictMaybe a)
_ = () () -> Decoder s (StrictMaybe ()) -> Decoder s ()
forall a b. a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ Decoder s () -> Decoder s (StrictMaybe ())
forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeStrictMaybe (Proxy a -> Decoder s ()
forall s. Proxy a -> Decoder s ()
forall a s. DecCBOR a => Proxy a -> Decoder s ()
dropCBOR (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a))
instance DecCBOR a => DecCBOR (SSeq.StrictSeq a) where
decCBOR :: forall s. Decoder s (StrictSeq a)
decCBOR = Decoder s a -> Decoder s (StrictSeq a)
forall s a. Decoder s a -> Decoder s (StrictSeq a)
decodeStrictSeq Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance DecCBOR a => DecCBOR (Seq.Seq a) where
decCBOR :: forall s. Decoder s (Seq a)
decCBOR = Decoder s a -> Decoder s (Seq a)
forall s a. Decoder s a -> Decoder s (Seq a)
decodeSeq Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance (Ord a, DecCBOR a) => DecCBOR (Set.Set a) where
decCBOR :: forall s. Decoder s (Set a)
decCBOR = Decoder s a -> Decoder s (Set a)
forall a s. Ord a => Decoder s a -> Decoder s (Set a)
decodeSet Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance (Ord k, DecCBOR k, DecCBOR v) => DecCBOR (Map.Map k v) where
decCBOR :: forall s. Decoder s (Map k v)
decCBOR = Decoder s k -> Decoder s v -> Decoder s (Map k v)
forall k s v.
Ord k =>
Decoder s k -> Decoder s v -> Decoder s (Map k v)
decodeMap Decoder s k
forall s. Decoder s k
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s v
forall s. Decoder s v
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance DecCBOR v => DecCBOR (IntMap.IntMap v) where
decCBOR :: forall s. Decoder s (IntMap v)
decCBOR = Decoder s v -> Decoder s (IntMap v)
forall s v. Decoder s v -> Decoder s (IntMap v)
decodeIntMap Decoder s v
forall s. Decoder s v
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance
( Ord k
, DecCBOR k
, DecCBOR a
, Typeable kv
, Typeable av
, VMap.Vector kv k
, VMap.Vector av a
) =>
DecCBOR (VMap.VMap kv av k a)
where
decCBOR :: forall s. Decoder s (VMap kv av k a)
decCBOR = Decoder s k -> Decoder s a -> Decoder s (VMap kv av k a)
forall (kv :: Type -> Type) k (vv :: Type -> Type) v s.
(Vector kv k, Vector vv v, Ord k) =>
Decoder s k -> Decoder s v -> Decoder s (VMap kv vv k v)
decodeVMap Decoder s k
forall s. Decoder s k
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance DecCBOR a => DecCBOR (V.Vector a) where
decCBOR :: forall s. Decoder s (Vector a)
decCBOR = Decoder s a -> Decoder s (Vector a)
forall (vec :: Type -> Type) a s.
Vector vec a =>
Decoder s a -> Decoder s (vec a)
decodeVector Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance (DecCBOR a, VP.Prim a) => DecCBOR (VP.Vector a) where
decCBOR :: forall s. Decoder s (Vector a)
decCBOR = Decoder s a -> Decoder s (Vector a)
forall (vec :: Type -> Type) a s.
Vector vec a =>
Decoder s a -> Decoder s (vec a)
decodeVector Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance (DecCBOR a, VS.Storable a) => DecCBOR (VS.Vector a) where
decCBOR :: forall s. Decoder s (Vector a)
decCBOR = Decoder s a -> Decoder s (Vector a)
forall (vec :: Type -> Type) a s.
Vector vec a =>
Decoder s a -> Decoder s (vec a)
decodeVector Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance (DecCBOR a, VU.Unbox a) => DecCBOR (VU.Vector a) where
decCBOR :: forall s. Decoder s (Vector a)
decCBOR = Decoder s a -> Decoder s (Vector a)
forall (vec :: Type -> Type) a s.
Vector vec a =>
Decoder s a -> Decoder s (vec a)
decodeVector Decoder s a
forall s. Decoder s a
forall a s. DecCBOR a => Decoder s a
decCBOR
{-# INLINE decCBOR #-}
instance DecCBOR UTCTime where
decCBOR :: forall s. Decoder s UTCTime
decCBOR = Decoder s UTCTime
forall s. Decoder s UTCTime
decodeUTCTime
{-# INLINE decCBOR #-}
instance DSIGNAlgorithm v => DecCBOR (VerKeyDSIGN v) where
decCBOR :: forall s. Decoder s (VerKeyDSIGN v)
decCBOR = Decoder s (VerKeyDSIGN v)
forall v s. DSIGNAlgorithm v => Decoder s (VerKeyDSIGN v)
decodeVerKeyDSIGN
{-# INLINE decCBOR #-}
instance DSIGNAlgorithm v => DecCBOR (SignKeyDSIGN v) where
decCBOR :: forall s. Decoder s (SignKeyDSIGN v)
decCBOR = Decoder s (SignKeyDSIGN v)
forall v s. DSIGNAlgorithm v => Decoder s (SignKeyDSIGN v)
decodeSignKeyDSIGN
{-# INLINE decCBOR #-}
instance DSIGNAlgorithm v => DecCBOR (SigDSIGN v) where
decCBOR :: forall s. Decoder s (SigDSIGN v)
decCBOR = Decoder s (SigDSIGN v)
forall v s. DSIGNAlgorithm v => Decoder s (SigDSIGN v)
decodeSigDSIGN
{-# INLINE decCBOR #-}
instance (DSIGNAlgorithm v, Typeable a) => DecCBOR (SignedDSIGN v a) where
decCBOR :: forall s. Decoder s (SignedDSIGN v a)
decCBOR = Decoder s (SignedDSIGN v a)
forall v s a. DSIGNAlgorithm v => Decoder s (SignedDSIGN v a)
decodeSignedDSIGN
{-# INLINE decCBOR #-}
instance (HashAlgorithm h, Typeable a) => DecCBOR (Hash h a)
instance KESAlgorithm k => DecCBOR (VerKeyKES k) where
decCBOR :: forall s. Decoder s (VerKeyKES k)
decCBOR = Decoder s (VerKeyKES k)
forall v s. KESAlgorithm v => Decoder s (VerKeyKES v)
decodeVerKeyKES
{-# INLINE decCBOR #-}
instance KESAlgorithm k => DecCBOR (SigKES k) where
decCBOR :: forall s. Decoder s (SigKES k)
decCBOR = Decoder s (SigKES k)
forall v s. KESAlgorithm v => Decoder s (SigKES v)
decodeSigKES
{-# INLINE decCBOR #-}
instance DecCBOR (VerKeyVRF SimpleVRF) where
decCBOR :: forall s. Decoder s (VerKeyVRF SimpleVRF)
decCBOR = Decoder s (VerKeyVRF SimpleVRF)
forall v s. VRFAlgorithm v => Decoder s (VerKeyVRF v)
decodeVerKeyVRF
{-# INLINE decCBOR #-}
instance DecCBOR (SignKeyVRF SimpleVRF) where
decCBOR :: forall s. Decoder s (SignKeyVRF SimpleVRF)
decCBOR = Decoder s (SignKeyVRF SimpleVRF)
forall v s. VRFAlgorithm v => Decoder s (SignKeyVRF v)
decodeSignKeyVRF
{-# INLINE decCBOR #-}
instance DecCBOR (CertVRF SimpleVRF) where
decCBOR :: forall s. Decoder s (CertVRF SimpleVRF)
decCBOR = Decoder s (CertVRF SimpleVRF)
forall v s. VRFAlgorithm v => Decoder s (CertVRF v)
decodeCertVRF
{-# INLINE decCBOR #-}
instance DecCBOR (VerKeyVRF MockVRF) where
decCBOR :: forall s. Decoder s (VerKeyVRF MockVRF)
decCBOR = Decoder s (VerKeyVRF MockVRF)
forall v s. VRFAlgorithm v => Decoder s (VerKeyVRF v)
decodeVerKeyVRF
{-# INLINE decCBOR #-}
instance DecCBOR (SignKeyVRF MockVRF) where
decCBOR :: forall s. Decoder s (SignKeyVRF MockVRF)
decCBOR = Decoder s (SignKeyVRF MockVRF)
forall v s. VRFAlgorithm v => Decoder s (SignKeyVRF v)
decodeSignKeyVRF
{-# INLINE decCBOR #-}
instance DecCBOR (CertVRF MockVRF) where
decCBOR :: forall s. Decoder s (CertVRF MockVRF)
decCBOR = Decoder s (CertVRF MockVRF)
forall v s. VRFAlgorithm v => Decoder s (CertVRF v)
decodeCertVRF
{-# INLINE decCBOR #-}
instance DecCBOR Praos.Proof where
decCBOR :: forall s. Decoder s Proof
decCBOR = Decoder s ByteString
forall s. Decoder s ByteString
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s ByteString
-> (ByteString -> Decoder s Proof) -> Decoder s Proof
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> Decoder s Proof
forall (m :: Type -> Type). MonadFail m => ByteString -> m Proof
Praos.proofFromBytes
{-# INLINE decCBOR #-}
instance DecCBOR Praos.SignKey where
decCBOR :: forall s. Decoder s SignKey
decCBOR = Decoder s ByteString
forall s. Decoder s ByteString
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s ByteString
-> (ByteString -> Decoder s SignKey) -> Decoder s SignKey
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> Decoder s SignKey
forall (m :: Type -> Type). MonadFail m => ByteString -> m SignKey
Praos.skFromBytes
{-# INLINE decCBOR #-}
instance DecCBOR Praos.VerKey where
decCBOR :: forall s. Decoder s VerKey
decCBOR = Decoder s ByteString
forall s. Decoder s ByteString
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s ByteString
-> (ByteString -> Decoder s VerKey) -> Decoder s VerKey
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> Decoder s VerKey
forall (m :: Type -> Type). MonadFail m => ByteString -> m VerKey
Praos.vkFromBytes
{-# INLINE decCBOR #-}
deriving instance DecCBOR (VerKeyVRF Praos.PraosVRF)
deriving instance DecCBOR (SignKeyVRF Praos.PraosVRF)
deriving instance DecCBOR (CertVRF Praos.PraosVRF)
deriving instance Typeable v => DecCBOR (OutputVRF v)
instance (VRFAlgorithm v, Typeable a) => DecCBOR (CertifiedVRF v a) where
decCBOR :: forall s. Decoder s (CertifiedVRF v a)
decCBOR =
OutputVRF v -> CertVRF v -> CertifiedVRF v a
forall v a. OutputVRF v -> CertVRF v -> CertifiedVRF v a
CertifiedVRF
(OutputVRF v -> CertVRF v -> CertifiedVRF v a)
-> Decoder s ()
-> Decoder s (OutputVRF v -> CertVRF v -> CertifiedVRF v a)
forall a b. a -> Decoder s b -> Decoder s a
forall (f :: Type -> Type) a b. Functor f => a -> f b -> f a
<$ Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"CertifiedVRF" Int
2
Decoder s (OutputVRF v -> CertVRF v -> CertifiedVRF v a)
-> Decoder s (OutputVRF v)
-> Decoder s (CertVRF v -> CertifiedVRF v a)
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Decoder s (OutputVRF v)
forall s. Decoder s (OutputVRF v)
forall a s. DecCBOR a => Decoder s a
decCBOR
Decoder s (CertVRF v -> CertifiedVRF v a)
-> Decoder s (CertVRF v) -> Decoder s (CertifiedVRF v a)
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Decoder s (CertVRF v)
forall v s. VRFAlgorithm v => Decoder s (CertVRF v)
decodeCertVRF
{-# INLINE decCBOR #-}
instance DecCBOR SlotNo where
decCBOR :: forall s. Decoder s SlotNo
decCBOR = Decoder s SlotNo -> Decoder s SlotNo
forall s a. Decoder s a -> Decoder s a
fromPlainDecoder Decoder s SlotNo
forall s. Decoder s SlotNo
forall a s. Serialise a => Decoder s a
Serialise.decode
{-# INLINE decCBOR #-}
instance (Serialise.Serialise t, Typeable t) => DecCBOR (WithOrigin t) where
decCBOR :: forall s. Decoder s (WithOrigin t)
decCBOR = Decoder s (WithOrigin t) -> Decoder s (WithOrigin t)
forall s a. Decoder s a -> Decoder s a
fromPlainDecoder Decoder s (WithOrigin t)
forall s. Decoder s (WithOrigin t)
forall a s. Serialise a => Decoder s a
Serialise.decode
{-# INLINE decCBOR #-}
deriving instance DecCBOR EpochNo
deriving instance DecCBOR EpochSize
deriving instance DecCBOR SystemStart
instance DecCBOR BlockNo where
decCBOR :: forall s. Decoder s BlockNo
decCBOR = Decoder s BlockNo -> Decoder s BlockNo
forall s a. Decoder s a -> Decoder s a
fromPlainDecoder Decoder s BlockNo
forall s. Decoder s BlockNo
forall a s. Serialise a => Decoder s a
decode
{-# INLINE decCBOR #-}
deriving instance DecCBOR EpochInterval
instance DecCBOR PV1.Data where
decCBOR :: forall s. Decoder s Data
decCBOR = Decoder s Data -> Decoder s Data
forall s a. Decoder s a -> Decoder s a
fromPlainDecoder Decoder s Data
forall s. Decoder s Data
forall a s. Serialise a => Decoder s a
decode
{-# INLINE decCBOR #-}
instance DecCBOR PV1.ScriptContext where
decCBOR :: forall s. Decoder s ScriptContext
decCBOR = Decoder s Data
forall s. Decoder s Data
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s Data
-> (Data -> Decoder s ScriptContext) -> Decoder s ScriptContext
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= Data -> Decoder s ScriptContext
forall a (m :: Type -> Type).
(FromData a, MonadFail m) =>
Data -> m a
decodeScriptContextFromData
instance DecCBOR PV2.ScriptContext where
decCBOR :: forall s. Decoder s ScriptContext
decCBOR = Decoder s Data
forall s. Decoder s Data
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s Data
-> (Data -> Decoder s ScriptContext) -> Decoder s ScriptContext
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= Data -> Decoder s ScriptContext
forall a (m :: Type -> Type).
(FromData a, MonadFail m) =>
Data -> m a
decodeScriptContextFromData
instance DecCBOR PV3.ScriptContext where
decCBOR :: forall s. Decoder s ScriptContext
decCBOR = Decoder s Data
forall s. Decoder s Data
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s Data
-> (Data -> Decoder s ScriptContext) -> Decoder s ScriptContext
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= Data -> Decoder s ScriptContext
forall a (m :: Type -> Type).
(FromData a, MonadFail m) =>
Data -> m a
decodeScriptContextFromData
decodeScriptContextFromData :: (PV3.FromData a, MonadFail m) => PV3.Data -> m a
decodeScriptContextFromData :: forall a (m :: Type -> Type).
(FromData a, MonadFail m) =>
Data -> m a
decodeScriptContextFromData Data
scriptContextData =
case Data -> Maybe a
forall a. FromData a => Data -> Maybe a
PV3.fromData Data
scriptContextData of
Maybe a
Nothing -> String -> m a
forall a. String -> m a
forall (m :: Type -> Type) a. MonadFail m => String -> m a
fail (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"ScriptContext cannot be decoded from Data: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Data -> String
forall a. Show a => a -> String
show Data
scriptContextData
Just a
scriptContext -> a -> m a
forall a. a -> m a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure a
scriptContext