{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Cardano.Api.DeserialiseAnyOf
( InputFormat (..)
, InputDecodeError (..)
, deserialiseInput
, deserialiseInputAnyOf
, renderInputDecodeError
, SomeAddressVerificationKey (..)
, deserialiseAnyVerificationKey
, deserialiseAnyVerificationKeyBech32
, deserialiseAnyVerificationKeyTextEnvelope
, renderSomeAddressVerificationKey
, mapSomeAddressVerificationKey
)
where
import Cardano.Api.Address
import Cardano.Api.Error
import Cardano.Api.Keys.Byron
import Cardano.Api.Keys.Class
import Cardano.Api.Keys.Praos
import Cardano.Api.Keys.Shelley
import Cardano.Api.SerialiseBech32
import Cardano.Api.SerialiseRaw
import Cardano.Api.SerialiseTextEnvelope
import qualified Cardano.Chain.Common as Common
import qualified Cardano.Crypto.Signing as Crypto
import qualified Data.Aeson as Aeson
import Data.Bifunctor (first)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BSC
import Data.Char (toLower)
import Data.Data (Data)
import Data.List.NonEmpty (NonEmpty)
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
import Formatting (build, sformat, (%))
import GHC.Exts (IsList (..))
import Prettyprinter
data InputFormat a where
InputFormatBech32 :: SerialiseAsBech32 a => InputFormat a
InputFormatHex :: SerialiseAsRawBytes a => InputFormat a
InputFormatTextEnvelope :: HasTextEnvelope a => InputFormat a
data InputDecodeError
=
InputTextEnvelopeError !TextEnvelopeError
|
InputBech32DecodeError !Bech32DecodeError
|
InputInvalidError
deriving (InputDecodeError -> InputDecodeError -> Bool
(InputDecodeError -> InputDecodeError -> Bool)
-> (InputDecodeError -> InputDecodeError -> Bool)
-> Eq InputDecodeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputDecodeError -> InputDecodeError -> Bool
== :: InputDecodeError -> InputDecodeError -> Bool
$c/= :: InputDecodeError -> InputDecodeError -> Bool
/= :: InputDecodeError -> InputDecodeError -> Bool
Eq, Int -> InputDecodeError -> ShowS
[InputDecodeError] -> ShowS
InputDecodeError -> String
(Int -> InputDecodeError -> ShowS)
-> (InputDecodeError -> String)
-> ([InputDecodeError] -> ShowS)
-> Show InputDecodeError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputDecodeError -> ShowS
showsPrec :: Int -> InputDecodeError -> ShowS
$cshow :: InputDecodeError -> String
show :: InputDecodeError -> String
$cshowList :: [InputDecodeError] -> ShowS
showList :: [InputDecodeError] -> ShowS
Show, Typeable InputDecodeError
Typeable InputDecodeError =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InputDecodeError -> c InputDecodeError)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InputDecodeError)
-> (InputDecodeError -> Constr)
-> (InputDecodeError -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InputDecodeError))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InputDecodeError))
-> ((forall b. Data b => b -> b)
-> InputDecodeError -> InputDecodeError)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r)
-> (forall u.
(forall d. Data d => d -> u) -> InputDecodeError -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> InputDecodeError -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError)
-> Data InputDecodeError
InputDecodeError -> Constr
InputDecodeError -> DataType
(forall b. Data b => b -> b)
-> InputDecodeError -> InputDecodeError
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) -> InputDecodeError -> u
forall u. (forall d. Data d => d -> u) -> InputDecodeError -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InputDecodeError
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InputDecodeError -> c InputDecodeError
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InputDecodeError)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InputDecodeError)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InputDecodeError -> c InputDecodeError
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InputDecodeError -> c InputDecodeError
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InputDecodeError
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InputDecodeError
$ctoConstr :: InputDecodeError -> Constr
toConstr :: InputDecodeError -> Constr
$cdataTypeOf :: InputDecodeError -> DataType
dataTypeOf :: InputDecodeError -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InputDecodeError)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InputDecodeError)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InputDecodeError)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InputDecodeError)
$cgmapT :: (forall b. Data b => b -> b)
-> InputDecodeError -> InputDecodeError
gmapT :: (forall b. Data b => b -> b)
-> InputDecodeError -> InputDecodeError
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> InputDecodeError -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> InputDecodeError -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> InputDecodeError -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> InputDecodeError -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> InputDecodeError -> m InputDecodeError
Data)
instance Error InputDecodeError where
prettyError :: forall ann. InputDecodeError -> Doc ann
prettyError = InputDecodeError -> Doc ann
forall ann. InputDecodeError -> Doc ann
renderInputDecodeError
renderInputDecodeError :: InputDecodeError -> Doc ann
renderInputDecodeError :: forall ann. InputDecodeError -> Doc ann
renderInputDecodeError = \case
InputTextEnvelopeError TextEnvelopeError
textEnvErr ->
TextEnvelopeError -> Doc ann
forall e ann. Error e => e -> Doc ann
forall ann. TextEnvelopeError -> Doc ann
prettyError TextEnvelopeError
textEnvErr
InputBech32DecodeError Bech32DecodeError
decodeErr ->
Bech32DecodeError -> Doc ann
forall e ann. Error e => e -> Doc ann
forall ann. Bech32DecodeError -> Doc ann
prettyError Bech32DecodeError
decodeErr
InputDecodeError
InputInvalidError ->
Doc ann
"Invalid key."
data DeserialiseInputResult a
=
DeserialiseInputSuccess !a
|
DeserialiseInputError !InputDecodeError
|
DeserialiseInputErrorFormatMismatch
deserialiseInput
:: forall a
. AsType a
-> NonEmpty (InputFormat a)
-> ByteString
-> Either InputDecodeError a
deserialiseInput :: forall a.
AsType a
-> NonEmpty (InputFormat a)
-> ByteString
-> Either InputDecodeError a
deserialiseInput AsType a
asType NonEmpty (InputFormat a)
acceptedFormats ByteString
inputBs =
[InputFormat a] -> Either InputDecodeError a
go (NonEmpty (InputFormat a) -> [Item (NonEmpty (InputFormat a))]
forall l. IsList l => l -> [Item l]
toList NonEmpty (InputFormat a)
acceptedFormats)
where
inputText :: Text
inputText :: Text
inputText = ByteString -> Text
Text.decodeUtf8 ByteString
inputBs
go :: [InputFormat a] -> Either InputDecodeError a
go :: [InputFormat a] -> Either InputDecodeError a
go [] = InputDecodeError -> Either InputDecodeError a
forall a b. a -> Either a b
Left InputDecodeError
InputInvalidError
go (InputFormat a
kf : [InputFormat a]
kfs) =
let res :: DeserialiseInputResult a
res =
case InputFormat a
kf of
InputFormat a
InputFormatBech32 -> DeserialiseInputResult a
SerialiseAsBech32 a => DeserialiseInputResult a
deserialiseBech32
InputFormat a
InputFormatHex -> DeserialiseInputResult a
SerialiseAsRawBytes a => DeserialiseInputResult a
deserialiseHex
InputFormat a
InputFormatTextEnvelope -> DeserialiseInputResult a
HasTextEnvelope a => DeserialiseInputResult a
deserialiseTextEnvelope
in case DeserialiseInputResult a
res of
DeserialiseInputSuccess a
a -> a -> Either InputDecodeError a
forall a b. b -> Either a b
Right a
a
DeserialiseInputError InputDecodeError
err -> InputDecodeError -> Either InputDecodeError a
forall a b. a -> Either a b
Left InputDecodeError
err
DeserialiseInputResult a
DeserialiseInputErrorFormatMismatch -> [InputFormat a] -> Either InputDecodeError a
go [InputFormat a]
kfs
deserialiseTextEnvelope :: HasTextEnvelope a => DeserialiseInputResult a
deserialiseTextEnvelope :: HasTextEnvelope a => DeserialiseInputResult a
deserialiseTextEnvelope = do
let textEnvRes :: Either TextEnvelopeError a
textEnvRes :: Either TextEnvelopeError a
textEnvRes =
AsType a -> TextEnvelope -> Either TextEnvelopeError a
forall a.
HasTextEnvelope a =>
AsType a -> TextEnvelope -> Either TextEnvelopeError a
deserialiseFromTextEnvelope AsType a
asType
(TextEnvelope -> Either TextEnvelopeError a)
-> Either TextEnvelopeError TextEnvelope
-> Either TextEnvelopeError a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (String -> TextEnvelopeError)
-> Either String TextEnvelope
-> Either TextEnvelopeError TextEnvelope
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 String -> TextEnvelopeError
TextEnvelopeAesonDecodeError (ByteString -> Either String TextEnvelope
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict' ByteString
inputBs)
case Either TextEnvelopeError a
textEnvRes of
Right a
res -> a -> DeserialiseInputResult a
forall a. a -> DeserialiseInputResult a
DeserialiseInputSuccess a
res
Left err :: TextEnvelopeError
err@TextEnvelopeTypeError{} ->
InputDecodeError -> DeserialiseInputResult a
forall a. InputDecodeError -> DeserialiseInputResult a
DeserialiseInputError (TextEnvelopeError -> InputDecodeError
InputTextEnvelopeError TextEnvelopeError
err)
Left TextEnvelopeError
_ -> DeserialiseInputResult a
forall a. DeserialiseInputResult a
DeserialiseInputErrorFormatMismatch
deserialiseBech32 :: SerialiseAsBech32 a => DeserialiseInputResult a
deserialiseBech32 :: SerialiseAsBech32 a => DeserialiseInputResult a
deserialiseBech32 =
case AsType a -> Text -> Either Bech32DecodeError a
forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 AsType a
asType Text
inputText of
Right a
res -> a -> DeserialiseInputResult a
forall a. a -> DeserialiseInputResult a
DeserialiseInputSuccess a
res
Left (Bech32DecodingError DecodingError
_) -> DeserialiseInputResult a
forall a. DeserialiseInputResult a
DeserialiseInputErrorFormatMismatch
Left Bech32DecodeError
err -> InputDecodeError -> DeserialiseInputResult a
forall a. InputDecodeError -> DeserialiseInputResult a
DeserialiseInputError (InputDecodeError -> DeserialiseInputResult a)
-> InputDecodeError -> DeserialiseInputResult a
forall a b. (a -> b) -> a -> b
$ Bech32DecodeError -> InputDecodeError
InputBech32DecodeError Bech32DecodeError
err
deserialiseHex :: SerialiseAsRawBytes a => DeserialiseInputResult a
deserialiseHex :: SerialiseAsRawBytes a => DeserialiseInputResult a
deserialiseHex
| ByteString -> Bool
isValidHex ByteString
inputBs =
case AsType a -> ByteString -> Either RawBytesHexError a
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either RawBytesHexError a
deserialiseFromRawBytesHex AsType a
asType ByteString
inputBs of
Left RawBytesHexError
_ -> InputDecodeError -> DeserialiseInputResult a
forall a. InputDecodeError -> DeserialiseInputResult a
DeserialiseInputError InputDecodeError
InputInvalidError
Right a
x -> a -> DeserialiseInputResult a
forall a. a -> DeserialiseInputResult a
DeserialiseInputSuccess a
x
| Bool
otherwise = DeserialiseInputResult a
forall a. DeserialiseInputResult a
DeserialiseInputErrorFormatMismatch
isValidHex :: ByteString -> Bool
isValidHex :: ByteString -> Bool
isValidHex ByteString
x =
(Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
hexAlpha) (Char -> Bool) -> (Char -> Char) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Char
toLower) (ByteString -> String
BSC.unpack ByteString
x)
Bool -> Bool -> Bool
&& Int -> Bool
forall a. Integral a => a -> Bool
even (ByteString -> Int
BSC.length ByteString
x)
where
hexAlpha :: [Char]
hexAlpha :: String
hexAlpha = String
"0123456789abcdef"
deserialiseInputAnyOf
:: forall b
. [FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> ByteString
-> Either InputDecodeError b
deserialiseInputAnyOf :: forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> ByteString
-> Either InputDecodeError b
deserialiseInputAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes ByteString
inputBs =
case DeserialiseInputResult b
deserialiseBech32 DeserialiseInputResult b
-> DeserialiseInputResult b -> DeserialiseInputResult b
`orTry` DeserialiseInputResult b
deserialiseTextEnvelope of
DeserialiseInputSuccess b
res -> b -> Either InputDecodeError b
forall a b. b -> Either a b
Right b
res
DeserialiseInputError InputDecodeError
err -> InputDecodeError -> Either InputDecodeError b
forall a b. a -> Either a b
Left InputDecodeError
err
DeserialiseInputResult b
DeserialiseInputErrorFormatMismatch -> InputDecodeError -> Either InputDecodeError b
forall a b. a -> Either a b
Left InputDecodeError
InputInvalidError
where
inputText :: Text
inputText :: Text
inputText = ByteString -> Text
Text.decodeUtf8 ByteString
inputBs
orTry
:: DeserialiseInputResult b
-> DeserialiseInputResult b
-> DeserialiseInputResult b
orTry :: DeserialiseInputResult b
-> DeserialiseInputResult b -> DeserialiseInputResult b
orTry DeserialiseInputResult b
x DeserialiseInputResult b
y =
case DeserialiseInputResult b
x of
DeserialiseInputSuccess b
_ -> DeserialiseInputResult b
x
DeserialiseInputError InputDecodeError
_ -> DeserialiseInputResult b
x
DeserialiseInputResult b
DeserialiseInputErrorFormatMismatch -> DeserialiseInputResult b
y
deserialiseTextEnvelope :: DeserialiseInputResult b
deserialiseTextEnvelope :: DeserialiseInputResult b
deserialiseTextEnvelope = do
let textEnvRes :: Either TextEnvelopeError b
textEnvRes :: Either TextEnvelopeError b
textEnvRes =
[FromSomeType HasTextEnvelope b]
-> TextEnvelope -> Either TextEnvelopeError b
forall b.
[FromSomeType HasTextEnvelope b]
-> TextEnvelope -> Either TextEnvelopeError b
deserialiseFromTextEnvelopeAnyOf [FromSomeType HasTextEnvelope b]
textEnvTypes
(TextEnvelope -> Either TextEnvelopeError b)
-> Either TextEnvelopeError TextEnvelope
-> Either TextEnvelopeError b
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (String -> TextEnvelopeError)
-> Either String TextEnvelope
-> Either TextEnvelopeError TextEnvelope
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 String -> TextEnvelopeError
TextEnvelopeAesonDecodeError (ByteString -> Either String TextEnvelope
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict' ByteString
inputBs)
case Either TextEnvelopeError b
textEnvRes of
Right b
res -> b -> DeserialiseInputResult b
forall a. a -> DeserialiseInputResult a
DeserialiseInputSuccess b
res
Left err :: TextEnvelopeError
err@TextEnvelopeTypeError{} ->
InputDecodeError -> DeserialiseInputResult b
forall a. InputDecodeError -> DeserialiseInputResult a
DeserialiseInputError (TextEnvelopeError -> InputDecodeError
InputTextEnvelopeError TextEnvelopeError
err)
Left TextEnvelopeError
_ -> DeserialiseInputResult b
forall a. DeserialiseInputResult a
DeserialiseInputErrorFormatMismatch
deserialiseBech32 :: DeserialiseInputResult b
deserialiseBech32 :: DeserialiseInputResult b
deserialiseBech32 =
case [FromSomeType SerialiseAsBech32 b]
-> Text -> Either Bech32DecodeError b
forall b.
[FromSomeType SerialiseAsBech32 b]
-> Text -> Either Bech32DecodeError b
deserialiseAnyOfFromBech32 [FromSomeType SerialiseAsBech32 b]
bech32Types Text
inputText of
Right b
res -> b -> DeserialiseInputResult b
forall a. a -> DeserialiseInputResult a
DeserialiseInputSuccess b
res
Left (Bech32DecodingError DecodingError
_) -> DeserialiseInputResult b
forall a. DeserialiseInputResult a
DeserialiseInputErrorFormatMismatch
Left Bech32DecodeError
err -> InputDecodeError -> DeserialiseInputResult b
forall a. InputDecodeError -> DeserialiseInputResult a
DeserialiseInputError (InputDecodeError -> DeserialiseInputResult b)
-> InputDecodeError -> DeserialiseInputResult b
forall a b. (a -> b) -> a -> b
$ Bech32DecodeError -> InputDecodeError
InputBech32DecodeError Bech32DecodeError
err
data SomeAddressVerificationKey
= AByronVerificationKey (VerificationKey ByronKey)
| APaymentVerificationKey (VerificationKey PaymentKey)
| APaymentExtendedVerificationKey (VerificationKey PaymentExtendedKey)
| AGenesisUTxOVerificationKey (VerificationKey GenesisUTxOKey)
| AGenesisExtendedVerificationKey (VerificationKey GenesisExtendedKey)
| AGenesisDelegateExtendedVerificationKey
(VerificationKey GenesisDelegateExtendedKey)
| AKesVerificationKey (VerificationKey KesKey)
| AVrfVerificationKey (VerificationKey VrfKey)
| AStakeVerificationKey (VerificationKey StakeKey)
| AStakeExtendedVerificationKey (VerificationKey StakeExtendedKey)
| ADRepVerificationKey (VerificationKey DRepKey)
| ADRepExtendedVerificationKey (VerificationKey DRepExtendedKey)
| ACommitteeColdVerificationKey (VerificationKey CommitteeColdKey)
| ACommitteeColdExtendedVerificationKey (VerificationKey CommitteeColdExtendedKey)
| ACommitteeHotVerificationKey (VerificationKey CommitteeHotKey)
| ACommitteeHotExtendedVerificationKey (VerificationKey CommitteeHotExtendedKey)
deriving Int -> SomeAddressVerificationKey -> ShowS
[SomeAddressVerificationKey] -> ShowS
SomeAddressVerificationKey -> String
(Int -> SomeAddressVerificationKey -> ShowS)
-> (SomeAddressVerificationKey -> String)
-> ([SomeAddressVerificationKey] -> ShowS)
-> Show SomeAddressVerificationKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SomeAddressVerificationKey -> ShowS
showsPrec :: Int -> SomeAddressVerificationKey -> ShowS
$cshow :: SomeAddressVerificationKey -> String
show :: SomeAddressVerificationKey -> String
$cshowList :: [SomeAddressVerificationKey] -> ShowS
showList :: [SomeAddressVerificationKey] -> ShowS
Show
renderSomeAddressVerificationKey :: SomeAddressVerificationKey -> Text
renderSomeAddressVerificationKey :: SomeAddressVerificationKey -> Text
renderSomeAddressVerificationKey =
\case
AByronVerificationKey VerificationKey ByronKey
vk -> VerificationKey ByronKey -> Text
prettyByronVerificationKey VerificationKey ByronKey
vk
APaymentVerificationKey VerificationKey PaymentKey
vk -> VerificationKey PaymentKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey PaymentKey
vk
APaymentExtendedVerificationKey VerificationKey PaymentExtendedKey
vk -> VerificationKey PaymentExtendedKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey PaymentExtendedKey
vk
AGenesisUTxOVerificationKey VerificationKey GenesisUTxOKey
vk -> VerificationKey PaymentKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 (VerificationKey GenesisUTxOKey -> VerificationKey PaymentKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisUTxOKey
vk :: VerificationKey PaymentKey)
AGenesisExtendedVerificationKey VerificationKey GenesisExtendedKey
vk ->
let genKey :: VerificationKey GenesisKey
genKey = (VerificationKey GenesisExtendedKey -> VerificationKey GenesisKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisExtendedKey
vk :: VerificationKey GenesisKey)
payKey :: VerificationKey PaymentKey
payKey = (VerificationKey GenesisKey -> VerificationKey PaymentKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisKey
genKey :: VerificationKey PaymentKey)
in VerificationKey PaymentKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey PaymentKey
payKey
AGenesisDelegateExtendedVerificationKey VerificationKey GenesisDelegateExtendedKey
vk ->
let genDelegKey :: VerificationKey GenesisDelegateKey
genDelegKey = (VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisDelegateExtendedKey
vk :: VerificationKey GenesisDelegateKey)
stakePoolKey :: VerificationKey StakePoolKey
stakePoolKey = VerificationKey GenesisDelegateKey -> VerificationKey StakePoolKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisDelegateKey
genDelegKey :: VerificationKey StakePoolKey
in VerificationKey StakePoolKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey StakePoolKey
stakePoolKey
AKesVerificationKey VerificationKey KesKey
vk -> VerificationKey KesKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey KesKey
vk
AVrfVerificationKey VerificationKey VrfKey
vk -> VerificationKey VrfKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey VrfKey
vk
AStakeVerificationKey VerificationKey StakeKey
vk -> VerificationKey StakeKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey StakeKey
vk
AStakeExtendedVerificationKey VerificationKey StakeExtendedKey
vk -> VerificationKey StakeExtendedKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey StakeExtendedKey
vk
ADRepVerificationKey VerificationKey DRepKey
vk -> VerificationKey DRepKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey DRepKey
vk
ADRepExtendedVerificationKey VerificationKey DRepExtendedKey
vk -> VerificationKey DRepExtendedKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey DRepExtendedKey
vk
ACommitteeColdVerificationKey VerificationKey CommitteeColdKey
vk -> VerificationKey CommitteeColdKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey CommitteeColdKey
vk
ACommitteeColdExtendedVerificationKey VerificationKey CommitteeColdExtendedKey
vk -> VerificationKey CommitteeColdExtendedKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey CommitteeColdExtendedKey
vk
ACommitteeHotVerificationKey VerificationKey CommitteeHotKey
vk -> VerificationKey CommitteeHotKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey CommitteeHotKey
vk
ACommitteeHotExtendedVerificationKey VerificationKey CommitteeHotExtendedKey
vk -> VerificationKey CommitteeHotExtendedKey -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 VerificationKey CommitteeHotExtendedKey
vk
mapSomeAddressVerificationKey
:: ()
=> (forall keyrole. Key keyrole => VerificationKey keyrole -> a)
-> SomeAddressVerificationKey
-> a
mapSomeAddressVerificationKey :: forall a.
(forall keyrole. Key keyrole => VerificationKey keyrole -> a)
-> SomeAddressVerificationKey -> a
mapSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f = \case
AByronVerificationKey VerificationKey ByronKey
vk -> VerificationKey ByronKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey ByronKey
vk
APaymentVerificationKey VerificationKey PaymentKey
vk -> VerificationKey PaymentKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey PaymentKey
vk
APaymentExtendedVerificationKey VerificationKey PaymentExtendedKey
vk -> VerificationKey PaymentExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey PaymentExtendedKey
vk
AGenesisUTxOVerificationKey VerificationKey GenesisUTxOKey
vk -> VerificationKey GenesisUTxOKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey GenesisUTxOKey
vk
AKesVerificationKey VerificationKey KesKey
vk -> VerificationKey KesKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey KesKey
vk
AGenesisDelegateExtendedVerificationKey VerificationKey GenesisDelegateExtendedKey
vk -> VerificationKey GenesisDelegateExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey GenesisDelegateExtendedKey
vk
AGenesisExtendedVerificationKey VerificationKey GenesisExtendedKey
vk -> VerificationKey GenesisExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey GenesisExtendedKey
vk
AVrfVerificationKey VerificationKey VrfKey
vk -> VerificationKey VrfKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey VrfKey
vk
AStakeVerificationKey VerificationKey StakeKey
vk -> VerificationKey StakeKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey StakeKey
vk
AStakeExtendedVerificationKey VerificationKey StakeExtendedKey
vk -> VerificationKey StakeExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey StakeExtendedKey
vk
ADRepVerificationKey VerificationKey DRepKey
vk -> VerificationKey DRepKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey DRepKey
vk
ADRepExtendedVerificationKey VerificationKey DRepExtendedKey
vk -> VerificationKey DRepExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey DRepExtendedKey
vk
ACommitteeColdVerificationKey VerificationKey CommitteeColdKey
vk -> VerificationKey CommitteeColdKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey CommitteeColdKey
vk
ACommitteeColdExtendedVerificationKey VerificationKey CommitteeColdExtendedKey
vk -> VerificationKey CommitteeColdExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey CommitteeColdExtendedKey
vk
ACommitteeHotVerificationKey VerificationKey CommitteeHotKey
vk -> VerificationKey CommitteeHotKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey CommitteeHotKey
vk
ACommitteeHotExtendedVerificationKey VerificationKey CommitteeHotExtendedKey
vk -> VerificationKey CommitteeHotExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey CommitteeHotExtendedKey
vk
prettyByronVerificationKey :: VerificationKey ByronKey -> Text
prettyByronVerificationKey :: VerificationKey ByronKey -> Text
prettyByronVerificationKey (ByronVerificationKey VerificationKey
vk) =
Format
Text
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
-> AddressHash VerificationKey
-> VerificationKey
-> VerificationKey
-> Text
forall a. Format Text a -> a
sformat
( Format
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
" public key hash: "
Format
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
-> Format
Text
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
-> Format
Text
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format
(VerificationKey -> VerificationKey -> Text)
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
forall a r. Buildable a => Format r (a -> r)
build
Format
(VerificationKey -> VerificationKey -> Text)
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
-> Format Text (VerificationKey -> VerificationKey -> Text)
-> Format
Text
(AddressHash VerificationKey
-> VerificationKey -> VerificationKey -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format
(VerificationKey -> VerificationKey -> Text)
(VerificationKey -> VerificationKey -> Text)
"\npublic key (base64): "
Format
(VerificationKey -> VerificationKey -> Text)
(VerificationKey -> VerificationKey -> Text)
-> Format Text (VerificationKey -> VerificationKey -> Text)
-> Format Text (VerificationKey -> VerificationKey -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format
(VerificationKey -> Text)
(VerificationKey -> VerificationKey -> Text)
forall r. Format r (VerificationKey -> r)
Crypto.fullVerificationKeyF
Format
(VerificationKey -> Text)
(VerificationKey -> VerificationKey -> Text)
-> Format Text (VerificationKey -> Text)
-> Format Text (VerificationKey -> VerificationKey -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (VerificationKey -> Text) (VerificationKey -> Text)
"\n public key (hex): "
Format (VerificationKey -> Text) (VerificationKey -> Text)
-> Format Text (VerificationKey -> Text)
-> Format Text (VerificationKey -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format Text (VerificationKey -> Text)
forall r. Format r (VerificationKey -> r)
Crypto.fullVerificationKeyHexF
)
(VerificationKey -> AddressHash VerificationKey
forall a. EncCBOR a => a -> AddressHash a
Common.addressHash VerificationKey
vk)
VerificationKey
vk
VerificationKey
vk
deserialiseAnyVerificationKey
:: ByteString -> Either InputDecodeError SomeAddressVerificationKey
deserialiseAnyVerificationKey :: ByteString -> Either InputDecodeError SomeAddressVerificationKey
deserialiseAnyVerificationKey ByteString
bs =
case ByteString -> Either Bech32DecodeError SomeAddressVerificationKey
deserialiseAnyVerificationKeyBech32 ByteString
bs of
Right SomeAddressVerificationKey
vk -> SomeAddressVerificationKey
-> Either InputDecodeError SomeAddressVerificationKey
forall a b. b -> Either a b
Right SomeAddressVerificationKey
vk
Left Bech32DecodeError
_e ->
case ByteString -> Either TextEnvelopeError SomeAddressVerificationKey
deserialiseAnyVerificationKeyTextEnvelope ByteString
bs of
Right SomeAddressVerificationKey
vk -> SomeAddressVerificationKey
-> Either InputDecodeError SomeAddressVerificationKey
forall a b. b -> Either a b
Right SomeAddressVerificationKey
vk
Left TextEnvelopeError
_e -> InputDecodeError
-> Either InputDecodeError SomeAddressVerificationKey
forall a b. a -> Either a b
Left InputDecodeError
InputInvalidError
deserialiseAnyVerificationKeyBech32
:: ByteString -> Either Bech32DecodeError SomeAddressVerificationKey
deserialiseAnyVerificationKeyBech32 :: ByteString -> Either Bech32DecodeError SomeAddressVerificationKey
deserialiseAnyVerificationKeyBech32 =
[FromSomeType SerialiseAsBech32 SomeAddressVerificationKey]
-> Text -> Either Bech32DecodeError SomeAddressVerificationKey
forall b.
[FromSomeType SerialiseAsBech32 b]
-> Text -> Either Bech32DecodeError b
deserialiseAnyOfFromBech32 [FromSomeType SerialiseAsBech32 SomeAddressVerificationKey]
allBech32VerKey (Text -> Either Bech32DecodeError SomeAddressVerificationKey)
-> (ByteString -> Text)
-> ByteString
-> Either Bech32DecodeError SomeAddressVerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf8
where
allBech32VerKey
:: [FromSomeType SerialiseAsBech32 SomeAddressVerificationKey]
allBech32VerKey :: [FromSomeType SerialiseAsBech32 SomeAddressVerificationKey]
allBech32VerKey =
[ AsType (VerificationKey DRepKey)
-> (VerificationKey DRepKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType DRepKey -> AsType (VerificationKey DRepKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType DRepKey
AsDRepKey) VerificationKey DRepKey -> SomeAddressVerificationKey
ADRepVerificationKey
, AsType (VerificationKey DRepExtendedKey)
-> (VerificationKey DRepExtendedKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType DRepExtendedKey -> AsType (VerificationKey DRepExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType DRepExtendedKey
AsDRepExtendedKey) VerificationKey DRepExtendedKey -> SomeAddressVerificationKey
ADRepExtendedVerificationKey
, AsType (VerificationKey CommitteeColdKey)
-> (VerificationKey CommitteeColdKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeColdKey
-> AsType (VerificationKey CommitteeColdKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeColdKey
AsCommitteeColdKey) VerificationKey CommitteeColdKey -> SomeAddressVerificationKey
ACommitteeColdVerificationKey
, AsType (VerificationKey CommitteeColdExtendedKey)
-> (VerificationKey CommitteeColdExtendedKey
-> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeColdExtendedKey
-> AsType (VerificationKey CommitteeColdExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeColdExtendedKey
AsCommitteeColdExtendedKey) VerificationKey CommitteeColdExtendedKey
-> SomeAddressVerificationKey
ACommitteeColdExtendedVerificationKey
, AsType (VerificationKey CommitteeHotKey)
-> (VerificationKey CommitteeHotKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeHotKey -> AsType (VerificationKey CommitteeHotKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeHotKey
AsCommitteeHotKey) VerificationKey CommitteeHotKey -> SomeAddressVerificationKey
ACommitteeHotVerificationKey
, AsType (VerificationKey CommitteeHotExtendedKey)
-> (VerificationKey CommitteeHotExtendedKey
-> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeHotExtendedKey
-> AsType (VerificationKey CommitteeHotExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeHotExtendedKey
AsCommitteeHotExtendedKey) VerificationKey CommitteeHotExtendedKey
-> SomeAddressVerificationKey
ACommitteeHotExtendedVerificationKey
, AsType (VerificationKey PaymentKey)
-> (VerificationKey PaymentKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentKey -> AsType (VerificationKey PaymentKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType PaymentKey
AsPaymentKey) VerificationKey PaymentKey -> SomeAddressVerificationKey
APaymentVerificationKey
, AsType (VerificationKey PaymentExtendedKey)
-> (VerificationKey PaymentExtendedKey
-> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentExtendedKey
-> AsType (VerificationKey PaymentExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType PaymentExtendedKey
AsPaymentExtendedKey) VerificationKey PaymentExtendedKey -> SomeAddressVerificationKey
APaymentExtendedVerificationKey
, AsType (VerificationKey KesKey)
-> (VerificationKey KesKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType KesKey -> AsType (VerificationKey KesKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType KesKey
AsKesKey) VerificationKey KesKey -> SomeAddressVerificationKey
AKesVerificationKey
, AsType (VerificationKey VrfKey)
-> (VerificationKey VrfKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VrfKey -> AsType (VerificationKey VrfKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType VrfKey
AsVrfKey) VerificationKey VrfKey -> SomeAddressVerificationKey
AVrfVerificationKey
, AsType (VerificationKey StakeKey)
-> (VerificationKey StakeKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeKey -> AsType (VerificationKey StakeKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType StakeKey
AsStakeKey) VerificationKey StakeKey -> SomeAddressVerificationKey
AStakeVerificationKey
, AsType (VerificationKey StakeExtendedKey)
-> (VerificationKey StakeExtendedKey -> SomeAddressVerificationKey)
-> FromSomeType SerialiseAsBech32 SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeExtendedKey
-> AsType (VerificationKey StakeExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType StakeExtendedKey
AsStakeExtendedKey) VerificationKey StakeExtendedKey -> SomeAddressVerificationKey
AStakeExtendedVerificationKey
]
deserialiseAnyVerificationKeyTextEnvelope
:: ByteString -> Either TextEnvelopeError SomeAddressVerificationKey
deserialiseAnyVerificationKeyTextEnvelope :: ByteString -> Either TextEnvelopeError SomeAddressVerificationKey
deserialiseAnyVerificationKeyTextEnvelope ByteString
bs =
[FromSomeType HasTextEnvelope SomeAddressVerificationKey]
-> TextEnvelope
-> Either TextEnvelopeError SomeAddressVerificationKey
forall b.
[FromSomeType HasTextEnvelope b]
-> TextEnvelope -> Either TextEnvelopeError b
deserialiseFromTextEnvelopeAnyOf [FromSomeType HasTextEnvelope SomeAddressVerificationKey]
allTextEnvelopeCBOR
(TextEnvelope
-> Either TextEnvelopeError SomeAddressVerificationKey)
-> Either TextEnvelopeError TextEnvelope
-> Either TextEnvelopeError SomeAddressVerificationKey
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (String -> TextEnvelopeError)
-> Either String TextEnvelope
-> Either TextEnvelopeError TextEnvelope
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 String -> TextEnvelopeError
TextEnvelopeAesonDecodeError (ByteString -> Either String TextEnvelope
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict' ByteString
bs)
where
allTextEnvelopeCBOR
:: [FromSomeType HasTextEnvelope SomeAddressVerificationKey]
allTextEnvelopeCBOR :: [FromSomeType HasTextEnvelope SomeAddressVerificationKey]
allTextEnvelopeCBOR =
[ AsType (VerificationKey ByronKey)
-> (VerificationKey ByronKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType ByronKey -> AsType (VerificationKey ByronKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType ByronKey
AsByronKey) VerificationKey ByronKey -> SomeAddressVerificationKey
AByronVerificationKey
, AsType (VerificationKey DRepKey)
-> (VerificationKey DRepKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType DRepKey -> AsType (VerificationKey DRepKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType DRepKey
AsDRepKey) VerificationKey DRepKey -> SomeAddressVerificationKey
ADRepVerificationKey
, AsType (VerificationKey DRepExtendedKey)
-> (VerificationKey DRepExtendedKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType DRepExtendedKey -> AsType (VerificationKey DRepExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType DRepExtendedKey
AsDRepExtendedKey) VerificationKey DRepExtendedKey -> SomeAddressVerificationKey
ADRepExtendedVerificationKey
, AsType (VerificationKey CommitteeColdKey)
-> (VerificationKey CommitteeColdKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeColdKey
-> AsType (VerificationKey CommitteeColdKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeColdKey
AsCommitteeColdKey) VerificationKey CommitteeColdKey -> SomeAddressVerificationKey
ACommitteeColdVerificationKey
, AsType (VerificationKey CommitteeColdExtendedKey)
-> (VerificationKey CommitteeColdExtendedKey
-> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeColdExtendedKey
-> AsType (VerificationKey CommitteeColdExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeColdExtendedKey
AsCommitteeColdExtendedKey) VerificationKey CommitteeColdExtendedKey
-> SomeAddressVerificationKey
ACommitteeColdExtendedVerificationKey
, AsType (VerificationKey CommitteeHotKey)
-> (VerificationKey CommitteeHotKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeHotKey -> AsType (VerificationKey CommitteeHotKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeHotKey
AsCommitteeHotKey) VerificationKey CommitteeHotKey -> SomeAddressVerificationKey
ACommitteeHotVerificationKey
, AsType (VerificationKey CommitteeHotExtendedKey)
-> (VerificationKey CommitteeHotExtendedKey
-> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType CommitteeHotExtendedKey
-> AsType (VerificationKey CommitteeHotExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType CommitteeHotExtendedKey
AsCommitteeHotExtendedKey) VerificationKey CommitteeHotExtendedKey
-> SomeAddressVerificationKey
ACommitteeHotExtendedVerificationKey
, AsType (VerificationKey PaymentKey)
-> (VerificationKey PaymentKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentKey -> AsType (VerificationKey PaymentKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType PaymentKey
AsPaymentKey) VerificationKey PaymentKey -> SomeAddressVerificationKey
APaymentVerificationKey
, AsType (VerificationKey PaymentExtendedKey)
-> (VerificationKey PaymentExtendedKey
-> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentExtendedKey
-> AsType (VerificationKey PaymentExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType PaymentExtendedKey
AsPaymentExtendedKey) VerificationKey PaymentExtendedKey -> SomeAddressVerificationKey
APaymentExtendedVerificationKey
, AsType (VerificationKey StakeExtendedKey)
-> (VerificationKey StakeExtendedKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeExtendedKey
-> AsType (VerificationKey StakeExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType StakeExtendedKey
AsStakeExtendedKey) VerificationKey StakeExtendedKey -> SomeAddressVerificationKey
AStakeExtendedVerificationKey
, AsType (VerificationKey GenesisUTxOKey)
-> (VerificationKey GenesisUTxOKey -> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisUTxOKey -> AsType (VerificationKey GenesisUTxOKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType GenesisUTxOKey
AsGenesisUTxOKey) VerificationKey GenesisUTxOKey -> SomeAddressVerificationKey
AGenesisUTxOVerificationKey
, AsType (VerificationKey GenesisExtendedKey)
-> (VerificationKey GenesisExtendedKey
-> SomeAddressVerificationKey)
-> FromSomeType HasTextEnvelope SomeAddressVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisExtendedKey
-> AsType (VerificationKey GenesisExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType GenesisExtendedKey
AsGenesisExtendedKey) VerificationKey GenesisExtendedKey -> SomeAddressVerificationKey
AGenesisExtendedVerificationKey
]