{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Cardano.CLI.Shelley.Run.Address
( ShelleyAddressCmdError(..)
, SomeAddressVerificationKey(..)
, buildShelleyAddress
, renderShelleyAddressCmdError
, runAddressCmd
, runAddressKeyGenToFile
, makeStakeAddressRef
) where
import Cardano.Prelude hiding (putStrLn)
import Control.Monad.Trans.Except.Extra (firstExceptT, left, newExceptT)
import qualified Data.ByteString.Char8 as BS
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import Cardano.Api
import Cardano.Api.Shelley
import Cardano.CLI.Shelley.Key (PaymentVerifier (..), StakeVerifier (..),
VerificationKeyTextOrFile, VerificationKeyTextOrFileError (..), generateKeyPair,
readVerificationKeyOrFile, readVerificationKeyTextOrFileAnyOf,
renderVerificationKeyTextOrFileError)
import Cardano.CLI.Shelley.Parsers (AddressCmd (..), AddressKeyType (..), OutputFile (..))
import Cardano.CLI.Shelley.Run.Address.Info (ShelleyAddressInfoError, runAddressInfo)
import Cardano.CLI.Shelley.Run.Read
import Cardano.CLI.Types
data ShelleyAddressCmdError
= ShelleyAddressCmdAddressInfoError !ShelleyAddressInfoError
| ShelleyAddressCmdReadKeyFileError !(FileError InputDecodeError)
| ShelleyAddressCmdReadScriptFileError !(FileError ScriptDecodeError)
| ShelleyAddressCmdVerificationKeyTextOrFileError !VerificationKeyTextOrFileError
| ShelleyAddressCmdWriteFileError !(FileError ())
| ShelleyAddressCmdExpectedPaymentVerificationKey SomeAddressVerificationKey
deriving Int -> ShelleyAddressCmdError -> ShowS
[ShelleyAddressCmdError] -> ShowS
ShelleyAddressCmdError -> String
(Int -> ShelleyAddressCmdError -> ShowS)
-> (ShelleyAddressCmdError -> String)
-> ([ShelleyAddressCmdError] -> ShowS)
-> Show ShelleyAddressCmdError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShelleyAddressCmdError] -> ShowS
$cshowList :: [ShelleyAddressCmdError] -> ShowS
show :: ShelleyAddressCmdError -> String
$cshow :: ShelleyAddressCmdError -> String
showsPrec :: Int -> ShelleyAddressCmdError -> ShowS
$cshowsPrec :: Int -> ShelleyAddressCmdError -> ShowS
Show
renderShelleyAddressCmdError :: ShelleyAddressCmdError -> Text
renderShelleyAddressCmdError :: ShelleyAddressCmdError -> Text
renderShelleyAddressCmdError ShelleyAddressCmdError
err =
case ShelleyAddressCmdError
err of
ShelleyAddressCmdAddressInfoError ShelleyAddressInfoError
addrInfoErr ->
String -> Text
Text.pack (ShelleyAddressInfoError -> String
forall e. Error e => e -> String
displayError ShelleyAddressInfoError
addrInfoErr)
ShelleyAddressCmdReadKeyFileError FileError InputDecodeError
fileErr ->
String -> Text
Text.pack (FileError InputDecodeError -> String
forall e. Error e => e -> String
displayError FileError InputDecodeError
fileErr)
ShelleyAddressCmdVerificationKeyTextOrFileError VerificationKeyTextOrFileError
vkTextOrFileErr ->
VerificationKeyTextOrFileError -> Text
renderVerificationKeyTextOrFileError VerificationKeyTextOrFileError
vkTextOrFileErr
ShelleyAddressCmdReadScriptFileError FileError ScriptDecodeError
fileErr ->
String -> Text
Text.pack (FileError ScriptDecodeError -> String
forall e. Error e => e -> String
displayError FileError ScriptDecodeError
fileErr)
ShelleyAddressCmdWriteFileError FileError ()
fileErr -> String -> Text
Text.pack (FileError () -> String
forall e. Error e => e -> String
displayError FileError ()
fileErr)
ShelleyAddressCmdExpectedPaymentVerificationKey SomeAddressVerificationKey
someAddress ->
Text
"Expected payment verification key but got: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SomeAddressVerificationKey -> Text
renderSomeAddressVerificationKey SomeAddressVerificationKey
someAddress
runAddressCmd :: AddressCmd -> ExceptT ShelleyAddressCmdError IO ()
runAddressCmd :: AddressCmd -> ExceptT ShelleyAddressCmdError IO ()
runAddressCmd AddressCmd
cmd =
case AddressCmd
cmd of
AddressKeyGen AddressKeyType
kt VerificationKeyFile
vkf SigningKeyFile
skf -> AddressKeyType
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
runAddressKeyGenToFile AddressKeyType
kt VerificationKeyFile
vkf SigningKeyFile
skf
AddressKeyHash VerificationKeyTextOrFile
vkf Maybe OutputFile
mOFp -> VerificationKeyTextOrFile
-> Maybe OutputFile -> ExceptT ShelleyAddressCmdError IO ()
runAddressKeyHash VerificationKeyTextOrFile
vkf Maybe OutputFile
mOFp
AddressBuild PaymentVerifier
paymentVerifier Maybe StakeVerifier
mbStakeVerifier NetworkId
nw Maybe OutputFile
mOutFp -> PaymentVerifier
-> Maybe StakeVerifier
-> NetworkId
-> Maybe OutputFile
-> ExceptT ShelleyAddressCmdError IO ()
runAddressBuild PaymentVerifier
paymentVerifier Maybe StakeVerifier
mbStakeVerifier NetworkId
nw Maybe OutputFile
mOutFp
AddressInfo Text
txt Maybe OutputFile
mOFp -> (ShelleyAddressInfoError -> ShelleyAddressCmdError)
-> ExceptT ShelleyAddressInfoError IO ()
-> ExceptT ShelleyAddressCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ShelleyAddressInfoError -> ShelleyAddressCmdError
ShelleyAddressCmdAddressInfoError (ExceptT ShelleyAddressInfoError IO ()
-> ExceptT ShelleyAddressCmdError IO ())
-> ExceptT ShelleyAddressInfoError IO ()
-> ExceptT ShelleyAddressCmdError IO ()
forall a b. (a -> b) -> a -> b
$ Text -> Maybe OutputFile -> ExceptT ShelleyAddressInfoError IO ()
runAddressInfo Text
txt Maybe OutputFile
mOFp
runAddressKeyGenToFile
:: AddressKeyType
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
runAddressKeyGenToFile :: AddressKeyType
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
runAddressKeyGenToFile AddressKeyType
kt VerificationKeyFile
vkf SigningKeyFile
skf = case AddressKeyType
kt of
AddressKeyType
AddressKeyShelley -> AsType PaymentKey
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
forall keyrole.
Key keyrole =>
AsType keyrole
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
generateAndWriteKeyFiles AsType PaymentKey
AsPaymentKey VerificationKeyFile
vkf SigningKeyFile
skf
AddressKeyType
AddressKeyShelleyExtended -> AsType PaymentExtendedKey
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
forall keyrole.
Key keyrole =>
AsType keyrole
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
generateAndWriteKeyFiles AsType PaymentExtendedKey
AsPaymentExtendedKey VerificationKeyFile
vkf SigningKeyFile
skf
AddressKeyType
AddressKeyByron -> AsType ByronKey
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
forall keyrole.
Key keyrole =>
AsType keyrole
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
generateAndWriteKeyFiles AsType ByronKey
AsByronKey VerificationKeyFile
vkf SigningKeyFile
skf
generateAndWriteKeyFiles
:: Key keyrole
=> AsType keyrole
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
generateAndWriteKeyFiles :: AsType keyrole
-> VerificationKeyFile
-> SigningKeyFile
-> ExceptT ShelleyAddressCmdError IO ()
generateAndWriteKeyFiles AsType keyrole
asType VerificationKeyFile
vkf SigningKeyFile
skf = do
(VerificationKey keyrole
-> SigningKey keyrole -> ExceptT ShelleyAddressCmdError IO ())
-> (VerificationKey keyrole, SigningKey keyrole)
-> ExceptT ShelleyAddressCmdError IO ()
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (VerificationKeyFile
-> SigningKeyFile
-> VerificationKey keyrole
-> SigningKey keyrole
-> ExceptT ShelleyAddressCmdError IO ()
forall keyrole.
Key keyrole =>
VerificationKeyFile
-> SigningKeyFile
-> VerificationKey keyrole
-> SigningKey keyrole
-> ExceptT ShelleyAddressCmdError IO ()
writePaymentKeyFiles VerificationKeyFile
vkf SigningKeyFile
skf) ((VerificationKey keyrole, SigningKey keyrole)
-> ExceptT ShelleyAddressCmdError IO ())
-> ExceptT
ShelleyAddressCmdError
IO
(VerificationKey keyrole, SigningKey keyrole)
-> ExceptT ShelleyAddressCmdError IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (VerificationKey keyrole, SigningKey keyrole)
-> ExceptT
ShelleyAddressCmdError
IO
(VerificationKey keyrole, SigningKey keyrole)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (AsType keyrole -> IO (VerificationKey keyrole, SigningKey keyrole)
forall keyrole.
Key keyrole =>
AsType keyrole -> IO (VerificationKey keyrole, SigningKey keyrole)
generateKeyPair AsType keyrole
asType)
writePaymentKeyFiles
:: Key keyrole
=> VerificationKeyFile
-> SigningKeyFile
-> VerificationKey keyrole
-> SigningKey keyrole
-> ExceptT ShelleyAddressCmdError IO ()
writePaymentKeyFiles :: VerificationKeyFile
-> SigningKeyFile
-> VerificationKey keyrole
-> SigningKey keyrole
-> ExceptT ShelleyAddressCmdError IO ()
writePaymentKeyFiles (VerificationKeyFile String
vkeyPath) (SigningKeyFile String
skeyPath) VerificationKey keyrole
vkey SigningKey keyrole
skey = do
(FileError () -> ShelleyAddressCmdError)
-> ExceptT (FileError ()) IO ()
-> ExceptT ShelleyAddressCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> ShelleyAddressCmdError
ShelleyAddressCmdWriteFileError (ExceptT (FileError ()) IO ()
-> ExceptT ShelleyAddressCmdError IO ())
-> ExceptT (FileError ()) IO ()
-> ExceptT ShelleyAddressCmdError IO ()
forall a b. (a -> b) -> a -> b
$ do
IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall a b. (a -> b) -> a -> b
$ String
-> Maybe TextEnvelopeDescr
-> SigningKey keyrole
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
skeyPath (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
skeyDesc) SigningKey keyrole
skey
IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall a b. (a -> b) -> a -> b
$ String
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
vkeyPath (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
vkeyDesc) VerificationKey keyrole
vkey
where
skeyDesc, vkeyDesc :: TextEnvelopeDescr
skeyDesc :: TextEnvelopeDescr
skeyDesc = TextEnvelopeDescr
"Payment Signing Key"
vkeyDesc :: TextEnvelopeDescr
vkeyDesc = TextEnvelopeDescr
"Payment Verification Key"
runAddressKeyHash :: VerificationKeyTextOrFile
-> Maybe OutputFile
-> ExceptT ShelleyAddressCmdError IO ()
runAddressKeyHash :: VerificationKeyTextOrFile
-> Maybe OutputFile -> ExceptT ShelleyAddressCmdError IO ()
runAddressKeyHash VerificationKeyTextOrFile
vkeyTextOrFile Maybe OutputFile
mOutputFp = do
SomeAddressVerificationKey
vkey <- (VerificationKeyTextOrFileError -> ShelleyAddressCmdError)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT ShelleyAddressCmdError IO SomeAddressVerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT VerificationKeyTextOrFileError -> ShelleyAddressCmdError
ShelleyAddressCmdVerificationKeyTextOrFileError (ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT ShelleyAddressCmdError IO SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT ShelleyAddressCmdError IO SomeAddressVerificationKey
forall a b. (a -> b) -> a -> b
$
IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey)
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
forall a b. (a -> b) -> a -> b
$ VerificationKeyTextOrFile
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
readVerificationKeyTextOrFileAnyOf VerificationKeyTextOrFile
vkeyTextOrFile
let hexKeyHash :: ByteString
hexKeyHash = (forall keyrole.
Key keyrole =>
VerificationKey keyrole -> ByteString)
-> SomeAddressVerificationKey -> ByteString
forall a.
(forall keyrole. Key keyrole => VerificationKey keyrole -> a)
-> SomeAddressVerificationKey -> a
foldSomeAddressVerificationKey
(Hash keyrole -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytesHex (Hash keyrole -> ByteString)
-> (VerificationKey keyrole -> Hash keyrole)
-> VerificationKey keyrole
-> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. VerificationKey keyrole -> Hash keyrole
forall keyrole.
Key keyrole =>
VerificationKey keyrole -> Hash keyrole
verificationKeyHash) SomeAddressVerificationKey
vkey
case Maybe OutputFile
mOutputFp of
Just (OutputFile String
fpath) -> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ShelleyAddressCmdError IO ())
-> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
BS.writeFile String
fpath ByteString
hexKeyHash
Maybe OutputFile
Nothing -> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ShelleyAddressCmdError IO ())
-> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> IO ()
BS.putStrLn ByteString
hexKeyHash
runAddressBuild :: PaymentVerifier
-> Maybe StakeVerifier
-> NetworkId
-> Maybe OutputFile
-> ExceptT ShelleyAddressCmdError IO ()
runAddressBuild :: PaymentVerifier
-> Maybe StakeVerifier
-> NetworkId
-> Maybe OutputFile
-> ExceptT ShelleyAddressCmdError IO ()
runAddressBuild PaymentVerifier
paymentVerifier Maybe StakeVerifier
mbStakeVerifier NetworkId
nw Maybe OutputFile
mOutFp = do
Text
outText <- case PaymentVerifier
paymentVerifier of
PaymentVerifierKey VerificationKeyTextOrFile
payVkeyTextOrFile -> do
SomeAddressVerificationKey
payVKey <- (VerificationKeyTextOrFileError -> ShelleyAddressCmdError)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT ShelleyAddressCmdError IO SomeAddressVerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT VerificationKeyTextOrFileError -> ShelleyAddressCmdError
ShelleyAddressCmdVerificationKeyTextOrFileError (ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT ShelleyAddressCmdError IO SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT ShelleyAddressCmdError IO SomeAddressVerificationKey
forall a b. (a -> b) -> a -> b
$
IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey)
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
forall a b. (a -> b) -> a -> b
$ VerificationKeyTextOrFile
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
readVerificationKeyTextOrFileAnyOf VerificationKeyTextOrFile
payVkeyTextOrFile
AddressAny
addr <- case SomeAddressVerificationKey
payVKey of
AByronVerificationKey VerificationKey ByronKey
vk ->
AddressAny -> ExceptT ShelleyAddressCmdError IO AddressAny
forall (m :: * -> *) a. Monad m => a -> m a
return (Address ByronAddr -> AddressAny
AddressByron (NetworkId -> VerificationKey ByronKey -> Address ByronAddr
makeByronAddress NetworkId
nw VerificationKey ByronKey
vk))
APaymentVerificationKey VerificationKey PaymentKey
vk ->
Address ShelleyAddr -> AddressAny
AddressShelley (Address ShelleyAddr -> AddressAny)
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
-> ExceptT ShelleyAddressCmdError IO AddressAny
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> VerificationKey PaymentKey
-> Maybe StakeVerifier
-> NetworkId
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
buildShelleyAddress VerificationKey PaymentKey
vk Maybe StakeVerifier
mbStakeVerifier NetworkId
nw
APaymentExtendedVerificationKey VerificationKey PaymentExtendedKey
vk ->
Address ShelleyAddr -> AddressAny
AddressShelley (Address ShelleyAddr -> AddressAny)
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
-> ExceptT ShelleyAddressCmdError IO AddressAny
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> VerificationKey PaymentKey
-> Maybe StakeVerifier
-> NetworkId
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
buildShelleyAddress (VerificationKey PaymentExtendedKey -> VerificationKey PaymentKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey PaymentExtendedKey
vk) Maybe StakeVerifier
mbStakeVerifier NetworkId
nw
AGenesisUTxOVerificationKey VerificationKey GenesisUTxOKey
vk ->
Address ShelleyAddr -> AddressAny
AddressShelley (Address ShelleyAddr -> AddressAny)
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
-> ExceptT ShelleyAddressCmdError IO AddressAny
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> VerificationKey PaymentKey
-> Maybe StakeVerifier
-> NetworkId
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
buildShelleyAddress (VerificationKey GenesisUTxOKey -> VerificationKey PaymentKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisUTxOKey
vk) Maybe StakeVerifier
mbStakeVerifier NetworkId
nw
SomeAddressVerificationKey
nonPaymentKey ->
ShelleyAddressCmdError
-> ExceptT ShelleyAddressCmdError IO AddressAny
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left (ShelleyAddressCmdError
-> ExceptT ShelleyAddressCmdError IO AddressAny)
-> ShelleyAddressCmdError
-> ExceptT ShelleyAddressCmdError IO AddressAny
forall a b. (a -> b) -> a -> b
$ SomeAddressVerificationKey -> ShelleyAddressCmdError
ShelleyAddressCmdExpectedPaymentVerificationKey SomeAddressVerificationKey
nonPaymentKey
Text -> ExceptT ShelleyAddressCmdError IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ExceptT ShelleyAddressCmdError IO Text)
-> Text -> ExceptT ShelleyAddressCmdError IO Text
forall a b. (a -> b) -> a -> b
$ AddressAny -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress (AddressAny
addr :: AddressAny)
PaymentVerifierScriptFile (ScriptFile String
fp) -> do
ScriptInAnyLang ScriptLanguage lang
_lang Script lang
script <-
(FileError ScriptDecodeError -> ShelleyAddressCmdError)
-> ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
-> ExceptT ShelleyAddressCmdError IO ScriptInAnyLang
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError ScriptDecodeError -> ShelleyAddressCmdError
ShelleyAddressCmdReadScriptFileError (ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
-> ExceptT ShelleyAddressCmdError IO ScriptInAnyLang)
-> ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
-> ExceptT ShelleyAddressCmdError IO ScriptInAnyLang
forall a b. (a -> b) -> a -> b
$
String -> ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
readFileScriptInAnyLang String
fp
let payCred :: PaymentCredential
payCred = ScriptHash -> PaymentCredential
PaymentCredentialByScript (Script lang -> ScriptHash
forall lang. Script lang -> ScriptHash
hashScript Script lang
script)
StakeAddressReference
stakeAddressReference <- ExceptT ShelleyAddressCmdError IO StakeAddressReference
-> (StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference)
-> Maybe StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (StakeAddressReference
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall (m :: * -> *) a. Monad m => a -> m a
return StakeAddressReference
NoStakeAddress) StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
makeStakeAddressRef Maybe StakeVerifier
mbStakeVerifier
Text -> ExceptT ShelleyAddressCmdError IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ExceptT ShelleyAddressCmdError IO Text)
-> Text -> ExceptT ShelleyAddressCmdError IO Text
forall a b. (a -> b) -> a -> b
$ Address ShelleyAddr -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress (Address ShelleyAddr -> Text)
-> (StakeAddressReference -> Address ShelleyAddr)
-> StakeAddressReference
-> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
makeShelleyAddress NetworkId
nw PaymentCredential
payCred (StakeAddressReference -> Text) -> StakeAddressReference -> Text
forall a b. (a -> b) -> a -> b
$ StakeAddressReference
stakeAddressReference
case Maybe OutputFile
mOutFp of
Just (OutputFile String
fpath) -> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ShelleyAddressCmdError IO ())
-> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text -> IO ()
Text.writeFile String
fpath Text
outText
Maybe OutputFile
Nothing -> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> ExceptT ShelleyAddressCmdError IO ())
-> IO () -> ExceptT ShelleyAddressCmdError IO ()
forall a b. (a -> b) -> a -> b
$ Text -> IO ()
Text.putStr Text
outText
makeStakeAddressRef
:: StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
makeStakeAddressRef :: StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
makeStakeAddressRef StakeVerifier
stakeVerifier = case StakeVerifier
stakeVerifier of
StakeVerifierKey VerificationKeyOrFile StakeKey
stkVkeyOrFile -> do
VerificationKey StakeKey
stakeVKey <- (FileError InputDecodeError -> ShelleyAddressCmdError)
-> ExceptT
(FileError InputDecodeError) IO (VerificationKey StakeKey)
-> ExceptT ShelleyAddressCmdError IO (VerificationKey StakeKey)
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError InputDecodeError -> ShelleyAddressCmdError
ShelleyAddressCmdReadKeyFileError (ExceptT (FileError InputDecodeError) IO (VerificationKey StakeKey)
-> ExceptT ShelleyAddressCmdError IO (VerificationKey StakeKey))
-> ExceptT
(FileError InputDecodeError) IO (VerificationKey StakeKey)
-> ExceptT ShelleyAddressCmdError IO (VerificationKey StakeKey)
forall a b. (a -> b) -> a -> b
$
IO (Either (FileError InputDecodeError) (VerificationKey StakeKey))
-> ExceptT
(FileError InputDecodeError) IO (VerificationKey StakeKey)
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO
(Either (FileError InputDecodeError) (VerificationKey StakeKey))
-> ExceptT
(FileError InputDecodeError) IO (VerificationKey StakeKey))
-> IO
(Either (FileError InputDecodeError) (VerificationKey StakeKey))
-> ExceptT
(FileError InputDecodeError) IO (VerificationKey StakeKey)
forall a b. (a -> b) -> a -> b
$ AsType StakeKey
-> VerificationKeyOrFile StakeKey
-> IO
(Either (FileError InputDecodeError) (VerificationKey StakeKey))
forall keyrole.
(HasTextEnvelope (VerificationKey keyrole),
SerialiseAsBech32 (VerificationKey keyrole)) =>
AsType keyrole
-> VerificationKeyOrFile keyrole
-> IO
(Either (FileError InputDecodeError) (VerificationKey keyrole))
readVerificationKeyOrFile AsType StakeKey
AsStakeKey VerificationKeyOrFile StakeKey
stkVkeyOrFile
StakeAddressReference
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall (m :: * -> *) a. Monad m => a -> m a
return (StakeAddressReference
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference)
-> (VerificationKey StakeKey -> StakeAddressReference)
-> VerificationKey StakeKey
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. StakeCredential -> StakeAddressReference
StakeAddressByValue (StakeCredential -> StakeAddressReference)
-> (VerificationKey StakeKey -> StakeCredential)
-> VerificationKey StakeKey
-> StakeAddressReference
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Hash StakeKey -> StakeCredential
StakeCredentialByKey (Hash StakeKey -> StakeCredential)
-> (VerificationKey StakeKey -> Hash StakeKey)
-> VerificationKey StakeKey
-> StakeCredential
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. VerificationKey StakeKey -> Hash StakeKey
forall keyrole.
Key keyrole =>
VerificationKey keyrole -> Hash keyrole
verificationKeyHash (VerificationKey StakeKey
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference)
-> VerificationKey StakeKey
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall a b. (a -> b) -> a -> b
$ VerificationKey StakeKey
stakeVKey
StakeVerifierScriptFile (ScriptFile String
fp) -> do
ScriptInAnyLang ScriptLanguage lang
_lang Script lang
script <-
(FileError ScriptDecodeError -> ShelleyAddressCmdError)
-> ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
-> ExceptT ShelleyAddressCmdError IO ScriptInAnyLang
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError ScriptDecodeError -> ShelleyAddressCmdError
ShelleyAddressCmdReadScriptFileError (ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
-> ExceptT ShelleyAddressCmdError IO ScriptInAnyLang)
-> ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
-> ExceptT ShelleyAddressCmdError IO ScriptInAnyLang
forall a b. (a -> b) -> a -> b
$
String -> ExceptT (FileError ScriptDecodeError) IO ScriptInAnyLang
readFileScriptInAnyLang String
fp
let stakeCred :: StakeCredential
stakeCred = ScriptHash -> StakeCredential
StakeCredentialByScript (Script lang -> ScriptHash
forall lang. Script lang -> ScriptHash
hashScript Script lang
script)
StakeAddressReference
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall (m :: * -> *) a. Monad m => a -> m a
return (StakeCredential -> StakeAddressReference
StakeAddressByValue StakeCredential
stakeCred)
buildShelleyAddress
:: VerificationKey PaymentKey
-> Maybe StakeVerifier
-> NetworkId
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
buildShelleyAddress :: VerificationKey PaymentKey
-> Maybe StakeVerifier
-> NetworkId
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
buildShelleyAddress VerificationKey PaymentKey
vkey Maybe StakeVerifier
mbStakeVerifier NetworkId
nw =
NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
makeShelleyAddress NetworkId
nw (Hash PaymentKey -> PaymentCredential
PaymentCredentialByKey (VerificationKey PaymentKey -> Hash PaymentKey
forall keyrole.
Key keyrole =>
VerificationKey keyrole -> Hash keyrole
verificationKeyHash VerificationKey PaymentKey
vkey)) (StakeAddressReference -> Address ShelleyAddr)
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
-> ExceptT ShelleyAddressCmdError IO (Address ShelleyAddr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ExceptT ShelleyAddressCmdError IO StakeAddressReference
-> (StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference)
-> Maybe StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (StakeAddressReference
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
forall (m :: * -> *) a. Monad m => a -> m a
return StakeAddressReference
NoStakeAddress) StakeVerifier
-> ExceptT ShelleyAddressCmdError IO StakeAddressReference
makeStakeAddressRef Maybe StakeVerifier
mbStakeVerifier
foldSomeAddressVerificationKey :: (forall keyrole. Key keyrole =>
VerificationKey keyrole -> a)
-> SomeAddressVerificationKey -> a
foldSomeAddressVerificationKey :: (forall keyrole. Key keyrole => VerificationKey keyrole -> a)
-> SomeAddressVerificationKey -> a
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AByronVerificationKey VerificationKey ByronKey
vk) = VerificationKey ByronKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey ByronKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (APaymentVerificationKey VerificationKey PaymentKey
vk) = VerificationKey PaymentKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey PaymentKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (APaymentExtendedVerificationKey VerificationKey PaymentExtendedKey
vk) = VerificationKey PaymentExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey PaymentExtendedKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AGenesisUTxOVerificationKey VerificationKey GenesisUTxOKey
vk) = VerificationKey GenesisUTxOKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey GenesisUTxOKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AKesVerificationKey VerificationKey KesKey
vk) = VerificationKey KesKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey KesKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AGenesisDelegateExtendedVerificationKey VerificationKey GenesisDelegateExtendedKey
vk) = VerificationKey GenesisDelegateExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey GenesisDelegateExtendedKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AGenesisExtendedVerificationKey VerificationKey GenesisExtendedKey
vk) = VerificationKey GenesisExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey GenesisExtendedKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AVrfVerificationKey VerificationKey VrfKey
vk) = VerificationKey VrfKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey VrfKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AStakeVerificationKey VerificationKey StakeKey
vk) = VerificationKey StakeKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey StakeKey
vk
foldSomeAddressVerificationKey forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (AStakeExtendedVerificationKey VerificationKey StakeExtendedKey
vk) = VerificationKey StakeExtendedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f VerificationKey StakeExtendedKey
vk