{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Cardano.CLI.Run.Key
( runKeyCmds
, runConvertByronGenesisVKeyCmd
, runConvertByronKeyCmd
, runConvertCardanoAddressKeyCmd
, runConvertITNBip32KeyCmd
, runConvertITNExtendedKeyCmd
, runConvertITNKeyCmd
, runNonExtendedKeyCmd
, runVerificationKeyCmd
, ccColdSkeyDesc
, ccColdVkeyDesc
, ccHotSkeyDesc
, ccHotVkeyDesc
, drepSkeyDesc
, drepVkeyDesc
, genesisVkeyDesc
, genesisVkeyDelegateDesc
, stakeVkeyDesc
, paymentVkeyDesc
, decodeBech32
)
where
import Cardano.Api
import qualified Cardano.Api.Byron as ByronApi
import Cardano.Api.Crypto.Ed25519Bip32 (xPrvFromBytes)
import qualified Cardano.Api.Ledger as L
import qualified Cardano.CLI.Byron.Key as Byron
import qualified Cardano.CLI.Commands.Key as Cmd
import Cardano.CLI.Types.Common
import Cardano.CLI.Types.Errors.CardanoAddressSigningKeyConversionError
import Cardano.CLI.Types.Errors.ItnKeyConversionError
import Cardano.CLI.Types.Errors.KeyCmdError
import Cardano.CLI.Types.Key
import qualified Cardano.Crypto.DSIGN as DSIGN
import qualified Cardano.Crypto.Signing as Byron
import qualified Cardano.Crypto.Signing as Byron.Crypto
import qualified Cardano.Crypto.Signing as Crypto
import qualified Cardano.Crypto.Wallet as Crypto
import qualified Codec.Binary.Bech32 as Bech32
import qualified Control.Exception as Exception
import Data.Bifunctor (Bifunctor (..))
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Function
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import System.Exit (exitFailure)
ccColdSkeyDesc :: TextEnvelopeDescr
ccColdSkeyDesc :: TextEnvelopeDescr
ccColdSkeyDesc = TextEnvelopeDescr
"Constitutional Committee Cold Signing Key"
ccColdExtendedSkeyDesc :: TextEnvelopeDescr
ccColdExtendedSkeyDesc :: TextEnvelopeDescr
ccColdExtendedSkeyDesc = TextEnvelopeDescr
"Constitutional Committee Cold Extended Signing Key"
ccColdVkeyDesc :: TextEnvelopeDescr
ccColdVkeyDesc :: TextEnvelopeDescr
ccColdVkeyDesc = TextEnvelopeDescr
"Constitutional Committee Cold Verification Key"
ccHotExtendedSkeyDesc :: TextEnvelopeDescr
ccHotExtendedSkeyDesc :: TextEnvelopeDescr
ccHotExtendedSkeyDesc = TextEnvelopeDescr
"Constitutional Committee Hot Extended Signing Key"
ccHotSkeyDesc :: TextEnvelopeDescr
ccHotSkeyDesc :: TextEnvelopeDescr
ccHotSkeyDesc = TextEnvelopeDescr
"Constitutional Committee Hot Signing Key"
ccHotVkeyDesc :: TextEnvelopeDescr
ccHotVkeyDesc :: TextEnvelopeDescr
ccHotVkeyDesc = TextEnvelopeDescr
"Constitutional Committee Hot Verification Key"
drepSkeyDesc :: TextEnvelopeDescr
drepSkeyDesc :: TextEnvelopeDescr
drepSkeyDesc = TextEnvelopeDescr
"Delegated Representative Signing Key"
drepExtendedSkeyDesc :: TextEnvelopeDescr
drepExtendedSkeyDesc :: TextEnvelopeDescr
drepExtendedSkeyDesc = TextEnvelopeDescr
"Delegated Representative Extended Signing Key"
drepVkeyDesc :: TextEnvelopeDescr
drepVkeyDesc :: TextEnvelopeDescr
drepVkeyDesc = TextEnvelopeDescr
"Delegated Representative Verification Key"
genesisVkeyDesc :: TextEnvelopeDescr
genesisVkeyDesc :: TextEnvelopeDescr
genesisVkeyDesc = TextEnvelopeDescr
"Genesis Verification Key"
genesisVkeyDelegateDesc :: TextEnvelopeDescr
genesisVkeyDelegateDesc :: TextEnvelopeDescr
genesisVkeyDelegateDesc = TextEnvelopeDescr
"Genesis delegate operator key"
paymentVkeyDesc :: TextEnvelopeDescr
paymentVkeyDesc :: TextEnvelopeDescr
paymentVkeyDesc = TextEnvelopeDescr
"Payment Verification Key"
stakeVkeyDesc :: TextEnvelopeDescr
stakeVkeyDesc :: TextEnvelopeDescr
stakeVkeyDesc = TextEnvelopeDescr
"Stake Verification Key"
runKeyCmds
:: ()
=> Cmd.KeyCmds
-> ExceptT KeyCmdError IO ()
runKeyCmds :: KeyCmds -> ExceptT KeyCmdError IO ()
runKeyCmds = \case
Cmd.KeyVerificationKeyCmd KeyVerificationKeyCmdArgs
cmd ->
KeyVerificationKeyCmdArgs -> ExceptT KeyCmdError IO ()
runVerificationKeyCmd KeyVerificationKeyCmdArgs
cmd
Cmd.KeyNonExtendedKeyCmd KeyNonExtendedKeyCmdArgs
cmd ->
KeyNonExtendedKeyCmdArgs -> ExceptT KeyCmdError IO ()
runNonExtendedKeyCmd KeyNonExtendedKeyCmdArgs
cmd
Cmd.KeyConvertByronKeyCmd KeyConvertByronKeyCmdArgs
cmd ->
KeyConvertByronKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertByronKeyCmd KeyConvertByronKeyCmdArgs
cmd
Cmd.KeyConvertByronGenesisVKeyCmd KeyConvertByronGenesisVKeyCmdArgs
cmd ->
KeyConvertByronGenesisVKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertByronGenesisVKeyCmd KeyConvertByronGenesisVKeyCmdArgs
cmd
Cmd.KeyConvertITNKeyCmd KeyConvertITNKeyCmdArgs
cmd ->
KeyConvertITNKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertITNKeyCmd KeyConvertITNKeyCmdArgs
cmd
Cmd.KeyConvertITNExtendedKeyCmd KeyConvertITNExtendedKeyCmdArgs
cmd ->
KeyConvertITNExtendedKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertITNExtendedKeyCmd KeyConvertITNExtendedKeyCmdArgs
cmd
Cmd.KeyConvertITNBip32KeyCmd KeyConvertITNBip32KeyCmdArgs
cmd ->
KeyConvertITNBip32KeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertITNBip32KeyCmd KeyConvertITNBip32KeyCmdArgs
cmd
Cmd.KeyConvertCardanoAddressKeyCmd KeyConvertCardanoAddressKeyCmdArgs
cmd ->
KeyConvertCardanoAddressKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertCardanoAddressKeyCmd KeyConvertCardanoAddressKeyCmdArgs
cmd
runVerificationKeyCmd
:: ()
=> Cmd.KeyVerificationKeyCmdArgs
-> ExceptT KeyCmdError IO ()
runVerificationKeyCmd :: KeyVerificationKeyCmdArgs -> ExceptT KeyCmdError IO ()
runVerificationKeyCmd
Cmd.KeyVerificationKeyCmdArgs
{ skeyFile :: KeyVerificationKeyCmdArgs -> SigningKeyFile 'In
Cmd.skeyFile = SigningKeyFile 'In
skf
, vkeyFile :: KeyVerificationKeyCmdArgs -> VerificationKeyFile 'Out
Cmd.vkeyFile = VerificationKeyFile 'Out
vkf
} = do
SomeSigningKey
ssk <- (FileError InputDecodeError -> KeyCmdError)
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
-> ExceptT KeyCmdError IO SomeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError InputDecodeError -> KeyCmdError
KeyCmdReadKeyFileError (ExceptT (FileError InputDecodeError) IO SomeSigningKey
-> ExceptT KeyCmdError IO SomeSigningKey)
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
-> ExceptT KeyCmdError IO SomeSigningKey
forall a b. (a -> b) -> a -> b
$ SigningKeyFile 'In
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
readSigningKeyFile SigningKeyFile 'In
skf
SomeSigningKey
-> (forall {keyrole}.
(Key keyrole, HasTypeProxy keyrole) =>
SigningKey keyrole -> ExceptT KeyCmdError IO ())
-> ExceptT KeyCmdError IO ()
forall a.
SomeSigningKey
-> (forall keyrole.
(Key keyrole, HasTypeProxy keyrole) =>
SigningKey keyrole -> a)
-> a
withSomeSigningKey SomeSigningKey
ssk ((forall {keyrole}.
(Key keyrole, HasTypeProxy keyrole) =>
SigningKey keyrole -> ExceptT KeyCmdError IO ())
-> ExceptT KeyCmdError IO ())
-> (forall {keyrole}.
(Key keyrole, HasTypeProxy keyrole) =>
SigningKey keyrole -> ExceptT KeyCmdError IO ())
-> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$ \SigningKey keyrole
sk ->
let vk :: VerificationKey keyrole
vk = SigningKey keyrole -> VerificationKey keyrole
forall keyrole.
(Key keyrole, HasTypeProxy keyrole) =>
SigningKey keyrole -> VerificationKey keyrole
getVerificationKey SigningKey keyrole
sk
in (FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
VerificationKeyFile 'Out
-> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile VerificationKeyFile 'Out
vkf (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr -> VerificationKey keyrole -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey keyrole
vk
runNonExtendedKeyCmd
:: Cmd.KeyNonExtendedKeyCmdArgs
-> ExceptT KeyCmdError IO ()
runNonExtendedKeyCmd :: KeyNonExtendedKeyCmdArgs -> ExceptT KeyCmdError IO ()
runNonExtendedKeyCmd
Cmd.KeyNonExtendedKeyCmdArgs
{ extendedVkeyFileIn :: KeyNonExtendedKeyCmdArgs -> VerificationKeyFile 'In
Cmd.extendedVkeyFileIn = VerificationKeyFile 'In
evkf
, nonExtendedVkeyFileOut :: KeyNonExtendedKeyCmdArgs -> VerificationKeyFile 'Out
Cmd.nonExtendedVkeyFileOut = VerificationKeyFile 'Out
vkf
} =
SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
writeExtendedVerificationKey (SomeAddressVerificationKey -> ExceptT KeyCmdError IO ())
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
-> ExceptT KeyCmdError IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< VerificationKeyFile 'In
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
readExtendedVerificationKeyFile VerificationKeyFile 'In
evkf
where
writeExtendedVerificationKey
:: SomeAddressVerificationKey
-> ExceptT KeyCmdError IO ()
writeExtendedVerificationKey :: SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
writeExtendedVerificationKey SomeAddressVerificationKey
ssk =
case SomeAddressVerificationKey
ssk of
APaymentExtendedVerificationKey VerificationKey PaymentExtendedKey
vk ->
VerificationKeyFile 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey PaymentKey
-> ExceptT KeyCmdError IO ()
forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk VerificationKeyFile 'Out
vkf (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
paymentVkeyDesc) (VerificationKey PaymentExtendedKey -> VerificationKey PaymentKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey PaymentExtendedKey
vk :: VerificationKey PaymentKey)
ADRepExtendedVerificationKey VerificationKey DRepExtendedKey
vk ->
VerificationKeyFile 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey DRepKey
-> ExceptT KeyCmdError IO ()
forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk VerificationKeyFile 'Out
vkf (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
drepVkeyDesc) (VerificationKey DRepExtendedKey -> VerificationKey DRepKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey DRepExtendedKey
vk :: VerificationKey DRepKey)
ACommitteeColdExtendedVerificationKey VerificationKey CommitteeColdExtendedKey
vk ->
VerificationKeyFile 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey CommitteeColdKey
-> ExceptT KeyCmdError IO ()
forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk VerificationKeyFile 'Out
vkf (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
ccColdVkeyDesc) (VerificationKey CommitteeColdExtendedKey
-> VerificationKey CommitteeColdKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey CommitteeColdExtendedKey
vk :: VerificationKey CommitteeColdKey)
ACommitteeHotExtendedVerificationKey VerificationKey CommitteeHotExtendedKey
vk ->
VerificationKeyFile 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey CommitteeHotKey
-> ExceptT KeyCmdError IO ()
forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk VerificationKeyFile 'Out
vkf (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
ccHotVkeyDesc) (VerificationKey CommitteeHotExtendedKey
-> VerificationKey CommitteeHotKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey CommitteeHotExtendedKey
vk :: VerificationKey CommitteeHotKey)
AStakeExtendedVerificationKey VerificationKey StakeExtendedKey
vk ->
VerificationKeyFile 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey StakeKey
-> ExceptT KeyCmdError IO ()
forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk VerificationKeyFile 'Out
vkf (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
stakeVkeyDesc) (VerificationKey StakeExtendedKey -> VerificationKey StakeKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey StakeExtendedKey
vk :: VerificationKey StakeKey)
AGenesisExtendedVerificationKey VerificationKey GenesisExtendedKey
vk ->
VerificationKeyFile 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey GenesisKey
-> ExceptT KeyCmdError IO ()
forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk VerificationKeyFile 'Out
vkf (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
genesisVkeyDesc) (VerificationKey GenesisExtendedKey -> VerificationKey GenesisKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisExtendedKey
vk :: VerificationKey GenesisKey)
AGenesisDelegateExtendedVerificationKey VerificationKey GenesisDelegateExtendedKey
vk ->
VerificationKeyFile 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey GenesisDelegateKey
-> ExceptT KeyCmdError IO ()
forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk
VerificationKeyFile 'Out
vkf
(TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
genesisVkeyDelegateDesc)
(VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisDelegateExtendedKey
vk :: VerificationKey GenesisDelegateKey)
vk :: SomeAddressVerificationKey
vk@AByronVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@APaymentVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@AGenesisUTxOVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@AKesVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@AVrfVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@AStakeVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@ADRepVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@ACommitteeColdVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
vk :: SomeAddressVerificationKey
vk@ACommitteeHotVerificationKey{} -> SomeAddressVerificationKey -> ExceptT KeyCmdError IO ()
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
vk
where
goFail :: SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
nonExtendedKey = KeyCmdError -> ExceptT KeyCmdError m a
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left (KeyCmdError -> ExceptT KeyCmdError m a)
-> KeyCmdError -> ExceptT KeyCmdError m a
forall a b. (a -> b) -> a -> b
$ SomeAddressVerificationKey -> KeyCmdError
KeyCmdExpectedExtendedVerificationKey SomeAddressVerificationKey
nonExtendedKey
writeToDisk
:: Key keyrole
=> File content Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk :: forall keyrole content.
Key keyrole =>
File content 'Out
-> Maybe TextEnvelopeDescr
-> VerificationKey keyrole
-> ExceptT KeyCmdError IO ()
writeToDisk File content 'Out
vkf' Maybe TextEnvelopeDescr
descr VerificationKey keyrole
vk =
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File content 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File content 'Out
vkf' (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr -> VerificationKey keyrole -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
descr VerificationKey keyrole
vk
readExtendedVerificationKeyFile
:: VerificationKeyFile In
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
readExtendedVerificationKeyFile :: VerificationKeyFile 'In
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
readExtendedVerificationKeyFile VerificationKeyFile 'In
evkfile = do
SomeAddressVerificationKey
vKey <-
(VerificationKeyTextOrFileError -> KeyCmdError)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT VerificationKeyTextOrFileError -> KeyCmdError
KeyCmdVerificationKeyReadError
(ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey)
-> (IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT
VerificationKeyTextOrFileError IO SomeAddressVerificationKey)
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 KeyCmdError IO SomeAddressVerificationKey)
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a b. (a -> b) -> a -> b
$ VerificationKeyTextOrFile
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
readVerificationKeyTextOrFileAnyOf
(VerificationKeyTextOrFile
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey))
-> VerificationKeyTextOrFile
-> IO
(Either VerificationKeyTextOrFileError SomeAddressVerificationKey)
forall a b. (a -> b) -> a -> b
$ VerificationKeyFile 'In -> VerificationKeyTextOrFile
VktofVerificationKeyFile VerificationKeyFile 'In
evkfile
case SomeAddressVerificationKey
vKey of
k :: SomeAddressVerificationKey
k@APaymentExtendedVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@ADRepExtendedVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@ACommitteeColdExtendedVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@ACommitteeHotExtendedVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AStakeExtendedVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AGenesisExtendedVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AGenesisDelegateExtendedVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AByronVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@APaymentVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AGenesisUTxOVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AKesVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AVrfVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@AStakeVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@ADRepVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@ACommitteeColdVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
k :: SomeAddressVerificationKey
k@ACommitteeHotVerificationKey{} -> SomeAddressVerificationKey
-> ExceptT KeyCmdError IO SomeAddressVerificationKey
forall {m :: * -> *} {a}.
Monad m =>
SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k
where
goFail :: SomeAddressVerificationKey -> ExceptT KeyCmdError m a
goFail SomeAddressVerificationKey
k = KeyCmdError -> ExceptT KeyCmdError m a
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left (KeyCmdError -> ExceptT KeyCmdError m a)
-> KeyCmdError -> ExceptT KeyCmdError m a
forall a b. (a -> b) -> a -> b
$ SomeAddressVerificationKey -> KeyCmdError
KeyCmdExpectedExtendedVerificationKey SomeAddressVerificationKey
k
runConvertByronKeyCmd
:: Cmd.KeyConvertByronKeyCmdArgs
-> ExceptT KeyCmdError IO ()
runConvertByronKeyCmd :: KeyConvertByronKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertByronKeyCmd
Cmd.KeyConvertByronKeyCmdArgs
{ mPassword :: KeyConvertByronKeyCmdArgs -> Maybe Text
Cmd.mPassword = Maybe Text
mPwd
, ByronKeyType
byronKeyType :: ByronKeyType
byronKeyType :: KeyConvertByronKeyCmdArgs -> ByronKeyType
Cmd.byronKeyType
, someKeyFileIn :: KeyConvertByronKeyCmdArgs -> SomeKeyFile 'In
Cmd.someKeyFileIn = SomeKeyFile 'In
inFile
, someKeyFileOut :: KeyConvertByronKeyCmdArgs -> File () 'Out
Cmd.someKeyFileOut = File () 'Out
outFile
} =
case (ByronKeyType
byronKeyType, SomeKeyFile 'In
inFile) of
(ByronPaymentKey ByronKeyFormat
format, ASigningKeyFile SigningKeyFile 'In
skeyPathOld) ->
Maybe Text
-> ByronKeyFormat
-> (SigningKey -> SigningKey ByronKey)
-> SigningKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ByronKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronSigningKey Maybe Text
mPwd ByronKeyFormat
format SigningKey -> SigningKey ByronKey
convert SigningKeyFile 'In
skeyPathOld File () 'Out
outFile
where
convert :: Byron.SigningKey -> SigningKey ByronKey
convert :: SigningKey -> SigningKey ByronKey
convert = SigningKey -> SigningKey ByronKey
ByronSigningKey
(ByronGenesisKey ByronKeyFormat
format, ASigningKeyFile SigningKeyFile 'In
skeyPathOld) ->
Maybe Text
-> ByronKeyFormat
-> (SigningKey -> SigningKey GenesisExtendedKey)
-> SigningKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ByronKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronSigningKey Maybe Text
mPwd ByronKeyFormat
format SigningKey -> SigningKey GenesisExtendedKey
convert SigningKeyFile 'In
skeyPathOld File () 'Out
outFile
where
convert :: Byron.SigningKey -> SigningKey GenesisExtendedKey
convert :: SigningKey -> SigningKey GenesisExtendedKey
convert (Byron.SigningKey XPrv
xsk) = XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey XPrv
xsk
(ByronDelegateKey ByronKeyFormat
format, ASigningKeyFile SigningKeyFile 'In
skeyPathOld) ->
Maybe Text
-> ByronKeyFormat
-> (SigningKey -> SigningKey GenesisDelegateExtendedKey)
-> SigningKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ByronKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronSigningKey Maybe Text
mPwd ByronKeyFormat
format SigningKey -> SigningKey GenesisDelegateExtendedKey
convert SigningKeyFile 'In
skeyPathOld File () 'Out
outFile
where
convert :: Byron.SigningKey -> SigningKey GenesisDelegateExtendedKey
convert :: SigningKey -> SigningKey GenesisDelegateExtendedKey
convert (Byron.SigningKey XPrv
xsk) = XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey XPrv
xsk
(ByronPaymentKey ByronKeyFormat
NonLegacyByronKeyFormat, AVerificationKeyFile VerificationKeyFile 'In
vkeyPathOld) ->
(VerificationKey -> VerificationKey ByronKey)
-> VerificationKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronVerificationKey VerificationKey -> VerificationKey ByronKey
convert VerificationKeyFile 'In
vkeyPathOld File () 'Out
outFile
where
convert :: Byron.VerificationKey -> VerificationKey ByronKey
convert :: VerificationKey -> VerificationKey ByronKey
convert = VerificationKey -> VerificationKey ByronKey
ByronVerificationKey
(ByronGenesisKey ByronKeyFormat
NonLegacyByronKeyFormat, AVerificationKeyFile VerificationKeyFile 'In
vkeyPathOld) ->
(VerificationKey -> VerificationKey GenesisExtendedKey)
-> VerificationKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronVerificationKey VerificationKey -> VerificationKey GenesisExtendedKey
convert VerificationKeyFile 'In
vkeyPathOld File () 'Out
outFile
where
convert :: Byron.VerificationKey -> VerificationKey GenesisExtendedKey
convert :: VerificationKey -> VerificationKey GenesisExtendedKey
convert (Byron.VerificationKey XPub
xvk) = XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey XPub
xvk
(ByronDelegateKey ByronKeyFormat
NonLegacyByronKeyFormat, AVerificationKeyFile VerificationKeyFile 'In
vkeyPathOld) ->
(VerificationKey -> VerificationKey GenesisDelegateExtendedKey)
-> VerificationKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronVerificationKey VerificationKey -> VerificationKey GenesisDelegateExtendedKey
convert VerificationKeyFile 'In
vkeyPathOld File () 'Out
outFile
where
convert :: Byron.VerificationKey -> VerificationKey GenesisDelegateExtendedKey
convert :: VerificationKey -> VerificationKey GenesisDelegateExtendedKey
convert (Byron.VerificationKey XPub
xvk) =
XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey XPub
xvk
(ByronPaymentKey ByronKeyFormat
LegacyByronKeyFormat, AVerificationKeyFile{}) ->
ExceptT KeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
(ByronGenesisKey ByronKeyFormat
LegacyByronKeyFormat, AVerificationKeyFile{}) ->
ExceptT KeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
(ByronDelegateKey ByronKeyFormat
LegacyByronKeyFormat, AVerificationKeyFile{}) ->
ExceptT KeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
legacyVerificationKeysNotSupported :: ExceptT e IO a
legacyVerificationKeysNotSupported :: forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported =
IO a -> ExceptT e IO a
forall a. IO a -> ExceptT e IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> ExceptT e IO a) -> IO a -> ExceptT e IO a
forall a b. (a -> b) -> a -> b
$ do
[Char] -> IO ()
putStrLn ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$
[Char]
"convert keys: byron legacy format not supported for "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"verification keys. Convert the signing key and then get the "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"verification key."
IO a
forall a. IO a
exitFailure
convertByronSigningKey
:: forall keyrole
. Key keyrole
=> Maybe Text
-> ByronKeyFormat
-> (Byron.SigningKey -> SigningKey keyrole)
-> SigningKeyFile In
-> File () Out
-> ExceptT KeyCmdError IO ()
convertByronSigningKey :: forall keyrole.
Key keyrole =>
Maybe Text
-> ByronKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronSigningKey Maybe Text
mPwd ByronKeyFormat
byronFormat SigningKey -> SigningKey keyrole
convert SigningKeyFile 'In
skeyPathOld File () 'Out
skeyPathNew = do
SomeByronSigningKey
sKey <-
(ByronKeyFailure -> KeyCmdError)
-> ExceptT ByronKeyFailure IO SomeByronSigningKey
-> ExceptT KeyCmdError IO SomeByronSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> KeyCmdError
KeyCmdByronKeyFailure (ExceptT ByronKeyFailure IO SomeByronSigningKey
-> ExceptT KeyCmdError IO SomeByronSigningKey)
-> ExceptT ByronKeyFailure IO SomeByronSigningKey
-> ExceptT KeyCmdError IO SomeByronSigningKey
forall a b. (a -> b) -> a -> b
$
ByronKeyFormat
-> SigningKeyFile 'In
-> ExceptT ByronKeyFailure IO SomeByronSigningKey
Byron.readByronSigningKey ByronKeyFormat
byronFormat SigningKeyFile 'In
skeyPathOld
SigningKey
unprotectedSk <- case SomeByronSigningKey
sKey of
ByronApi.AByronSigningKeyLegacy (ByronSigningKeyLegacy sk :: SigningKey
sk@(Crypto.SigningKey XPrv
xprv)) ->
case Maybe Text
mPwd of
Just Text
pwd ->
SigningKey -> ExceptT KeyCmdError IO SigningKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey -> ExceptT KeyCmdError IO SigningKey)
-> (XPrv -> SigningKey)
-> XPrv
-> ExceptT KeyCmdError IO SigningKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XPrv -> SigningKey
Crypto.SigningKey (XPrv -> ExceptT KeyCmdError IO SigningKey)
-> XPrv -> ExceptT KeyCmdError IO SigningKey
forall a b. (a -> b) -> a -> b
$
ByteString -> ByteString -> XPrv -> XPrv
forall oldPassPhrase newPassPhrase.
(ByteArrayAccess oldPassPhrase, ByteArrayAccess newPassPhrase) =>
oldPassPhrase -> newPassPhrase -> XPrv -> XPrv
Crypto.xPrvChangePass (Text -> ByteString
Text.encodeUtf8 Text
pwd) (Text -> ByteString
Text.encodeUtf8 Text
"") XPrv
xprv
Maybe Text
Nothing -> SigningKey -> ExceptT KeyCmdError IO SigningKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SigningKey
sk
ByronApi.AByronSigningKey (ByronSigningKey SigningKey
sk) -> SigningKey -> ExceptT KeyCmdError IO SigningKey
forall a. a -> ExceptT KeyCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SigningKey
sk
let sk' :: SigningKey keyrole
sk' :: SigningKey keyrole
sk' = SigningKey -> SigningKey keyrole
convert SigningKey
unprotectedSk
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File () 'Out
skeyPathNew (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr -> SigningKey keyrole -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey keyrole
sk'
convertByronVerificationKey
:: forall keyrole
. Key keyrole
=> (Byron.VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile In
-> File () Out
-> ExceptT KeyCmdError IO ()
convertByronVerificationKey :: forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile 'In
-> File () 'Out
-> ExceptT KeyCmdError IO ()
convertByronVerificationKey VerificationKey -> VerificationKey keyrole
convert VerificationKeyFile 'In
vkeyPathOld File () 'Out
vkeyPathNew = do
VerificationKey
vk <-
(ByronKeyFailure -> KeyCmdError)
-> ExceptT ByronKeyFailure IO VerificationKey
-> ExceptT KeyCmdError IO VerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ByronKeyFailure -> KeyCmdError
KeyCmdByronKeyFailure (ExceptT ByronKeyFailure IO VerificationKey
-> ExceptT KeyCmdError IO VerificationKey)
-> ExceptT ByronKeyFailure IO VerificationKey
-> ExceptT KeyCmdError IO VerificationKey
forall a b. (a -> b) -> a -> b
$
VerificationKeyFile 'In
-> ExceptT ByronKeyFailure IO VerificationKey
Byron.readPaymentVerificationKey VerificationKeyFile 'In
vkeyPathOld
let vk' :: VerificationKey keyrole
vk' :: VerificationKey keyrole
vk' = VerificationKey -> VerificationKey keyrole
convert VerificationKey
vk
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File () 'Out
vkeyPathNew (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr -> VerificationKey keyrole -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey keyrole
vk'
runConvertByronGenesisVKeyCmd
:: Cmd.KeyConvertByronGenesisVKeyCmdArgs
-> ExceptT KeyCmdError IO ()
runConvertByronGenesisVKeyCmd :: KeyConvertByronGenesisVKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertByronGenesisVKeyCmd
Cmd.KeyConvertByronGenesisVKeyCmdArgs
{ vkey :: KeyConvertByronGenesisVKeyCmdArgs -> VerificationKeyBase64
Cmd.vkey = VerificationKeyBase64 [Char]
b64ByronVKey
, vkeyFileOut :: KeyConvertByronGenesisVKeyCmdArgs -> File () 'Out
Cmd.vkeyFileOut = File () 'Out
vkeyPathNew
} = do
VerificationKey
vk <-
(VerificationKeyParseError -> KeyCmdError)
-> ExceptT VerificationKeyParseError IO VerificationKey
-> ExceptT KeyCmdError IO VerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (Text -> KeyCmdError
KeyCmdByronKeyParseError (Text -> KeyCmdError)
-> (VerificationKeyParseError -> Text)
-> VerificationKeyParseError
-> KeyCmdError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VerificationKeyParseError -> Text
forall a. Show a => a -> Text
textShow)
(ExceptT VerificationKeyParseError IO VerificationKey
-> ExceptT KeyCmdError IO VerificationKey)
-> ([Char] -> ExceptT VerificationKeyParseError IO VerificationKey)
-> [Char]
-> ExceptT KeyCmdError IO VerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either VerificationKeyParseError VerificationKey
-> ExceptT VerificationKeyParseError IO VerificationKey
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither
(Either VerificationKeyParseError VerificationKey
-> ExceptT VerificationKeyParseError IO VerificationKey)
-> ([Char] -> Either VerificationKeyParseError VerificationKey)
-> [Char]
-> ExceptT VerificationKeyParseError IO VerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either VerificationKeyParseError VerificationKey
Byron.Crypto.parseFullVerificationKey
(Text -> Either VerificationKeyParseError VerificationKey)
-> ([Char] -> Text)
-> [Char]
-> Either VerificationKeyParseError VerificationKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
Text.pack
([Char] -> ExceptT KeyCmdError IO VerificationKey)
-> [Char] -> ExceptT KeyCmdError IO VerificationKey
forall a b. (a -> b) -> a -> b
$ [Char]
b64ByronVKey
let vk' :: VerificationKey GenesisKey
vk' :: VerificationKey GenesisKey
vk' = VerificationKey -> VerificationKey GenesisKey
convert VerificationKey
vk
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File () 'Out
vkeyPathNew (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr -> VerificationKey GenesisKey -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey GenesisKey
vk'
where
convert :: Byron.VerificationKey -> VerificationKey GenesisKey
convert :: VerificationKey -> VerificationKey GenesisKey
convert (Byron.VerificationKey XPub
xvk) =
VerificationKey GenesisExtendedKey -> VerificationKey GenesisKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey (XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey XPub
xvk)
runConvertITNKeyCmd
:: Cmd.KeyConvertITNKeyCmdArgs
-> ExceptT KeyCmdError IO ()
runConvertITNKeyCmd :: KeyConvertITNKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertITNKeyCmd
Cmd.KeyConvertITNKeyCmdArgs
{ SomeKeyFile 'In
itnKeyFile :: SomeKeyFile 'In
itnKeyFile :: KeyConvertITNKeyCmdArgs -> SomeKeyFile 'In
Cmd.itnKeyFile
, File () 'Out
outFile :: File () 'Out
outFile :: KeyConvertITNKeyCmdArgs -> File () 'Out
Cmd.outFile
} =
case SomeKeyFile 'In
itnKeyFile of
AVerificationKeyFile (File [Char]
vk) -> do
Text
bech32publicKey <-
(ItnKeyConversionError -> KeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$
[Char] -> IO (Either ItnKeyConversionError Text)
readFileITNKey [Char]
vk
VerificationKey StakeKey
vkey <-
Either KeyCmdError (VerificationKey StakeKey)
-> ExceptT KeyCmdError IO (VerificationKey StakeKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither
(Either KeyCmdError (VerificationKey StakeKey)
-> ExceptT KeyCmdError IO (VerificationKey StakeKey))
-> (Either ItnKeyConversionError (VerificationKey StakeKey)
-> Either KeyCmdError (VerificationKey StakeKey))
-> Either ItnKeyConversionError (VerificationKey StakeKey)
-> ExceptT KeyCmdError IO (VerificationKey StakeKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ItnKeyConversionError -> KeyCmdError)
-> Either ItnKeyConversionError (VerificationKey StakeKey)
-> Either KeyCmdError (VerificationKey StakeKey)
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 ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError
(Either ItnKeyConversionError (VerificationKey StakeKey)
-> ExceptT KeyCmdError IO (VerificationKey StakeKey))
-> Either ItnKeyConversionError (VerificationKey StakeKey)
-> ExceptT KeyCmdError IO (VerificationKey StakeKey)
forall a b. (a -> b) -> a -> b
$ Text -> Either ItnKeyConversionError (VerificationKey StakeKey)
convertITNVerificationKey Text
bech32publicKey
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File () 'Out
outFile (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr -> VerificationKey StakeKey -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey StakeKey
vkey
ASigningKeyFile (File [Char]
sk) -> do
Text
bech32privateKey <-
(ItnKeyConversionError -> KeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$
[Char] -> IO (Either ItnKeyConversionError Text)
readFileITNKey [Char]
sk
SigningKey StakeKey
skey <-
Either KeyCmdError (SigningKey StakeKey)
-> ExceptT KeyCmdError IO (SigningKey StakeKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither
(Either KeyCmdError (SigningKey StakeKey)
-> ExceptT KeyCmdError IO (SigningKey StakeKey))
-> (Either ItnKeyConversionError (SigningKey StakeKey)
-> Either KeyCmdError (SigningKey StakeKey))
-> Either ItnKeyConversionError (SigningKey StakeKey)
-> ExceptT KeyCmdError IO (SigningKey StakeKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ItnKeyConversionError -> KeyCmdError)
-> Either ItnKeyConversionError (SigningKey StakeKey)
-> Either KeyCmdError (SigningKey StakeKey)
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 ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError
(Either ItnKeyConversionError (SigningKey StakeKey)
-> ExceptT KeyCmdError IO (SigningKey StakeKey))
-> Either ItnKeyConversionError (SigningKey StakeKey)
-> ExceptT KeyCmdError IO (SigningKey StakeKey)
forall a b. (a -> b) -> a -> b
$ Text -> Either ItnKeyConversionError (SigningKey StakeKey)
convertITNSigningKey Text
bech32privateKey
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File () 'Out
outFile (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr -> SigningKey StakeKey -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeKey
skey
runConvertITNExtendedKeyCmd
:: ()
=> Cmd.KeyConvertITNExtendedKeyCmdArgs
-> ExceptT KeyCmdError IO ()
runConvertITNExtendedKeyCmd :: KeyConvertITNExtendedKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertITNExtendedKeyCmd
Cmd.KeyConvertITNExtendedKeyCmdArgs
{ SomeKeyFile 'In
itnPrivKeyFile :: SomeKeyFile 'In
itnPrivKeyFile :: KeyConvertITNExtendedKeyCmdArgs -> SomeKeyFile 'In
Cmd.itnPrivKeyFile
, File () 'Out
outFile :: File () 'Out
outFile :: KeyConvertITNExtendedKeyCmdArgs -> File () 'Out
Cmd.outFile
} =
case SomeKeyFile 'In
itnPrivKeyFile of
AVerificationKeyFile VerificationKeyFile 'In
_ ->
KeyCmdError -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left KeyCmdError
KeyCmdWrongKeyTypeError
ASigningKeyFile (File [Char]
sk) -> do
Text
bech32privateKey <- (ItnKeyConversionError -> KeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$ [Char] -> IO (Either ItnKeyConversionError Text)
readFileITNKey [Char]
sk
SigningKey StakeExtendedKey
skey <-
Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNExtendedSigningKey Text
bech32privateKey
Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> (Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either KeyCmdError (SigningKey StakeExtendedKey))
-> Either KeyCmdError (SigningKey StakeExtendedKey)
forall a b. a -> (a -> b) -> b
& (ItnKeyConversionError -> KeyCmdError)
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either KeyCmdError (SigningKey StakeExtendedKey)
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 ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError
Either KeyCmdError (SigningKey StakeExtendedKey)
-> (Either KeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT KeyCmdError IO (SigningKey StakeExtendedKey))
-> ExceptT KeyCmdError IO (SigningKey StakeExtendedKey)
forall a b. a -> (a -> b) -> b
& Either KeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT KeyCmdError IO (SigningKey StakeExtendedKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File () 'Out
outFile (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr
-> SigningKey StakeExtendedKey -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeExtendedKey
skey
runConvertITNBip32KeyCmd
:: ()
=> Cmd.KeyConvertITNBip32KeyCmdArgs
-> ExceptT KeyCmdError IO ()
runConvertITNBip32KeyCmd :: KeyConvertITNBip32KeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertITNBip32KeyCmd
Cmd.KeyConvertITNBip32KeyCmdArgs
{ SomeKeyFile 'In
itnPrivKeyFile :: SomeKeyFile 'In
itnPrivKeyFile :: KeyConvertITNBip32KeyCmdArgs -> SomeKeyFile 'In
Cmd.itnPrivKeyFile
, File () 'Out
outFile :: File () 'Out
outFile :: KeyConvertITNBip32KeyCmdArgs -> File () 'Out
Cmd.outFile
} =
case SomeKeyFile 'In
itnPrivKeyFile of
AVerificationKeyFile VerificationKeyFile 'In
_ ->
KeyCmdError -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left KeyCmdError
KeyCmdWrongKeyTypeError
ASigningKeyFile (File [Char]
sk) -> do
Text
bech32privateKey <- (ItnKeyConversionError -> KeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT KeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT KeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$ [Char] -> IO (Either ItnKeyConversionError Text)
readFileITNKey [Char]
sk
SigningKey StakeExtendedKey
skey <-
Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNBIP32SigningKey Text
bech32privateKey
Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> (Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either KeyCmdError (SigningKey StakeExtendedKey))
-> Either KeyCmdError (SigningKey StakeExtendedKey)
forall a b. a -> (a -> b) -> b
& (ItnKeyConversionError -> KeyCmdError)
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either KeyCmdError (SigningKey StakeExtendedKey)
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 ItnKeyConversionError -> KeyCmdError
KeyCmdItnKeyConvError
Either KeyCmdError (SigningKey StakeExtendedKey)
-> (Either KeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT KeyCmdError IO (SigningKey StakeExtendedKey))
-> ExceptT KeyCmdError IO (SigningKey StakeExtendedKey)
forall a b. a -> (a -> b) -> b
& Either KeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT KeyCmdError IO (SigningKey StakeExtendedKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File () 'Out
outFile (ByteString -> IO (Either (FileError ()) ()))
-> ByteString -> IO (Either (FileError ()) ())
forall a b. (a -> b) -> a -> b
$
Maybe TextEnvelopeDescr
-> SigningKey StakeExtendedKey -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeExtendedKey
skey
convertITNVerificationKey :: Text -> Either ItnKeyConversionError (VerificationKey StakeKey)
convertITNVerificationKey :: Text -> Either ItnKeyConversionError (VerificationKey StakeKey)
convertITNVerificationKey Text
pubKey = do
(HumanReadablePart
_, DataPart
_, ByteString
keyBS) <- (Bech32DecodeError -> ItnKeyConversionError)
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
-> Either
ItnKeyConversionError (HumanReadablePart, DataPart, ByteString)
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 Bech32DecodeError -> ItnKeyConversionError
ItnKeyBech32DecodeError (Text
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
decodeBech32 Text
pubKey)
case ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
DSIGN.rawDeserialiseVerKeyDSIGN ByteString
keyBS of
Just VerKeyDSIGN Ed25519DSIGN
verKey -> VerificationKey StakeKey
-> Either ItnKeyConversionError (VerificationKey StakeKey)
forall a b. b -> Either a b
Right (VerificationKey StakeKey
-> Either ItnKeyConversionError (VerificationKey StakeKey))
-> (VKey 'Staking StandardCrypto -> VerificationKey StakeKey)
-> VKey 'Staking StandardCrypto
-> Either ItnKeyConversionError (VerificationKey StakeKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VKey 'Staking StandardCrypto -> VerificationKey StakeKey
StakeVerificationKey (VKey 'Staking StandardCrypto
-> Either ItnKeyConversionError (VerificationKey StakeKey))
-> VKey 'Staking StandardCrypto
-> Either ItnKeyConversionError (VerificationKey StakeKey)
forall a b. (a -> b) -> a -> b
$ VerKeyDSIGN (DSIGN StandardCrypto) -> VKey 'Staking StandardCrypto
forall (kd :: KeyRole) c. VerKeyDSIGN (DSIGN c) -> VKey kd c
L.VKey VerKeyDSIGN Ed25519DSIGN
VerKeyDSIGN (DSIGN StandardCrypto)
verKey
Maybe (VerKeyDSIGN Ed25519DSIGN)
Nothing -> ItnKeyConversionError
-> Either ItnKeyConversionError (VerificationKey StakeKey)
forall a b. a -> Either a b
Left (ItnKeyConversionError
-> Either ItnKeyConversionError (VerificationKey StakeKey))
-> ItnKeyConversionError
-> Either ItnKeyConversionError (VerificationKey StakeKey)
forall a b. (a -> b) -> a -> b
$ ByteString -> ItnKeyConversionError
ItnVerificationKeyDeserialisationError ByteString
keyBS
convertITNSigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeKey)
convertITNSigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeKey)
convertITNSigningKey Text
privKey = do
(HumanReadablePart
_, DataPart
_, ByteString
keyBS) <- (Bech32DecodeError -> ItnKeyConversionError)
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
-> Either
ItnKeyConversionError (HumanReadablePart, DataPart, ByteString)
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 Bech32DecodeError -> ItnKeyConversionError
ItnKeyBech32DecodeError (Text
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
decodeBech32 Text
privKey)
case ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall v. DSIGNAlgorithm v => ByteString -> Maybe (SignKeyDSIGN v)
DSIGN.rawDeserialiseSignKeyDSIGN ByteString
keyBS of
Just SignKeyDSIGN Ed25519DSIGN
signKey -> SigningKey StakeKey
-> Either ItnKeyConversionError (SigningKey StakeKey)
forall a b. b -> Either a b
Right (SigningKey StakeKey
-> Either ItnKeyConversionError (SigningKey StakeKey))
-> SigningKey StakeKey
-> Either ItnKeyConversionError (SigningKey StakeKey)
forall a b. (a -> b) -> a -> b
$ SignKeyDSIGN StandardCrypto -> SigningKey StakeKey
StakeSigningKey SignKeyDSIGN Ed25519DSIGN
SignKeyDSIGN StandardCrypto
signKey
Maybe (SignKeyDSIGN Ed25519DSIGN)
Nothing -> ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeKey)
forall a b. a -> Either a b
Left (ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeKey))
-> ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeKey)
forall a b. (a -> b) -> a -> b
$ ByteString -> ItnKeyConversionError
ItnSigningKeyDeserialisationError ByteString
keyBS
convertITNExtendedSigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNExtendedSigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNExtendedSigningKey Text
privKey = do
(HumanReadablePart
_, DataPart
_, ByteString
privkeyBS) <- (Bech32DecodeError -> ItnKeyConversionError)
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
-> Either
ItnKeyConversionError (HumanReadablePart, DataPart, ByteString)
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 Bech32DecodeError -> ItnKeyConversionError
ItnKeyBech32DecodeError (Text
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
decodeBech32 Text
privKey)
let dummyChainCode :: ByteString
dummyChainCode = Int -> Word8 -> ByteString
BS.replicate Int
32 Word8
0
case ByteString -> Maybe XPrv
xPrvFromBytes (ByteString -> Maybe XPrv) -> ByteString -> Maybe XPrv
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
BS.concat [ByteString
privkeyBS, ByteString
dummyChainCode] of
Just XPrv
xprv -> SigningKey StakeExtendedKey
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. b -> Either a b
Right (SigningKey StakeExtendedKey
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey))
-> SigningKey StakeExtendedKey
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey XPrv
xprv
Maybe XPrv
Nothing -> ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. a -> Either a b
Left (ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey))
-> ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ ByteString -> ItnKeyConversionError
ItnSigningKeyDeserialisationError ByteString
privkeyBS
convertITNBIP32SigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNBIP32SigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNBIP32SigningKey Text
privKey = do
(HumanReadablePart
_, DataPart
_, ByteString
privkeyBS) <- (Bech32DecodeError -> ItnKeyConversionError)
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
-> Either
ItnKeyConversionError (HumanReadablePart, DataPart, ByteString)
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 Bech32DecodeError -> ItnKeyConversionError
ItnKeyBech32DecodeError (Text
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
decodeBech32 Text
privKey)
case ByteString -> Maybe XPrv
xPrvFromBytes ByteString
privkeyBS of
Just XPrv
xprv -> SigningKey StakeExtendedKey
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. b -> Either a b
Right (SigningKey StakeExtendedKey
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey))
-> SigningKey StakeExtendedKey
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey XPrv
xprv
Maybe XPrv
Nothing -> ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. a -> Either a b
Left (ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey))
-> ItnKeyConversionError
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ ByteString -> ItnKeyConversionError
ItnSigningKeyDeserialisationError ByteString
privkeyBS
readFileITNKey :: FilePath -> IO (Either ItnKeyConversionError Text)
readFileITNKey :: [Char] -> IO (Either ItnKeyConversionError Text)
readFileITNKey [Char]
fp = do
Either IOException [Char]
eStr <- IO [Char] -> IO (Either IOException [Char])
forall e a. Exception e => IO a -> IO (Either e a)
Exception.try (IO [Char] -> IO (Either IOException [Char]))
-> IO [Char] -> IO (Either IOException [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> IO [Char]
readFile [Char]
fp
case Either IOException [Char]
eStr of
Left IOException
e -> Either ItnKeyConversionError Text
-> IO (Either ItnKeyConversionError Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ItnKeyConversionError Text
-> IO (Either ItnKeyConversionError Text))
-> (ItnKeyConversionError -> Either ItnKeyConversionError Text)
-> ItnKeyConversionError
-> IO (Either ItnKeyConversionError Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ItnKeyConversionError -> Either ItnKeyConversionError Text
forall a b. a -> Either a b
Left (ItnKeyConversionError -> IO (Either ItnKeyConversionError Text))
-> ItnKeyConversionError -> IO (Either ItnKeyConversionError Text)
forall a b. (a -> b) -> a -> b
$ [Char] -> IOException -> ItnKeyConversionError
ItnReadBech32FileError [Char]
fp IOException
e
Right [Char]
str -> Either ItnKeyConversionError Text
-> IO (Either ItnKeyConversionError Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ItnKeyConversionError Text
-> IO (Either ItnKeyConversionError Text))
-> ([Text] -> Either ItnKeyConversionError Text)
-> [Text]
-> IO (Either ItnKeyConversionError Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either ItnKeyConversionError Text
forall a b. b -> Either a b
Right (Text -> Either ItnKeyConversionError Text)
-> ([Text] -> Text) -> [Text] -> Either ItnKeyConversionError Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Text.concat ([Text] -> IO (Either ItnKeyConversionError Text))
-> [Text] -> IO (Either ItnKeyConversionError Text)
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
Text.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
Text.pack [Char]
str
runConvertCardanoAddressKeyCmd
:: ()
=> Cmd.KeyConvertCardanoAddressKeyCmdArgs
-> ExceptT KeyCmdError IO ()
runConvertCardanoAddressKeyCmd :: KeyConvertCardanoAddressKeyCmdArgs -> ExceptT KeyCmdError IO ()
runConvertCardanoAddressKeyCmd
Cmd.KeyConvertCardanoAddressKeyCmdArgs
{ cardanoAddressKeyType :: KeyConvertCardanoAddressKeyCmdArgs -> CardanoAddressKeyType
cardanoAddressKeyType = CardanoAddressKeyType
keyType
, skeyFileIn :: KeyConvertCardanoAddressKeyCmdArgs -> SigningKeyFile 'In
skeyFileIn = SigningKeyFile 'In
skFile
, skeyFileOut :: KeyConvertCardanoAddressKeyCmdArgs -> File () 'Out
skeyFileOut = File () 'Out
outFile
} = do
SomeCardanoAddressSigningKey
sKey <-
(FileError CardanoAddressSigningKeyConversionError -> KeyCmdError)
-> ExceptT
(FileError CardanoAddressSigningKeyConversionError)
IO
SomeCardanoAddressSigningKey
-> ExceptT KeyCmdError IO SomeCardanoAddressSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError CardanoAddressSigningKeyConversionError -> KeyCmdError
KeyCmdCardanoAddressSigningKeyFileError
(ExceptT
(FileError CardanoAddressSigningKeyConversionError)
IO
SomeCardanoAddressSigningKey
-> ExceptT KeyCmdError IO SomeCardanoAddressSigningKey)
-> (IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
-> ExceptT
(FileError CardanoAddressSigningKeyConversionError)
IO
SomeCardanoAddressSigningKey)
-> IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
-> ExceptT KeyCmdError IO SomeCardanoAddressSigningKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
-> ExceptT
(FileError CardanoAddressSigningKeyConversionError)
IO
SomeCardanoAddressSigningKey
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT
(IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
-> ExceptT KeyCmdError IO SomeCardanoAddressSigningKey)
-> IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
-> ExceptT KeyCmdError IO SomeCardanoAddressSigningKey
forall a b. (a -> b) -> a -> b
$ CardanoAddressKeyType
-> SigningKeyFile 'In
-> IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
readSomeCardanoAddressSigningKeyFile CardanoAddressKeyType
keyType SigningKeyFile 'In
skFile
(FileError () -> KeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> KeyCmdError
KeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT KeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT KeyCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT KeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
File () 'Out
-> SomeCardanoAddressSigningKey -> IO (Either (FileError ()) ())
forall direction.
File direction 'Out
-> SomeCardanoAddressSigningKey -> IO (Either (FileError ()) ())
writeSomeCardanoAddressSigningKeyFile File () 'Out
outFile SomeCardanoAddressSigningKey
sKey
data SomeCardanoAddressSigningKey
= ACardanoAddrShelleyPaymentSigningKey !(SigningKey PaymentExtendedKey)
| ACardanoAddrShelleyStakeSigningKey !(SigningKey StakeExtendedKey)
| ACardanoAddrByronSigningKey !(SigningKey ByronKey)
| ACardanoAddrCommitteeColdKey !(SigningKey CommitteeColdExtendedKey)
| ACardanoAddrCommitteeHotKey !(SigningKey CommitteeHotExtendedKey)
| ACardanoAddrDRepKey !(SigningKey DRepExtendedKey)
decodeBech32
:: Text
-> Either Bech32DecodeError (Bech32.HumanReadablePart, Bech32.DataPart, ByteString)
decodeBech32 :: Text
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
decodeBech32 Text
bech32Str =
case Text -> Either DecodingError (HumanReadablePart, DataPart)
Bech32.decodeLenient Text
bech32Str of
Left DecodingError
err -> Bech32DecodeError
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
forall a b. a -> Either a b
Left (DecodingError -> Bech32DecodeError
Bech32DecodingError DecodingError
err)
Right (HumanReadablePart
hrPart, DataPart
dataPart) ->
case DataPart -> Maybe ByteString
Bech32.dataPartToBytes DataPart
dataPart of
Maybe ByteString
Nothing ->
Bech32DecodeError
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
forall a b. a -> Either a b
Left (Bech32DecodeError
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString))
-> Bech32DecodeError
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
forall a b. (a -> b) -> a -> b
$ Text -> Bech32DecodeError
Bech32DataPartToBytesError (DataPart -> Text
Bech32.dataPartToText DataPart
dataPart)
Just ByteString
bs -> (HumanReadablePart, DataPart, ByteString)
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
forall a b. b -> Either a b
Right (HumanReadablePart
hrPart, DataPart
dataPart, ByteString
bs)
convertBip32SigningKey
:: ByteString
-> Either CardanoAddressSigningKeyConversionError Crypto.XPrv
convertBip32SigningKey :: ByteString -> Either CardanoAddressSigningKeyConversionError XPrv
convertBip32SigningKey ByteString
signingKeyBs =
case ByteString -> Maybe XPrv
xPrvFromBytes ByteString
signingKeyBs of
Just XPrv
xPrv -> XPrv -> Either CardanoAddressSigningKeyConversionError XPrv
forall a b. b -> Either a b
Right XPrv
xPrv
Maybe XPrv
Nothing ->
CardanoAddressSigningKeyConversionError
-> Either CardanoAddressSigningKeyConversionError XPrv
forall a b. a -> Either a b
Left (CardanoAddressSigningKeyConversionError
-> Either CardanoAddressSigningKeyConversionError XPrv)
-> CardanoAddressSigningKeyConversionError
-> Either CardanoAddressSigningKeyConversionError XPrv
forall a b. (a -> b) -> a -> b
$ ByteString -> CardanoAddressSigningKeyConversionError
CardanoAddressSigningKeyDeserialisationError ByteString
signingKeyBs
readBech32Bip32SigningKeyFile
:: SigningKeyFile In
-> IO (Either (FileError CardanoAddressSigningKeyConversionError) Crypto.XPrv)
readBech32Bip32SigningKeyFile :: SigningKeyFile 'In
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
readBech32Bip32SigningKeyFile (File [Char]
fp) = do
Either IOException [Char]
eStr <- IO [Char] -> IO (Either IOException [Char])
forall e a. Exception e => IO a -> IO (Either e a)
Exception.try (IO [Char] -> IO (Either IOException [Char]))
-> IO [Char] -> IO (Either IOException [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> IO [Char]
readFile [Char]
fp
case Either IOException [Char]
eStr of
Left IOException
e -> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv))
-> (FileError CardanoAddressSigningKeyConversionError
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
-> FileError CardanoAddressSigningKeyConversionError
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileError CardanoAddressSigningKeyConversionError
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
forall a b. a -> Either a b
Left (FileError CardanoAddressSigningKeyConversionError
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv))
-> FileError CardanoAddressSigningKeyConversionError
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
forall a b. (a -> b) -> a -> b
$ [Char]
-> IOException -> FileError CardanoAddressSigningKeyConversionError
forall e. [Char] -> IOException -> FileError e
FileIOError [Char]
fp IOException
e
Right [Char]
str ->
case Text
-> Either
Bech32DecodeError (HumanReadablePart, DataPart, ByteString)
decodeBech32 ([Text] -> Text
Text.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
Text.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
Text.pack [Char]
str) of
Left Bech32DecodeError
err ->
Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv))
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
forall a b. (a -> b) -> a -> b
$
FileError CardanoAddressSigningKeyConversionError
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
forall a b. a -> Either a b
Left (FileError CardanoAddressSigningKeyConversionError
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
-> FileError CardanoAddressSigningKeyConversionError
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
forall a b. (a -> b) -> a -> b
$
[Char]
-> CardanoAddressSigningKeyConversionError
-> FileError CardanoAddressSigningKeyConversionError
forall e. [Char] -> e -> FileError e
FileError [Char]
fp (Bech32DecodeError -> CardanoAddressSigningKeyConversionError
CardanoAddressSigningKeyBech32DecodeError Bech32DecodeError
err)
Right (HumanReadablePart
_hrPart, DataPart
_dataPart, ByteString
bs) ->
Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv))
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
forall a b. (a -> b) -> a -> b
$ (CardanoAddressSigningKeyConversionError
-> FileError CardanoAddressSigningKeyConversionError)
-> Either CardanoAddressSigningKeyConversionError XPrv
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
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 ([Char]
-> CardanoAddressSigningKeyConversionError
-> FileError CardanoAddressSigningKeyConversionError
forall e. [Char] -> e -> FileError e
FileError [Char]
fp) (ByteString -> Either CardanoAddressSigningKeyConversionError XPrv
convertBip32SigningKey ByteString
bs)
readSomeCardanoAddressSigningKeyFile
:: CardanoAddressKeyType
-> SigningKeyFile In
-> IO (Either (FileError CardanoAddressSigningKeyConversionError) SomeCardanoAddressSigningKey)
readSomeCardanoAddressSigningKeyFile :: CardanoAddressKeyType
-> SigningKeyFile 'In
-> IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
readSomeCardanoAddressSigningKeyFile CardanoAddressKeyType
keyType SigningKeyFile 'In
skFile = do
Either (FileError CardanoAddressSigningKeyConversionError) XPrv
xPrv <- SigningKeyFile 'In
-> IO
(Either (FileError CardanoAddressSigningKeyConversionError) XPrv)
readBech32Bip32SigningKeyFile SigningKeyFile 'In
skFile
Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey
-> IO
(Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (XPrv -> SomeCardanoAddressSigningKey
toSomeCardanoAddressSigningKey (XPrv -> SomeCardanoAddressSigningKey)
-> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
-> Either
(FileError CardanoAddressSigningKeyConversionError)
SomeCardanoAddressSigningKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either (FileError CardanoAddressSigningKeyConversionError) XPrv
xPrv)
where
toSomeCardanoAddressSigningKey :: Crypto.XPrv -> SomeCardanoAddressSigningKey
toSomeCardanoAddressSigningKey :: XPrv -> SomeCardanoAddressSigningKey
toSomeCardanoAddressSigningKey XPrv
xPrv =
case CardanoAddressKeyType
keyType of
CardanoAddressKeyType
CardanoAddressShelleyPaymentKey -> SigningKey PaymentExtendedKey -> SomeCardanoAddressSigningKey
ACardanoAddrShelleyPaymentSigningKey (XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey XPrv
xPrv)
CardanoAddressKeyType
CardanoAddressShelleyStakeKey -> SigningKey StakeExtendedKey -> SomeCardanoAddressSigningKey
ACardanoAddrShelleyStakeSigningKey (XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey XPrv
xPrv)
CardanoAddressKeyType
CardanoAddressIcarusPaymentKey -> SigningKey ByronKey -> SomeCardanoAddressSigningKey
ACardanoAddrByronSigningKey (SigningKey ByronKey -> SomeCardanoAddressSigningKey)
-> SigningKey ByronKey -> SomeCardanoAddressSigningKey
forall a b. (a -> b) -> a -> b
$ SigningKey -> SigningKey ByronKey
ByronSigningKey (XPrv -> SigningKey
Byron.SigningKey XPrv
xPrv)
CardanoAddressKeyType
CardanoAddressByronPaymentKey -> SigningKey ByronKey -> SomeCardanoAddressSigningKey
ACardanoAddrByronSigningKey (SigningKey ByronKey -> SomeCardanoAddressSigningKey)
-> SigningKey ByronKey -> SomeCardanoAddressSigningKey
forall a b. (a -> b) -> a -> b
$ SigningKey -> SigningKey ByronKey
ByronSigningKey (XPrv -> SigningKey
Byron.SigningKey XPrv
xPrv)
CardanoAddressKeyType
CardanoAddressCommitteeColdKey -> SigningKey CommitteeColdExtendedKey -> SomeCardanoAddressSigningKey
ACardanoAddrCommitteeColdKey (XPrv -> SigningKey CommitteeColdExtendedKey
CommitteeColdExtendedSigningKey XPrv
xPrv)
CardanoAddressKeyType
CardanoAddressCommitteeHotKey -> SigningKey CommitteeHotExtendedKey -> SomeCardanoAddressSigningKey
ACardanoAddrCommitteeHotKey (XPrv -> SigningKey CommitteeHotExtendedKey
CommitteeHotExtendedSigningKey XPrv
xPrv)
CardanoAddressKeyType
CardanoAddressDRepKey -> SigningKey DRepExtendedKey -> SomeCardanoAddressSigningKey
ACardanoAddrDRepKey (XPrv -> SigningKey DRepExtendedKey
DRepExtendedSigningKey XPrv
xPrv)
writeSomeCardanoAddressSigningKeyFile
:: File direction Out
-> SomeCardanoAddressSigningKey
-> IO (Either (FileError ()) ())
writeSomeCardanoAddressSigningKeyFile :: forall direction.
File direction 'Out
-> SomeCardanoAddressSigningKey -> IO (Either (FileError ()) ())
writeSomeCardanoAddressSigningKeyFile File direction 'Out
outFile =
\case
ACardanoAddrShelleyPaymentSigningKey SigningKey PaymentExtendedKey
sk -> Maybe TextEnvelopeDescr
-> SigningKey PaymentExtendedKey -> IO (Either (FileError ()) ())
forall {m :: * -> *} {a} {e}.
(MonadIO m, HasTextEnvelope a) =>
Maybe TextEnvelopeDescr -> a -> m (Either (FileError e) ())
go Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey PaymentExtendedKey
sk
ACardanoAddrShelleyStakeSigningKey SigningKey StakeExtendedKey
sk -> Maybe TextEnvelopeDescr
-> SigningKey StakeExtendedKey -> IO (Either (FileError ()) ())
forall {m :: * -> *} {a} {e}.
(MonadIO m, HasTextEnvelope a) =>
Maybe TextEnvelopeDescr -> a -> m (Either (FileError e) ())
go Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeExtendedKey
sk
ACardanoAddrByronSigningKey SigningKey ByronKey
sk -> Maybe TextEnvelopeDescr
-> SigningKey ByronKey -> IO (Either (FileError ()) ())
forall {m :: * -> *} {a} {e}.
(MonadIO m, HasTextEnvelope a) =>
Maybe TextEnvelopeDescr -> a -> m (Either (FileError e) ())
go Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey ByronKey
sk
ACardanoAddrCommitteeColdKey SigningKey CommitteeColdExtendedKey
sk -> Maybe TextEnvelopeDescr
-> SigningKey CommitteeColdExtendedKey
-> IO (Either (FileError ()) ())
forall {m :: * -> *} {a} {e}.
(MonadIO m, HasTextEnvelope a) =>
Maybe TextEnvelopeDescr -> a -> m (Either (FileError e) ())
go (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
ccColdExtendedSkeyDesc) SigningKey CommitteeColdExtendedKey
sk
ACardanoAddrCommitteeHotKey SigningKey CommitteeHotExtendedKey
sk -> Maybe TextEnvelopeDescr
-> SigningKey CommitteeHotExtendedKey
-> IO (Either (FileError ()) ())
forall {m :: * -> *} {a} {e}.
(MonadIO m, HasTextEnvelope a) =>
Maybe TextEnvelopeDescr -> a -> m (Either (FileError e) ())
go (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
ccHotExtendedSkeyDesc) SigningKey CommitteeHotExtendedKey
sk
ACardanoAddrDRepKey SigningKey DRepExtendedKey
sk -> Maybe TextEnvelopeDescr
-> SigningKey DRepExtendedKey -> IO (Either (FileError ()) ())
forall {m :: * -> *} {a} {e}.
(MonadIO m, HasTextEnvelope a) =>
Maybe TextEnvelopeDescr -> a -> m (Either (FileError e) ())
go (TextEnvelopeDescr -> Maybe TextEnvelopeDescr
forall a. a -> Maybe a
Just TextEnvelopeDescr
drepExtendedSkeyDesc) SigningKey DRepExtendedKey
sk
where
go :: Maybe TextEnvelopeDescr -> a -> m (Either (FileError e) ())
go Maybe TextEnvelopeDescr
envelope a
sk = File direction 'Out -> ByteString -> m (Either (FileError e) ())
forall (m :: * -> *) content e.
MonadIO m =>
File content 'Out -> ByteString -> m (Either (FileError e) ())
writeLazyByteStringFile File direction 'Out
outFile (ByteString -> m (Either (FileError e) ()))
-> ByteString -> m (Either (FileError e) ())
forall a b. (a -> b) -> a -> b
$ Maybe TextEnvelopeDescr -> a -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
envelope a
sk