{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
module Bcc.CLI.Sophie.Key
( InputFormat (..)
, InputDecodeError (..)
, deserialiseInput
, deserialiseInputAnyOf
, renderInputDecodeError
, readKeyFile
, readKeyFileAnyOf
, readKeyFileTextEnvelope
, readSigningKeyFile
, readSigningKeyFileAnyOf
, VerificationKeyOrFile (..)
, readVerificationKeyOrFile
, readVerificationKeyOrTextEnvFile
, VerificationKeyTextOrFile (..)
, VerificationKeyTextOrFileError (..)
, readVerificationKeyTextOrFileAnyOf
, renderVerificationKeyTextOrFileError
, VerificationKeyOrHashOrFile (..)
, readVerificationKeyOrHashOrFile
, readVerificationKeyOrHashOrTextEnvFile
, PaymentVerifier(..)
, StakeVerifier(..)
) where
import Bcc.Prelude
import Control.Monad.Trans.Except.Extra (firstExceptT, handleIOExceptT, hoistEither)
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import qualified Data.List.NonEmpty as NE
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Bcc.Api
import Bcc.CLI.Types
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
/= :: InputDecodeError -> InputDecodeError -> Bool
$c/= :: InputDecodeError -> InputDecodeError -> Bool
== :: InputDecodeError -> InputDecodeError -> Bool
$c== :: 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
showList :: [InputDecodeError] -> ShowS
$cshowList :: [InputDecodeError] -> ShowS
show :: InputDecodeError -> String
$cshow :: InputDecodeError -> String
showsPrec :: Int -> InputDecodeError -> ShowS
$cshowsPrec :: Int -> InputDecodeError -> ShowS
Show)
instance Error InputDecodeError where
displayError :: InputDecodeError -> String
displayError = Text -> String
Text.unpack (Text -> String)
-> (InputDecodeError -> Text) -> InputDecodeError -> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. InputDecodeError -> Text
renderInputDecodeError
renderInputDecodeError :: InputDecodeError -> Text
renderInputDecodeError :: InputDecodeError -> Text
renderInputDecodeError InputDecodeError
err =
case InputDecodeError
err of
InputTextEnvelopeError TextEnvelopeError
textEnvErr ->
String -> Text
Text.pack (TextEnvelopeError -> String
forall e. Error e => e -> String
displayError TextEnvelopeError
textEnvErr)
InputBech32DecodeError Bech32DecodeError
decodeErr ->
String -> Text
Text.pack (Bech32DecodeError -> String
forall e. Error e => e -> String
displayError Bech32DecodeError
decodeErr)
InputDecodeError
InputInvalidError -> Text
"Invalid key."
data DeserialiseInputResult a
= DeserialiseInputSuccess !a
| DeserialiseInputError !InputDecodeError
| DeserialiseInputErrorFormatMismatch
deserialiseInput
:: forall a.
AsType a
-> NonEmpty (InputFormat a)
-> ByteString
-> Either InputDecodeError a
deserialiseInput :: 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) -> [InputFormat a]
forall a. NonEmpty a -> [a]
NE.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 :: 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 (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 :: 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 :: DeserialiseInputResult a
deserialiseHex
| ByteString -> Bool
isValidHex ByteString
inputBs =
DeserialiseInputResult a
-> (a -> DeserialiseInputResult a)
-> Maybe a
-> DeserialiseInputResult a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(InputDecodeError -> DeserialiseInputResult a
forall a. InputDecodeError -> DeserialiseInputResult a
DeserialiseInputError InputDecodeError
InputInvalidError)
a -> DeserialiseInputResult a
forall a. a -> DeserialiseInputResult a
DeserialiseInputSuccess
(AsType a -> ByteString -> Maybe a
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Maybe a
deserialiseFromRawBytesHex AsType a
asType ByteString
inputBs)
| 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 (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
hexAlpha) (Char -> Char
toLower (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 :: [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 (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
readKeyFile
:: AsType a
-> NonEmpty (InputFormat a)
-> FilePath
-> IO (Either (FileError InputDecodeError) a)
readKeyFile :: AsType a
-> NonEmpty (InputFormat a)
-> String
-> IO (Either (FileError InputDecodeError) a)
readKeyFile AsType a
asType NonEmpty (InputFormat a)
acceptedFormats String
path =
ExceptT (FileError InputDecodeError) IO a
-> IO (Either (FileError InputDecodeError) a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError InputDecodeError) IO a
-> IO (Either (FileError InputDecodeError) a))
-> ExceptT (FileError InputDecodeError) IO a
-> IO (Either (FileError InputDecodeError) a)
forall a b. (a -> b) -> a -> b
$ do
ByteString
content <- (IOException -> FileError InputDecodeError)
-> IO ByteString
-> ExceptT (FileError InputDecodeError) IO ByteString
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT (String -> IOException -> FileError InputDecodeError
forall e. String -> IOException -> FileError e
FileIOError String
path) (IO ByteString
-> ExceptT (FileError InputDecodeError) IO ByteString)
-> IO ByteString
-> ExceptT (FileError InputDecodeError) IO ByteString
forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
BS.readFile String
path
(InputDecodeError -> FileError InputDecodeError)
-> ExceptT InputDecodeError IO a
-> ExceptT (FileError InputDecodeError) IO a
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (String -> InputDecodeError -> FileError InputDecodeError
forall e. String -> e -> FileError e
FileError String
path) (ExceptT InputDecodeError IO a
-> ExceptT (FileError InputDecodeError) IO a)
-> ExceptT InputDecodeError IO a
-> ExceptT (FileError InputDecodeError) IO a
forall a b. (a -> b) -> a -> b
$ Either InputDecodeError a -> ExceptT InputDecodeError IO a
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either InputDecodeError a -> ExceptT InputDecodeError IO a)
-> Either InputDecodeError a -> ExceptT InputDecodeError IO a
forall a b. (a -> b) -> a -> b
$
AsType a
-> NonEmpty (InputFormat a)
-> ByteString
-> Either InputDecodeError a
forall a.
AsType a
-> NonEmpty (InputFormat a)
-> ByteString
-> Either InputDecodeError a
deserialiseInput AsType a
asType NonEmpty (InputFormat a)
acceptedFormats ByteString
content
readKeyFileTextEnvelope
:: HasTextEnvelope a
=> AsType a
-> FilePath
-> IO (Either (FileError InputDecodeError) a)
readKeyFileTextEnvelope :: AsType a -> String -> IO (Either (FileError InputDecodeError) a)
readKeyFileTextEnvelope AsType a
asType String
fp =
(FileError TextEnvelopeError -> FileError InputDecodeError)
-> Either (FileError TextEnvelopeError) a
-> Either (FileError InputDecodeError) a
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first FileError TextEnvelopeError -> FileError InputDecodeError
toInputDecodeError (Either (FileError TextEnvelopeError) a
-> Either (FileError InputDecodeError) a)
-> IO (Either (FileError TextEnvelopeError) a)
-> IO (Either (FileError InputDecodeError) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsType a -> String -> IO (Either (FileError TextEnvelopeError) a)
forall a.
HasTextEnvelope a =>
AsType a -> String -> IO (Either (FileError TextEnvelopeError) a)
readFileTextEnvelope AsType a
asType String
fp
where
toInputDecodeError
:: FileError TextEnvelopeError
-> FileError InputDecodeError
toInputDecodeError :: FileError TextEnvelopeError -> FileError InputDecodeError
toInputDecodeError FileError TextEnvelopeError
err =
case FileError TextEnvelopeError
err of
FileIOError String
path IOException
ex -> String -> IOException -> FileError InputDecodeError
forall e. String -> IOException -> FileError e
FileIOError String
path IOException
ex
FileError String
path TextEnvelopeError
textEnvErr ->
String -> InputDecodeError -> FileError InputDecodeError
forall e. String -> e -> FileError e
FileError String
path (TextEnvelopeError -> InputDecodeError
InputTextEnvelopeError TextEnvelopeError
textEnvErr)
FileErrorTempFile String
targetP String
tempP Handle
h ->
String -> String -> Handle -> FileError InputDecodeError
forall e. String -> String -> Handle -> FileError e
FileErrorTempFile String
targetP String
tempP Handle
h
readKeyFileAnyOf
:: forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> FilePath
-> IO (Either (FileError InputDecodeError) b)
readKeyFileAnyOf :: [FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> String
-> IO (Either (FileError InputDecodeError) b)
readKeyFileAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes String
path =
ExceptT (FileError InputDecodeError) IO b
-> IO (Either (FileError InputDecodeError) b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError InputDecodeError) IO b
-> IO (Either (FileError InputDecodeError) b))
-> ExceptT (FileError InputDecodeError) IO b
-> IO (Either (FileError InputDecodeError) b)
forall a b. (a -> b) -> a -> b
$ do
ByteString
content <- (IOException -> FileError InputDecodeError)
-> IO ByteString
-> ExceptT (FileError InputDecodeError) IO ByteString
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT (String -> IOException -> FileError InputDecodeError
forall e. String -> IOException -> FileError e
FileIOError String
path) (IO ByteString
-> ExceptT (FileError InputDecodeError) IO ByteString)
-> IO ByteString
-> ExceptT (FileError InputDecodeError) IO ByteString
forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
BS.readFile String
path
(InputDecodeError -> FileError InputDecodeError)
-> ExceptT InputDecodeError IO b
-> ExceptT (FileError InputDecodeError) IO b
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (String -> InputDecodeError -> FileError InputDecodeError
forall e. String -> e -> FileError e
FileError String
path) (ExceptT InputDecodeError IO b
-> ExceptT (FileError InputDecodeError) IO b)
-> ExceptT InputDecodeError IO b
-> ExceptT (FileError InputDecodeError) IO b
forall a b. (a -> b) -> a -> b
$ Either InputDecodeError b -> ExceptT InputDecodeError IO b
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either InputDecodeError b -> ExceptT InputDecodeError IO b)
-> Either InputDecodeError b -> ExceptT InputDecodeError IO b
forall a b. (a -> b) -> a -> b
$
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> ByteString
-> Either InputDecodeError b
forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> ByteString
-> Either InputDecodeError b
deserialiseInputAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes ByteString
content
readSigningKeyFile
:: forall keyrole.
( HasTextEnvelope (SigningKey keyrole)
, SerialiseAsBech32 (SigningKey keyrole)
)
=> AsType keyrole
-> SigningKeyFile
-> IO (Either (FileError InputDecodeError) (SigningKey keyrole))
readSigningKeyFile :: AsType keyrole
-> SigningKeyFile
-> IO (Either (FileError InputDecodeError) (SigningKey keyrole))
readSigningKeyFile AsType keyrole
asType (SigningKeyFile String
fp) =
AsType (SigningKey keyrole)
-> NonEmpty (InputFormat (SigningKey keyrole))
-> String
-> IO (Either (FileError InputDecodeError) (SigningKey keyrole))
forall a.
AsType a
-> NonEmpty (InputFormat a)
-> String
-> IO (Either (FileError InputDecodeError) a)
readKeyFile
(AsType keyrole -> AsType (SigningKey keyrole)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType keyrole
asType)
([InputFormat (SigningKey keyrole)]
-> NonEmpty (InputFormat (SigningKey keyrole))
forall a. [a] -> NonEmpty a
NE.fromList [InputFormat (SigningKey keyrole)
forall a. SerialiseAsBech32 a => InputFormat a
InputFormatBech32, InputFormat (SigningKey keyrole)
forall a. SerialiseAsRawBytes a => InputFormat a
InputFormatHex, InputFormat (SigningKey keyrole)
forall a. HasTextEnvelope a => InputFormat a
InputFormatTextEnvelope])
String
fp
readSigningKeyFileAnyOf
:: forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> SigningKeyFile
-> IO (Either (FileError InputDecodeError) b)
readSigningKeyFileAnyOf :: [FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> SigningKeyFile
-> IO (Either (FileError InputDecodeError) b)
readSigningKeyFileAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes (SigningKeyFile String
fp) =
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> String
-> IO (Either (FileError InputDecodeError) b)
forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> String
-> IO (Either (FileError InputDecodeError) b)
readKeyFileAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes String
fp
data VerificationKeyOrFile keyrole
= VerificationKeyValue !(VerificationKey keyrole)
| VerificationKeyFilePath !VerificationKeyFile
deriving instance Show (VerificationKey keyrole)
=> Show (VerificationKeyOrFile keyrole)
deriving instance Eq (VerificationKey keyrole)
=> Eq (VerificationKeyOrFile keyrole)
readVerificationKeyOrFile
:: ( HasTextEnvelope (VerificationKey keyrole)
, SerialiseAsBech32 (VerificationKey keyrole)
)
=> AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO (Either (FileError InputDecodeError) (VerificationKey keyrole))
readVerificationKeyOrFile :: AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
readVerificationKeyOrFile AsType keyrole
asType VerificationKeyOrFile keyrole
verKeyOrFile =
case VerificationKeyOrFile keyrole
verKeyOrFile of
VerificationKeyValue VerificationKey keyrole
vk -> Either (FileError InputDecodeError) (VerificationKey keyrole)
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VerificationKey keyrole
-> Either (FileError InputDecodeError) (VerificationKey keyrole)
forall a b. b -> Either a b
Right VerificationKey keyrole
vk)
VerificationKeyFilePath (VerificationKeyFile String
fp) ->
AsType (VerificationKey keyrole)
-> NonEmpty (InputFormat (VerificationKey keyrole))
-> String
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
forall a.
AsType a
-> NonEmpty (InputFormat a)
-> String
-> IO (Either (FileError InputDecodeError) a)
readKeyFile
(AsType keyrole -> AsType (VerificationKey keyrole)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType keyrole
asType)
([InputFormat (VerificationKey keyrole)]
-> NonEmpty (InputFormat (VerificationKey keyrole))
forall a. [a] -> NonEmpty a
NE.fromList [InputFormat (VerificationKey keyrole)
forall a. SerialiseAsBech32 a => InputFormat a
InputFormatBech32, InputFormat (VerificationKey keyrole)
forall a. SerialiseAsRawBytes a => InputFormat a
InputFormatHex, InputFormat (VerificationKey keyrole)
forall a. HasTextEnvelope a => InputFormat a
InputFormatTextEnvelope])
String
fp
readVerificationKeyOrTextEnvFile
:: HasTextEnvelope (VerificationKey keyrole)
=> AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO (Either (FileError InputDecodeError) (VerificationKey keyrole))
readVerificationKeyOrTextEnvFile :: AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
readVerificationKeyOrTextEnvFile AsType keyrole
asType VerificationKeyOrFile keyrole
verKeyOrFile =
case VerificationKeyOrFile keyrole
verKeyOrFile of
VerificationKeyValue VerificationKey keyrole
vk -> Either (FileError InputDecodeError) (VerificationKey keyrole)
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VerificationKey keyrole
-> Either (FileError InputDecodeError) (VerificationKey keyrole)
forall a b. b -> Either a b
Right VerificationKey keyrole
vk)
VerificationKeyFilePath (VerificationKeyFile String
fp) ->
AsType (VerificationKey keyrole)
-> String
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
forall a.
HasTextEnvelope a =>
AsType a -> String -> IO (Either (FileError InputDecodeError) a)
readKeyFileTextEnvelope (AsType keyrole -> AsType (VerificationKey keyrole)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType keyrole
asType) String
fp
data PaymentVerifier
= PaymentVerifierKey VerificationKeyTextOrFile
| PaymentVerifierScriptFile ScriptFile
deriving (PaymentVerifier -> PaymentVerifier -> Bool
(PaymentVerifier -> PaymentVerifier -> Bool)
-> (PaymentVerifier -> PaymentVerifier -> Bool)
-> Eq PaymentVerifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentVerifier -> PaymentVerifier -> Bool
$c/= :: PaymentVerifier -> PaymentVerifier -> Bool
== :: PaymentVerifier -> PaymentVerifier -> Bool
$c== :: PaymentVerifier -> PaymentVerifier -> Bool
Eq, Int -> PaymentVerifier -> ShowS
[PaymentVerifier] -> ShowS
PaymentVerifier -> String
(Int -> PaymentVerifier -> ShowS)
-> (PaymentVerifier -> String)
-> ([PaymentVerifier] -> ShowS)
-> Show PaymentVerifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentVerifier] -> ShowS
$cshowList :: [PaymentVerifier] -> ShowS
show :: PaymentVerifier -> String
$cshow :: PaymentVerifier -> String
showsPrec :: Int -> PaymentVerifier -> ShowS
$cshowsPrec :: Int -> PaymentVerifier -> ShowS
Show)
data StakeVerifier
= StakeVerifierKey (VerificationKeyOrFile StakeKey)
| StakeVerifierScriptFile ScriptFile
deriving (StakeVerifier -> StakeVerifier -> Bool
(StakeVerifier -> StakeVerifier -> Bool)
-> (StakeVerifier -> StakeVerifier -> Bool) -> Eq StakeVerifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakeVerifier -> StakeVerifier -> Bool
$c/= :: StakeVerifier -> StakeVerifier -> Bool
== :: StakeVerifier -> StakeVerifier -> Bool
$c== :: StakeVerifier -> StakeVerifier -> Bool
Eq, Int -> StakeVerifier -> ShowS
[StakeVerifier] -> ShowS
StakeVerifier -> String
(Int -> StakeVerifier -> ShowS)
-> (StakeVerifier -> String)
-> ([StakeVerifier] -> ShowS)
-> Show StakeVerifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakeVerifier] -> ShowS
$cshowList :: [StakeVerifier] -> ShowS
show :: StakeVerifier -> String
$cshow :: StakeVerifier -> String
showsPrec :: Int -> StakeVerifier -> ShowS
$cshowsPrec :: Int -> StakeVerifier -> ShowS
Show)
data VerificationKeyTextOrFile
= VktofVerificationKeyText !Text
| VktofVerificationKeyFile !VerificationKeyFile
deriving (VerificationKeyTextOrFile -> VerificationKeyTextOrFile -> Bool
(VerificationKeyTextOrFile -> VerificationKeyTextOrFile -> Bool)
-> (VerificationKeyTextOrFile -> VerificationKeyTextOrFile -> Bool)
-> Eq VerificationKeyTextOrFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKeyTextOrFile -> VerificationKeyTextOrFile -> Bool
$c/= :: VerificationKeyTextOrFile -> VerificationKeyTextOrFile -> Bool
== :: VerificationKeyTextOrFile -> VerificationKeyTextOrFile -> Bool
$c== :: VerificationKeyTextOrFile -> VerificationKeyTextOrFile -> Bool
Eq, Int -> VerificationKeyTextOrFile -> ShowS
[VerificationKeyTextOrFile] -> ShowS
VerificationKeyTextOrFile -> String
(Int -> VerificationKeyTextOrFile -> ShowS)
-> (VerificationKeyTextOrFile -> String)
-> ([VerificationKeyTextOrFile] -> ShowS)
-> Show VerificationKeyTextOrFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKeyTextOrFile] -> ShowS
$cshowList :: [VerificationKeyTextOrFile] -> ShowS
show :: VerificationKeyTextOrFile -> String
$cshow :: VerificationKeyTextOrFile -> String
showsPrec :: Int -> VerificationKeyTextOrFile -> ShowS
$cshowsPrec :: Int -> VerificationKeyTextOrFile -> ShowS
Show)
data VerificationKeyTextOrFileError
= VerificationKeyTextError !InputDecodeError
| VerificationKeyFileError !(FileError InputDecodeError)
deriving Int -> VerificationKeyTextOrFileError -> ShowS
[VerificationKeyTextOrFileError] -> ShowS
VerificationKeyTextOrFileError -> String
(Int -> VerificationKeyTextOrFileError -> ShowS)
-> (VerificationKeyTextOrFileError -> String)
-> ([VerificationKeyTextOrFileError] -> ShowS)
-> Show VerificationKeyTextOrFileError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKeyTextOrFileError] -> ShowS
$cshowList :: [VerificationKeyTextOrFileError] -> ShowS
show :: VerificationKeyTextOrFileError -> String
$cshow :: VerificationKeyTextOrFileError -> String
showsPrec :: Int -> VerificationKeyTextOrFileError -> ShowS
$cshowsPrec :: Int -> VerificationKeyTextOrFileError -> ShowS
Show
renderVerificationKeyTextOrFileError :: VerificationKeyTextOrFileError -> Text
renderVerificationKeyTextOrFileError :: VerificationKeyTextOrFileError -> Text
renderVerificationKeyTextOrFileError VerificationKeyTextOrFileError
vkTextOrFileErr =
case VerificationKeyTextOrFileError
vkTextOrFileErr of
VerificationKeyTextError InputDecodeError
err -> InputDecodeError -> Text
renderInputDecodeError InputDecodeError
err
VerificationKeyFileError FileError InputDecodeError
err -> String -> Text
Text.pack (FileError InputDecodeError -> String
forall e. Error e => e -> String
displayError FileError InputDecodeError
err)
readVerificationKeyTextOrFileAnyOf
:: forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> VerificationKeyTextOrFile
-> IO (Either VerificationKeyTextOrFileError b)
readVerificationKeyTextOrFileAnyOf :: [FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> VerificationKeyTextOrFile
-> IO (Either VerificationKeyTextOrFileError b)
readVerificationKeyTextOrFileAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes VerificationKeyTextOrFile
verKeyTextOrFile =
case VerificationKeyTextOrFile
verKeyTextOrFile of
VktofVerificationKeyText Text
vkText ->
Either VerificationKeyTextOrFileError b
-> IO (Either VerificationKeyTextOrFileError b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either VerificationKeyTextOrFileError b
-> IO (Either VerificationKeyTextOrFileError b))
-> Either VerificationKeyTextOrFileError b
-> IO (Either VerificationKeyTextOrFileError b)
forall a b. (a -> b) -> a -> b
$ (InputDecodeError -> VerificationKeyTextOrFileError)
-> Either InputDecodeError b
-> Either VerificationKeyTextOrFileError b
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first InputDecodeError -> VerificationKeyTextOrFileError
VerificationKeyTextError (Either InputDecodeError b
-> Either VerificationKeyTextOrFileError b)
-> Either InputDecodeError b
-> Either VerificationKeyTextOrFileError b
forall a b. (a -> b) -> a -> b
$
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> ByteString
-> Either InputDecodeError b
forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> ByteString
-> Either InputDecodeError b
deserialiseInputAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes (Text -> ByteString
Text.encodeUtf8 Text
vkText)
VktofVerificationKeyFile (VerificationKeyFile String
fp) ->
(FileError InputDecodeError -> VerificationKeyTextOrFileError)
-> Either (FileError InputDecodeError) b
-> Either VerificationKeyTextOrFileError b
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first FileError InputDecodeError -> VerificationKeyTextOrFileError
VerificationKeyFileError
(Either (FileError InputDecodeError) b
-> Either VerificationKeyTextOrFileError b)
-> IO (Either (FileError InputDecodeError) b)
-> IO (Either VerificationKeyTextOrFileError b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> String
-> IO (Either (FileError InputDecodeError) b)
forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> String
-> IO (Either (FileError InputDecodeError) b)
readKeyFileAnyOf [FromSomeType SerialiseAsBech32 b]
bech32Types [FromSomeType HasTextEnvelope b]
textEnvTypes String
fp
data VerificationKeyOrHashOrFile keyrole
= VerificationKeyOrFile !(VerificationKeyOrFile keyrole)
| VerificationKeyHash !(Hash keyrole)
deriving instance (Show (VerificationKeyOrFile keyrole), Show (Hash keyrole))
=> Show (VerificationKeyOrHashOrFile keyrole)
deriving instance (Eq (VerificationKeyOrFile keyrole), Eq (Hash keyrole))
=> Eq (VerificationKeyOrHashOrFile keyrole)
readVerificationKeyOrHashOrFile
:: (Key keyrole, SerialiseAsBech32 (VerificationKey keyrole))
=> AsType keyrole
-> VerificationKeyOrHashOrFile keyrole
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
readVerificationKeyOrHashOrFile :: AsType keyrole
-> VerificationKeyOrHashOrFile keyrole
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
readVerificationKeyOrHashOrFile AsType keyrole
asType VerificationKeyOrHashOrFile keyrole
verKeyOrHashOrFile =
case VerificationKeyOrHashOrFile keyrole
verKeyOrHashOrFile of
VerificationKeyOrFile VerificationKeyOrFile keyrole
vkOrFile -> do
Either (FileError InputDecodeError) (VerificationKey keyrole)
eitherVk <- AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
forall keyrole.
(HasTextEnvelope (VerificationKey keyrole),
SerialiseAsBech32 (VerificationKey keyrole)) =>
AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
readVerificationKeyOrFile AsType keyrole
asType VerificationKeyOrFile keyrole
vkOrFile
Either (FileError InputDecodeError) (Hash keyrole)
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VerificationKey keyrole -> Hash keyrole
forall keyrole.
Key keyrole =>
VerificationKey keyrole -> Hash keyrole
verificationKeyHash (VerificationKey keyrole -> Hash keyrole)
-> Either (FileError InputDecodeError) (VerificationKey keyrole)
-> Either (FileError InputDecodeError) (Hash keyrole)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either (FileError InputDecodeError) (VerificationKey keyrole)
eitherVk)
VerificationKeyHash Hash keyrole
vkHash -> Either (FileError InputDecodeError) (Hash keyrole)
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Hash keyrole -> Either (FileError InputDecodeError) (Hash keyrole)
forall a b. b -> Either a b
Right Hash keyrole
vkHash)
readVerificationKeyOrHashOrTextEnvFile
:: Key keyrole
=> AsType keyrole
-> VerificationKeyOrHashOrFile keyrole
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
readVerificationKeyOrHashOrTextEnvFile :: AsType keyrole
-> VerificationKeyOrHashOrFile keyrole
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
readVerificationKeyOrHashOrTextEnvFile AsType keyrole
asType VerificationKeyOrHashOrFile keyrole
verKeyOrHashOrFile =
case VerificationKeyOrHashOrFile keyrole
verKeyOrHashOrFile of
VerificationKeyOrFile VerificationKeyOrFile keyrole
vkOrFile -> do
Either (FileError InputDecodeError) (VerificationKey keyrole)
eitherVk <- AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
forall keyrole.
HasTextEnvelope (VerificationKey keyrole) =>
AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
readVerificationKeyOrTextEnvFile AsType keyrole
asType VerificationKeyOrFile keyrole
vkOrFile
Either (FileError InputDecodeError) (Hash keyrole)
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VerificationKey keyrole -> Hash keyrole
forall keyrole.
Key keyrole =>
VerificationKey keyrole -> Hash keyrole
verificationKeyHash (VerificationKey keyrole -> Hash keyrole)
-> Either (FileError InputDecodeError) (VerificationKey keyrole)
-> Either (FileError InputDecodeError) (Hash keyrole)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either (FileError InputDecodeError) (VerificationKey keyrole)
eitherVk)
VerificationKeyHash Hash keyrole
vkHash -> Either (FileError InputDecodeError) (Hash keyrole)
-> IO (Either (FileError InputDecodeError) (Hash keyrole))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Hash keyrole -> Either (FileError InputDecodeError) (Hash keyrole)
forall a b. b -> Either a b
Right Hash keyrole
vkHash)