{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Cardano.Api.Serialise.TextEnvelope.Internal
( HasTextEnvelope (..)
, textEnvelopeTypeInEra
, TextEnvelope (..)
, TextEnvelopeType (..)
, TextEnvelopeDescr (..)
, textEnvelopeRawCBOR
, TextEnvelopeError (..)
, serialiseToTextEnvelope
, deserialiseFromTextEnvelope
, readFileTextEnvelope
, writeFileTextEnvelope
, readTextEnvelopeFromFile
, readTextEnvelopeOfTypeFromFile
, textEnvelopeToJSON
, serialiseTextEnvelope
, legacyComparison
, textEnvelopeTypeToEra
, FromSomeType (..)
, deserialiseFromTextEnvelopeAnyOf
, readFileTextEnvelopeAnyOf
, AsType (..)
)
where
import Cardano.Api.Era
import Cardano.Api.Error
import Cardano.Api.HasTypeProxy
import Cardano.Api.IO
import Cardano.Api.Internal.Orphans ()
import Cardano.Api.Pretty
import Cardano.Api.Serialise.Cbor
import Cardano.Binary (DecoderError)
import Control.Monad (unless)
import Control.Monad.Trans.Except (ExceptT (..), runExceptT)
import Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither)
import Data.Aeson (FromJSON (..), ToJSON (..), object, withObject, (.:), (.=))
import Data.Aeson qualified as Aeson
import Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', keyOrder)
import Data.Bifunctor (first)
import Data.ByteString (ByteString)
import Data.ByteString.Base16 qualified as Base16
import Data.ByteString.Lazy qualified as LBS
import Data.Data (Data)
import Data.List qualified as List
import Data.Maybe (fromMaybe)
import Data.String (IsString)
import Data.Text (Text)
import Data.Text.Encoding qualified as Text
newtype TextEnvelopeType = TextEnvelopeType String
deriving (TextEnvelopeType -> TextEnvelopeType -> Bool
(TextEnvelopeType -> TextEnvelopeType -> Bool)
-> (TextEnvelopeType -> TextEnvelopeType -> Bool)
-> Eq TextEnvelopeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextEnvelopeType -> TextEnvelopeType -> Bool
== :: TextEnvelopeType -> TextEnvelopeType -> Bool
$c/= :: TextEnvelopeType -> TextEnvelopeType -> Bool
/= :: TextEnvelopeType -> TextEnvelopeType -> Bool
Eq, Int -> TextEnvelopeType -> ShowS
[TextEnvelopeType] -> ShowS
TextEnvelopeType -> String
(Int -> TextEnvelopeType -> ShowS)
-> (TextEnvelopeType -> String)
-> ([TextEnvelopeType] -> ShowS)
-> Show TextEnvelopeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextEnvelopeType -> ShowS
showsPrec :: Int -> TextEnvelopeType -> ShowS
$cshow :: TextEnvelopeType -> String
show :: TextEnvelopeType -> String
$cshowList :: [TextEnvelopeType] -> ShowS
showList :: [TextEnvelopeType] -> ShowS
Show, Typeable TextEnvelopeType
Typeable TextEnvelopeType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeType -> c TextEnvelopeType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeType)
-> (TextEnvelopeType -> Constr)
-> (TextEnvelopeType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeType))
-> ((forall b. Data b => b -> b)
-> TextEnvelopeType -> TextEnvelopeType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r)
-> (forall u.
(forall d. Data d => d -> u) -> TextEnvelopeType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType)
-> Data TextEnvelopeType
TextEnvelopeType -> Constr
TextEnvelopeType -> DataType
(forall b. Data b => b -> b)
-> TextEnvelopeType -> TextEnvelopeType
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeType -> u
forall u. (forall d. Data d => d -> u) -> TextEnvelopeType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeType -> c TextEnvelopeType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeType -> c TextEnvelopeType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeType -> c TextEnvelopeType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeType
$ctoConstr :: TextEnvelopeType -> Constr
toConstr :: TextEnvelopeType -> Constr
$cdataTypeOf :: TextEnvelopeType -> DataType
dataTypeOf :: TextEnvelopeType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeType)
$cgmapT :: (forall b. Data b => b -> b)
-> TextEnvelopeType -> TextEnvelopeType
gmapT :: (forall b. Data b => b -> b)
-> TextEnvelopeType -> TextEnvelopeType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TextEnvelopeType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TextEnvelopeType -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeType -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeType -> m TextEnvelopeType
Data)
deriving newtype (String -> TextEnvelopeType
(String -> TextEnvelopeType) -> IsString TextEnvelopeType
forall a. (String -> a) -> IsString a
$cfromString :: String -> TextEnvelopeType
fromString :: String -> TextEnvelopeType
IsString, NonEmpty TextEnvelopeType -> TextEnvelopeType
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
(TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType)
-> (NonEmpty TextEnvelopeType -> TextEnvelopeType)
-> (forall b.
Integral b =>
b -> TextEnvelopeType -> TextEnvelopeType)
-> Semigroup TextEnvelopeType
forall b. Integral b => b -> TextEnvelopeType -> TextEnvelopeType
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
<> :: TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
$csconcat :: NonEmpty TextEnvelopeType -> TextEnvelopeType
sconcat :: NonEmpty TextEnvelopeType -> TextEnvelopeType
$cstimes :: forall b. Integral b => b -> TextEnvelopeType -> TextEnvelopeType
stimes :: forall b. Integral b => b -> TextEnvelopeType -> TextEnvelopeType
Semigroup, [TextEnvelopeType] -> Value
[TextEnvelopeType] -> Encoding
TextEnvelopeType -> Bool
TextEnvelopeType -> Value
TextEnvelopeType -> Encoding
(TextEnvelopeType -> Value)
-> (TextEnvelopeType -> Encoding)
-> ([TextEnvelopeType] -> Value)
-> ([TextEnvelopeType] -> Encoding)
-> (TextEnvelopeType -> Bool)
-> ToJSON TextEnvelopeType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: TextEnvelopeType -> Value
toJSON :: TextEnvelopeType -> Value
$ctoEncoding :: TextEnvelopeType -> Encoding
toEncoding :: TextEnvelopeType -> Encoding
$ctoJSONList :: [TextEnvelopeType] -> Value
toJSONList :: [TextEnvelopeType] -> Value
$ctoEncodingList :: [TextEnvelopeType] -> Encoding
toEncodingList :: [TextEnvelopeType] -> Encoding
$comitField :: TextEnvelopeType -> Bool
omitField :: TextEnvelopeType -> Bool
ToJSON, Maybe TextEnvelopeType
Value -> Parser [TextEnvelopeType]
Value -> Parser TextEnvelopeType
(Value -> Parser TextEnvelopeType)
-> (Value -> Parser [TextEnvelopeType])
-> Maybe TextEnvelopeType
-> FromJSON TextEnvelopeType
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser TextEnvelopeType
parseJSON :: Value -> Parser TextEnvelopeType
$cparseJSONList :: Value -> Parser [TextEnvelopeType]
parseJSONList :: Value -> Parser [TextEnvelopeType]
$comittedField :: Maybe TextEnvelopeType
omittedField :: Maybe TextEnvelopeType
FromJSON)
newtype TextEnvelopeDescr = TextEnvelopeDescr String
deriving (TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
(TextEnvelopeDescr -> TextEnvelopeDescr -> Bool)
-> (TextEnvelopeDescr -> TextEnvelopeDescr -> Bool)
-> Eq TextEnvelopeDescr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
== :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
$c/= :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
/= :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
Eq, Int -> TextEnvelopeDescr -> ShowS
[TextEnvelopeDescr] -> ShowS
TextEnvelopeDescr -> String
(Int -> TextEnvelopeDescr -> ShowS)
-> (TextEnvelopeDescr -> String)
-> ([TextEnvelopeDescr] -> ShowS)
-> Show TextEnvelopeDescr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextEnvelopeDescr -> ShowS
showsPrec :: Int -> TextEnvelopeDescr -> ShowS
$cshow :: TextEnvelopeDescr -> String
show :: TextEnvelopeDescr -> String
$cshowList :: [TextEnvelopeDescr] -> ShowS
showList :: [TextEnvelopeDescr] -> ShowS
Show, Typeable TextEnvelopeDescr
Typeable TextEnvelopeDescr =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TextEnvelopeDescr
-> c TextEnvelopeDescr)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeDescr)
-> (TextEnvelopeDescr -> Constr)
-> (TextEnvelopeDescr -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeDescr))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeDescr))
-> ((forall b. Data b => b -> b)
-> TextEnvelopeDescr -> TextEnvelopeDescr)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r)
-> (forall u.
(forall d. Data d => d -> u) -> TextEnvelopeDescr -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeDescr -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr)
-> Data TextEnvelopeDescr
TextEnvelopeDescr -> Constr
TextEnvelopeDescr -> DataType
(forall b. Data b => b -> b)
-> TextEnvelopeDescr -> TextEnvelopeDescr
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeDescr -> u
forall u. (forall d. Data d => d -> u) -> TextEnvelopeDescr -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeDescr
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeDescr -> c TextEnvelopeDescr
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeDescr)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeDescr)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeDescr -> c TextEnvelopeDescr
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeDescr -> c TextEnvelopeDescr
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeDescr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeDescr
$ctoConstr :: TextEnvelopeDescr -> Constr
toConstr :: TextEnvelopeDescr -> Constr
$cdataTypeOf :: TextEnvelopeDescr -> DataType
dataTypeOf :: TextEnvelopeDescr -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeDescr)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeDescr)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeDescr)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeDescr)
$cgmapT :: (forall b. Data b => b -> b)
-> TextEnvelopeDescr -> TextEnvelopeDescr
gmapT :: (forall b. Data b => b -> b)
-> TextEnvelopeDescr -> TextEnvelopeDescr
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TextEnvelopeDescr -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TextEnvelopeDescr -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeDescr -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeDescr -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeDescr -> m TextEnvelopeDescr
Data)
deriving newtype (String -> TextEnvelopeDescr
(String -> TextEnvelopeDescr) -> IsString TextEnvelopeDescr
forall a. (String -> a) -> IsString a
$cfromString :: String -> TextEnvelopeDescr
fromString :: String -> TextEnvelopeDescr
IsString, NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr
TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr
(TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr)
-> (NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr)
-> (forall b.
Integral b =>
b -> TextEnvelopeDescr -> TextEnvelopeDescr)
-> Semigroup TextEnvelopeDescr
forall b. Integral b => b -> TextEnvelopeDescr -> TextEnvelopeDescr
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr
<> :: TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr
$csconcat :: NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr
sconcat :: NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr
$cstimes :: forall b. Integral b => b -> TextEnvelopeDescr -> TextEnvelopeDescr
stimes :: forall b. Integral b => b -> TextEnvelopeDescr -> TextEnvelopeDescr
Semigroup, [TextEnvelopeDescr] -> Value
[TextEnvelopeDescr] -> Encoding
TextEnvelopeDescr -> Bool
TextEnvelopeDescr -> Value
TextEnvelopeDescr -> Encoding
(TextEnvelopeDescr -> Value)
-> (TextEnvelopeDescr -> Encoding)
-> ([TextEnvelopeDescr] -> Value)
-> ([TextEnvelopeDescr] -> Encoding)
-> (TextEnvelopeDescr -> Bool)
-> ToJSON TextEnvelopeDescr
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: TextEnvelopeDescr -> Value
toJSON :: TextEnvelopeDescr -> Value
$ctoEncoding :: TextEnvelopeDescr -> Encoding
toEncoding :: TextEnvelopeDescr -> Encoding
$ctoJSONList :: [TextEnvelopeDescr] -> Value
toJSONList :: [TextEnvelopeDescr] -> Value
$ctoEncodingList :: [TextEnvelopeDescr] -> Encoding
toEncodingList :: [TextEnvelopeDescr] -> Encoding
$comitField :: TextEnvelopeDescr -> Bool
omitField :: TextEnvelopeDescr -> Bool
ToJSON, Maybe TextEnvelopeDescr
Value -> Parser [TextEnvelopeDescr]
Value -> Parser TextEnvelopeDescr
(Value -> Parser TextEnvelopeDescr)
-> (Value -> Parser [TextEnvelopeDescr])
-> Maybe TextEnvelopeDescr
-> FromJSON TextEnvelopeDescr
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser TextEnvelopeDescr
parseJSON :: Value -> Parser TextEnvelopeDescr
$cparseJSONList :: Value -> Parser [TextEnvelopeDescr]
parseJSONList :: Value -> Parser [TextEnvelopeDescr]
$comittedField :: Maybe TextEnvelopeDescr
omittedField :: Maybe TextEnvelopeDescr
FromJSON)
data TextEnvelope = TextEnvelope
{ TextEnvelope -> TextEnvelopeType
teType :: !TextEnvelopeType
, TextEnvelope -> TextEnvelopeDescr
teDescription :: !TextEnvelopeDescr
, TextEnvelope -> ByteString
teRawCBOR :: !ByteString
}
deriving (TextEnvelope -> TextEnvelope -> Bool
(TextEnvelope -> TextEnvelope -> Bool)
-> (TextEnvelope -> TextEnvelope -> Bool) -> Eq TextEnvelope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextEnvelope -> TextEnvelope -> Bool
== :: TextEnvelope -> TextEnvelope -> Bool
$c/= :: TextEnvelope -> TextEnvelope -> Bool
/= :: TextEnvelope -> TextEnvelope -> Bool
Eq, Int -> TextEnvelope -> ShowS
[TextEnvelope] -> ShowS
TextEnvelope -> String
(Int -> TextEnvelope -> ShowS)
-> (TextEnvelope -> String)
-> ([TextEnvelope] -> ShowS)
-> Show TextEnvelope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextEnvelope -> ShowS
showsPrec :: Int -> TextEnvelope -> ShowS
$cshow :: TextEnvelope -> String
show :: TextEnvelope -> String
$cshowList :: [TextEnvelope] -> ShowS
showList :: [TextEnvelope] -> ShowS
Show)
instance HasTypeProxy TextEnvelope where
data AsType TextEnvelope = AsTextEnvelope
proxyToAsType :: Proxy TextEnvelope -> AsType TextEnvelope
proxyToAsType Proxy TextEnvelope
_ = AsType TextEnvelope
AsTextEnvelope
instance ToJSON TextEnvelope where
toJSON :: TextEnvelope -> Value
toJSON TextEnvelope{TextEnvelopeType
teType :: TextEnvelope -> TextEnvelopeType
teType :: TextEnvelopeType
teType, TextEnvelopeDescr
teDescription :: TextEnvelope -> TextEnvelopeDescr
teDescription :: TextEnvelopeDescr
teDescription, ByteString
teRawCBOR :: TextEnvelope -> ByteString
teRawCBOR :: ByteString
teRawCBOR} =
[Pair] -> Value
object
[ Key
"type" Key -> TextEnvelopeType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TextEnvelopeType
teType
, Key
"description" Key -> TextEnvelopeDescr -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TextEnvelopeDescr
teDescription
, Key
"cborHex" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ByteString -> Text
Text.decodeUtf8 (ByteString -> ByteString
Base16.encode ByteString
teRawCBOR)
]
instance FromJSON TextEnvelope where
parseJSON :: Value -> Parser TextEnvelope
parseJSON = String
-> (Object -> Parser TextEnvelope) -> Value -> Parser TextEnvelope
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TextEnvelope" ((Object -> Parser TextEnvelope) -> Value -> Parser TextEnvelope)
-> (Object -> Parser TextEnvelope) -> Value -> Parser TextEnvelope
forall a b. (a -> b) -> a -> b
$ \Object
v ->
TextEnvelopeType -> TextEnvelopeDescr -> ByteString -> TextEnvelope
TextEnvelope
(TextEnvelopeType
-> TextEnvelopeDescr -> ByteString -> TextEnvelope)
-> Parser TextEnvelopeType
-> Parser (TextEnvelopeDescr -> ByteString -> TextEnvelope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
v Object -> Key -> Parser TextEnvelopeType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type")
Parser (TextEnvelopeDescr -> ByteString -> TextEnvelope)
-> Parser TextEnvelopeDescr -> Parser (ByteString -> TextEnvelope)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Key -> Parser TextEnvelopeDescr
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description")
Parser (ByteString -> TextEnvelope)
-> Parser ByteString -> Parser TextEnvelope
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Value -> Parser ByteString
parseJSONBase16 (Value -> Parser ByteString) -> Parser Value -> Parser ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cborHex")
where
parseJSONBase16 :: Value -> Parser ByteString
parseJSONBase16 Value
v =
(String -> Parser ByteString)
-> (ByteString -> Parser ByteString)
-> Either String ByteString
-> Parser ByteString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Parser ByteString
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail ByteString -> Parser ByteString
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String ByteString -> Parser ByteString)
-> (Text -> Either String ByteString) -> Text -> Parser ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
Base16.decode (ByteString -> Either String ByteString)
-> (Text -> ByteString) -> Text -> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8 (Text -> Parser ByteString) -> Parser Text -> Parser ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
textEnvelopeJsonConfig :: Config
textEnvelopeJsonConfig :: Config
textEnvelopeJsonConfig = Config
defConfig{confCompare = textEnvelopeJsonKeyOrder}
textEnvelopeJsonKeyOrder :: Text -> Text -> Ordering
textEnvelopeJsonKeyOrder :: Text -> Text -> Ordering
textEnvelopeJsonKeyOrder = [Text] -> Text -> Text -> Ordering
keyOrder [Text
"type", Text
"description", Text
"cborHex"]
textEnvelopeRawCBOR :: TextEnvelope -> ByteString
textEnvelopeRawCBOR :: TextEnvelope -> ByteString
textEnvelopeRawCBOR = TextEnvelope -> ByteString
teRawCBOR
data TextEnvelopeError
=
TextEnvelopeTypeError ![TextEnvelopeType] !TextEnvelopeType
| TextEnvelopeDecodeError !DecoderError
| TextEnvelopeAesonDecodeError !String
| TextEnvelopeUnknownKeyWitness !TextEnvelopeDescr
| TextEnvelopeUnknownType !Text
deriving (TextEnvelopeError -> TextEnvelopeError -> Bool
(TextEnvelopeError -> TextEnvelopeError -> Bool)
-> (TextEnvelopeError -> TextEnvelopeError -> Bool)
-> Eq TextEnvelopeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextEnvelopeError -> TextEnvelopeError -> Bool
== :: TextEnvelopeError -> TextEnvelopeError -> Bool
$c/= :: TextEnvelopeError -> TextEnvelopeError -> Bool
/= :: TextEnvelopeError -> TextEnvelopeError -> Bool
Eq, Int -> TextEnvelopeError -> ShowS
[TextEnvelopeError] -> ShowS
TextEnvelopeError -> String
(Int -> TextEnvelopeError -> ShowS)
-> (TextEnvelopeError -> String)
-> ([TextEnvelopeError] -> ShowS)
-> Show TextEnvelopeError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextEnvelopeError -> ShowS
showsPrec :: Int -> TextEnvelopeError -> ShowS
$cshow :: TextEnvelopeError -> String
show :: TextEnvelopeError -> String
$cshowList :: [TextEnvelopeError] -> ShowS
showList :: [TextEnvelopeError] -> ShowS
Show, Typeable TextEnvelopeError
Typeable TextEnvelopeError =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TextEnvelopeError
-> c TextEnvelopeError)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeError)
-> (TextEnvelopeError -> Constr)
-> (TextEnvelopeError -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeError))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeError))
-> ((forall b. Data b => b -> b)
-> TextEnvelopeError -> TextEnvelopeError)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r)
-> (forall u.
(forall d. Data d => d -> u) -> TextEnvelopeError -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeError -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError)
-> Data TextEnvelopeError
TextEnvelopeError -> Constr
TextEnvelopeError -> DataType
(forall b. Data b => b -> b)
-> TextEnvelopeError -> TextEnvelopeError
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeError -> u
forall u. (forall d. Data d => d -> u) -> TextEnvelopeError -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeError
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeError -> c TextEnvelopeError
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeError)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeError)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeError -> c TextEnvelopeError
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextEnvelopeError -> c TextEnvelopeError
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeError
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextEnvelopeError
$ctoConstr :: TextEnvelopeError -> Constr
toConstr :: TextEnvelopeError -> Constr
$cdataTypeOf :: TextEnvelopeError -> DataType
dataTypeOf :: TextEnvelopeError -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeError)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeError)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeError)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextEnvelopeError)
$cgmapT :: (forall b. Data b => b -> b)
-> TextEnvelopeError -> TextEnvelopeError
gmapT :: (forall b. Data b => b -> b)
-> TextEnvelopeError -> TextEnvelopeError
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TextEnvelopeError -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TextEnvelopeError -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeError -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TextEnvelopeError -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TextEnvelopeError -> m TextEnvelopeError
Data)
instance Error TextEnvelopeError where
prettyError :: forall ann. TextEnvelopeError -> Doc ann
prettyError = \case
TextEnvelopeTypeError [TextEnvelopeType String
expType] (TextEnvelopeType String
actType) ->
[Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat
[ Doc ann
"TextEnvelope type error: "
, Doc ann
" Expected: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
expType
, Doc ann
" Actual: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
actType
]
TextEnvelopeTypeError [TextEnvelopeType]
expTypes (TextEnvelopeType String
actType) ->
[Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat
[ Doc ann
"TextEnvelope type error: "
, Doc ann
" Expected one of: "
, [Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
List.intersperse Doc ann
", " [String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
expType | TextEnvelopeType String
expType <- [TextEnvelopeType]
expTypes]
, Doc ann
" Actual: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
actType
]
TextEnvelopeAesonDecodeError String
decErr ->
Doc ann
"TextEnvelope aeson decode error: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
decErr
TextEnvelopeDecodeError DecoderError
decErr ->
Doc ann
"TextEnvelope decode error: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> DecoderError -> Doc ann
forall a ann. Show a => a -> Doc ann
pshow DecoderError
decErr
TextEnvelopeUnknownKeyWitness TextEnvelopeDescr
desc ->
Doc ann
"Unknown key witness specified: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> TextEnvelopeDescr -> Doc ann
forall a ann. Show a => a -> Doc ann
pshow TextEnvelopeDescr
desc
TextEnvelopeUnknownType Text
unknownType ->
Doc ann
"Unknown TextEnvelope type: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Text -> Doc ann
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Text
unknownType
expectTextEnvelopeOfType :: TextEnvelopeType -> TextEnvelope -> Either TextEnvelopeError ()
expectTextEnvelopeOfType :: TextEnvelopeType -> TextEnvelope -> Either TextEnvelopeError ()
expectTextEnvelopeOfType TextEnvelopeType
expectedType TextEnvelope{teType :: TextEnvelope -> TextEnvelopeType
teType = TextEnvelopeType
actualType} =
Bool -> Either TextEnvelopeError () -> Either TextEnvelopeError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (TextEnvelopeType
expectedType TextEnvelopeType -> TextEnvelopeType -> Bool
`legacyComparison` TextEnvelopeType
actualType) (Either TextEnvelopeError () -> Either TextEnvelopeError ())
-> Either TextEnvelopeError () -> Either TextEnvelopeError ()
forall a b. (a -> b) -> a -> b
$
TextEnvelopeError -> Either TextEnvelopeError ()
forall a b. a -> Either a b
Left ([TextEnvelopeType] -> TextEnvelopeType -> TextEnvelopeError
TextEnvelopeTypeError [TextEnvelopeType
expectedType] TextEnvelopeType
actualType)
legacyComparison :: TextEnvelopeType -> TextEnvelopeType -> Bool
legacyComparison :: TextEnvelopeType -> TextEnvelopeType -> Bool
legacyComparison (TextEnvelopeType String
expectedType) (TextEnvelopeType String
actualType) =
case (String
expectedType, String
actualType) of
(String
"TxSignedShelley", String
"Witnessed Tx ShelleyEra") -> Bool
True
(String
"Tx AllegraEra", String
"Witnessed Tx AllegraEra") -> Bool
True
(String
"Tx MaryEra", String
"Witnessed Tx MaryEra") -> Bool
True
(String
"Tx AlonzoEra", String
"Witnessed Tx AlonzoEra") -> Bool
True
(String
"Tx BabbageEra", String
"Witnessed Tx BabbageEra") -> Bool
True
(String
"Tx ConwayEra", String
"Witnessed Tx ConwayEra") -> Bool
True
(String
"TxSignedShelley", String
"Unwitnessed Tx ShelleyEra") -> Bool
True
(String
"Tx AllegraEra", String
"Unwitnessed Tx AllegraEra") -> Bool
True
(String
"Tx MaryEra", String
"Unwitnessed Tx MaryEra") -> Bool
True
(String
"Tx AlonzoEra", String
"Unwitnessed Tx AlonzoEra") -> Bool
True
(String
"Tx BabbageEra", String
"Unwitnessed Tx BabbageEra") -> Bool
True
(String
"Tx ConwayEra", String
"Unwitnessed Tx ConwayEra") -> Bool
True
(String
expectedOther, String
expectedActual) -> String
expectedOther String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
expectedActual
class SerialiseAsCBOR a => HasTextEnvelope a where
textEnvelopeType :: AsType a -> TextEnvelopeType
textEnvelopeDefaultDescr :: a -> TextEnvelopeDescr
textEnvelopeDefaultDescr a
_ = TextEnvelopeDescr
""
textEnvelopeTypeInEra
:: ()
=> HasTextEnvelope (f era)
=> CardanoEra era
-> AsType (f era)
-> TextEnvelopeType
textEnvelopeTypeInEra :: forall (f :: * -> *) era.
HasTextEnvelope (f era) =>
CardanoEra era -> AsType (f era) -> TextEnvelopeType
textEnvelopeTypeInEra CardanoEra era
_ =
AsType (f era) -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType
serialiseToTextEnvelope
:: forall a
. HasTextEnvelope a
=> Maybe TextEnvelopeDescr -> a -> TextEnvelope
serialiseToTextEnvelope :: forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> TextEnvelope
serialiseToTextEnvelope Maybe TextEnvelopeDescr
mbDescr a
a =
TextEnvelope
{ teType :: TextEnvelopeType
teType = AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken
, teDescription :: TextEnvelopeDescr
teDescription = TextEnvelopeDescr -> Maybe TextEnvelopeDescr -> TextEnvelopeDescr
forall a. a -> Maybe a -> a
fromMaybe (a -> TextEnvelopeDescr
forall a. HasTextEnvelope a => a -> TextEnvelopeDescr
textEnvelopeDefaultDescr a
a) Maybe TextEnvelopeDescr
mbDescr
, teRawCBOR :: ByteString
teRawCBOR = a -> ByteString
forall a. SerialiseAsCBOR a => a -> ByteString
serialiseToCBOR a
a
}
where
ttoken :: AsType a
ttoken = AsType a
forall t. HasTypeProxy t => AsType t
asType :: AsType a
deserialiseFromTextEnvelope
:: forall a
. HasTextEnvelope a
=> TextEnvelope
-> Either TextEnvelopeError a
deserialiseFromTextEnvelope :: forall a.
HasTextEnvelope a =>
TextEnvelope -> Either TextEnvelopeError a
deserialiseFromTextEnvelope TextEnvelope
te = do
TextEnvelopeType -> TextEnvelope -> Either TextEnvelopeError ()
expectTextEnvelopeOfType (AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken) TextEnvelope
te
(DecoderError -> TextEnvelopeError)
-> Either DecoderError a -> Either TextEnvelopeError a
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first DecoderError -> TextEnvelopeError
TextEnvelopeDecodeError (Either DecoderError a -> Either TextEnvelopeError a)
-> Either DecoderError a -> Either TextEnvelopeError a
forall a b. (a -> b) -> a -> b
$
AsType a -> ByteString -> Either DecoderError a
forall a.
SerialiseAsCBOR a =>
AsType a -> ByteString -> Either DecoderError a
deserialiseFromCBOR AsType a
ttoken (TextEnvelope -> ByteString
teRawCBOR TextEnvelope
te)
where
ttoken :: AsType a
ttoken = AsType a
forall t. HasTypeProxy t => AsType t
asType :: AsType a
deserialiseFromTextEnvelopeAnyOf
:: [FromSomeType HasTextEnvelope b]
-> TextEnvelope
-> Either TextEnvelopeError b
deserialiseFromTextEnvelopeAnyOf :: forall b.
[FromSomeType HasTextEnvelope b]
-> TextEnvelope -> Either TextEnvelopeError b
deserialiseFromTextEnvelopeAnyOf [FromSomeType HasTextEnvelope b]
types TextEnvelope
te =
case (FromSomeType HasTextEnvelope b -> Bool)
-> [FromSomeType HasTextEnvelope b]
-> Maybe (FromSomeType HasTextEnvelope b)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
List.find FromSomeType HasTextEnvelope b -> Bool
matching [FromSomeType HasTextEnvelope b]
types of
Maybe (FromSomeType HasTextEnvelope b)
Nothing ->
TextEnvelopeError -> Either TextEnvelopeError b
forall a b. a -> Either a b
Left ([TextEnvelopeType] -> TextEnvelopeType -> TextEnvelopeError
TextEnvelopeTypeError [TextEnvelopeType]
expectedTypes TextEnvelopeType
actualType)
Just (FromSomeType AsType a
ttoken a -> b
f) ->
(DecoderError -> TextEnvelopeError)
-> Either DecoderError b -> Either TextEnvelopeError b
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first DecoderError -> TextEnvelopeError
TextEnvelopeDecodeError (Either DecoderError b -> Either TextEnvelopeError b)
-> Either DecoderError b -> Either TextEnvelopeError b
forall a b. (a -> b) -> a -> b
$
a -> b
f (a -> b) -> Either DecoderError a -> Either DecoderError b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsType a -> ByteString -> Either DecoderError a
forall a.
SerialiseAsCBOR a =>
AsType a -> ByteString -> Either DecoderError a
deserialiseFromCBOR AsType a
ttoken (TextEnvelope -> ByteString
teRawCBOR TextEnvelope
te)
where
actualType :: TextEnvelopeType
actualType = TextEnvelope -> TextEnvelopeType
teType TextEnvelope
te
expectedTypes :: [TextEnvelopeType]
expectedTypes =
[ AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken
| FromSomeType AsType a
ttoken a -> b
_f <- [FromSomeType HasTextEnvelope b]
types
]
matching :: FromSomeType HasTextEnvelope b -> Bool
matching (FromSomeType AsType a
ttoken a -> b
_f) = AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken TextEnvelopeType -> TextEnvelopeType -> Bool
`legacyComparison` TextEnvelopeType
actualType
writeFileTextEnvelope
:: HasTextEnvelope a
=> File content Out
-> Maybe TextEnvelopeDescr
-> a
-> IO (Either (FileError ()) ())
writeFileTextEnvelope :: forall a content.
HasTextEnvelope a =>
File content 'Out
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope File content 'Out
outputFile Maybe TextEnvelopeDescr
mbDescr a
a =
File content 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File content 'Out
outputFile (Maybe TextEnvelopeDescr -> a -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
mbDescr a
a)
textEnvelopeToJSON :: HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> LBS.ByteString
textEnvelopeToJSON :: forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
mbDescr a
a =
TextEnvelope -> ByteString
serialiseTextEnvelope (TextEnvelope -> ByteString) -> TextEnvelope -> ByteString
forall a b. (a -> b) -> a -> b
$ Maybe TextEnvelopeDescr -> a -> TextEnvelope
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> TextEnvelope
serialiseToTextEnvelope Maybe TextEnvelopeDescr
mbDescr a
a
serialiseTextEnvelope :: TextEnvelope -> LBS.ByteString
serialiseTextEnvelope :: TextEnvelope -> ByteString
serialiseTextEnvelope TextEnvelope
te = Config -> TextEnvelope -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
encodePretty' Config
textEnvelopeJsonConfig TextEnvelope
te ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"\n"
readFileTextEnvelope
:: HasTextEnvelope a
=> File content In
-> IO (Either (FileError TextEnvelopeError) a)
readFileTextEnvelope :: forall a content.
HasTextEnvelope a =>
File content 'In -> IO (Either (FileError TextEnvelopeError) a)
readFileTextEnvelope File content 'In
path =
ExceptT (FileError TextEnvelopeError) IO a
-> IO (Either (FileError TextEnvelopeError) a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO a
-> IO (Either (FileError TextEnvelopeError) a))
-> ExceptT (FileError TextEnvelopeError) IO a
-> IO (Either (FileError TextEnvelopeError) a)
forall a b. (a -> b) -> a -> b
$ do
content <- String
-> (String -> IO ByteString)
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall (m :: * -> *) s e.
MonadIO m =>
String -> (String -> IO s) -> ExceptT (FileError e) m s
fileIOExceptT (File content 'In -> String
forall content (direction :: FileDirection).
File content direction -> String
unFile File content 'In
path) String -> IO ByteString
readFileBlocking
firstExceptT (FileError (unFile path)) $ hoistEither $ do
te <- first TextEnvelopeAesonDecodeError $ Aeson.eitherDecodeStrict' content
deserialiseFromTextEnvelope te
readFileTextEnvelopeAnyOf
:: [FromSomeType HasTextEnvelope b]
-> File content In
-> IO (Either (FileError TextEnvelopeError) b)
readFileTextEnvelopeAnyOf :: forall b content.
[FromSomeType HasTextEnvelope b]
-> File content 'In -> IO (Either (FileError TextEnvelopeError) b)
readFileTextEnvelopeAnyOf [FromSomeType HasTextEnvelope b]
types File content 'In
path =
ExceptT (FileError TextEnvelopeError) IO b
-> IO (Either (FileError TextEnvelopeError) b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO b
-> IO (Either (FileError TextEnvelopeError) b))
-> ExceptT (FileError TextEnvelopeError) IO b
-> IO (Either (FileError TextEnvelopeError) b)
forall a b. (a -> b) -> a -> b
$ do
content <- String
-> (String -> IO ByteString)
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall (m :: * -> *) s e.
MonadIO m =>
String -> (String -> IO s) -> ExceptT (FileError e) m s
fileIOExceptT (File content 'In -> String
forall content (direction :: FileDirection).
File content direction -> String
unFile File content 'In
path) String -> IO ByteString
readFileBlocking
firstExceptT (FileError (unFile path)) $ hoistEither $ do
te <- first TextEnvelopeAesonDecodeError $ Aeson.eitherDecodeStrict' content
deserialiseFromTextEnvelopeAnyOf types te
readTextEnvelopeFromFile
:: FilePath
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeFromFile :: String -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeFromFile String
path =
ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope))
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall a b. (a -> b) -> a -> b
$ do
bs <- String
-> (String -> IO ByteString)
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall (m :: * -> *) s e.
MonadIO m =>
String -> (String -> IO s) -> ExceptT (FileError e) m s
fileIOExceptT String
path String -> IO ByteString
readFileBlocking
firstExceptT (FileError path . TextEnvelopeAesonDecodeError)
. hoistEither
$ Aeson.eitherDecodeStrict' bs
readTextEnvelopeOfTypeFromFile
:: TextEnvelopeType
-> FilePath
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeOfTypeFromFile :: TextEnvelopeType
-> String -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeOfTypeFromFile TextEnvelopeType
expectedType String
path =
ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope))
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall a b. (a -> b) -> a -> b
$ do
te <- IO (Either (FileError TextEnvelopeError) TextEnvelope)
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (String -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeFromFile String
path)
firstExceptT (FileError path) $
hoistEither $
expectTextEnvelopeOfType expectedType te
return te
textEnvelopeTypeToEra :: Text -> Either TextEnvelopeError AnyShelleyBasedEra
textEnvelopeTypeToEra :: Text -> Either TextEnvelopeError AnyShelleyBasedEra
textEnvelopeTypeToEra =
\case
Text
"TxSignedShelley" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ShelleyEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ShelleyEra
ShelleyBasedEraShelley
Text
"Tx AllegraEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AllegraEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AllegraEra
ShelleyBasedEraAllegra
Text
"Tx MaryEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra MaryEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra MaryEra
ShelleyBasedEraMary
Text
"Tx AlonzoEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AlonzoEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AlonzoEra
ShelleyBasedEraAlonzo
Text
"Tx BabbageEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra BabbageEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra BabbageEra
ShelleyBasedEraBabbage
Text
"Tx ConwayEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ConwayEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ConwayEra
ShelleyBasedEraConway
Text
"Witnessed Tx ShelleyEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ShelleyEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ShelleyEra
ShelleyBasedEraShelley
Text
"Witnessed Tx AllegraEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AllegraEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AllegraEra
ShelleyBasedEraAllegra
Text
"Witnessed Tx MaryEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra MaryEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra MaryEra
ShelleyBasedEraMary
Text
"Witnessed Tx AlonzoEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AlonzoEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AlonzoEra
ShelleyBasedEraAlonzo
Text
"Witnessed Tx BabbageEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra BabbageEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra BabbageEra
ShelleyBasedEraBabbage
Text
"Witnessed Tx ConwayEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ConwayEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ConwayEra
ShelleyBasedEraConway
Text
"Unwitnessed Tx ShelleyEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ShelleyEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ShelleyEra
ShelleyBasedEraShelley
Text
"Unwitnessed Tx AllegraEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AllegraEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AllegraEra
ShelleyBasedEraAllegra
Text
"Unwitnessed Tx MaryEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra MaryEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra MaryEra
ShelleyBasedEraMary
Text
"Unwitnessed Tx AlonzoEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AlonzoEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AlonzoEra
ShelleyBasedEraAlonzo
Text
"Unwitnessed Tx BabbageEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra BabbageEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra BabbageEra
ShelleyBasedEraBabbage
Text
"Unwitnessed Tx ConwayEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ConwayEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ConwayEra
ShelleyBasedEraConway
Text
"TxWitness ShelleyEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ShelleyEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ShelleyEra
ShelleyBasedEraShelley
Text
"TxWitness AllegraEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AllegraEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AllegraEra
ShelleyBasedEraAllegra
Text
"TxWitness MaryEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra MaryEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra MaryEra
ShelleyBasedEraMary
Text
"TxWitness AlonzoEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra AlonzoEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra AlonzoEra
ShelleyBasedEraAlonzo
Text
"TxWitness BabbageEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra BabbageEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra BabbageEra
ShelleyBasedEraBabbage
Text
"TxWitness ConwayEra" -> AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra
forall a. a -> Either TextEnvelopeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (AnyShelleyBasedEra -> Either TextEnvelopeError AnyShelleyBasedEra)
-> AnyShelleyBasedEra
-> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra ConwayEra -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra ShelleyBasedEra ConwayEra
ShelleyBasedEraConway
Text
unknownCddlType -> TextEnvelopeError -> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. a -> Either a b
Left (TextEnvelopeError -> Either TextEnvelopeError AnyShelleyBasedEra)
-> TextEnvelopeError -> Either TextEnvelopeError AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ Text -> TextEnvelopeError
TextEnvelopeUnknownType Text
unknownCddlType