{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Bcc.CLI.Sophie.Run.Key
( SophieKeyCmdError
, SomeSigningKey(..)
, renderSophieKeyCmdError
, runKeyCmd
, decodeBech32
) where
import Bcc.Prelude
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import qualified Data.Text as Text
import qualified Control.Exception as Exception
import Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither, left, newExceptT)
import qualified Codec.Binary.Bech32 as Bech32
import qualified Bcc.Crypto.DSIGN as DSIGN
import qualified Bcc.Crypto.Signing as Cole.Crypto
import qualified Bcc.Crypto.Signing as Cole
import qualified Bcc.Crypto.Signing as Crypto
import qualified Bcc.Crypto.Wallet as Crypto
import qualified Bcc.Ledger.Keys as Sophie
import Bcc.Api
import Bcc.Api.Cole hiding (SomeColeSigningKey (..))
import qualified Bcc.Api.Cole as ColeApi
import Bcc.Api.Crypto.Ed25519Bip32 (xPrvFromBytes)
import Bcc.Api.Sophie
import qualified Bcc.CLI.Cole.Key as Cole
import Bcc.CLI.Helpers (textShow)
import Bcc.CLI.Sophie.Commands
import Bcc.CLI.Sophie.Key (InputDecodeError, readSigningKeyFileAnyOf)
import Bcc.CLI.Types (SigningKeyFile (..), VerificationKeyFile (..))
data SophieKeyCmdError
= SophieKeyCmdReadFileError !(FileError TextEnvelopeError)
| SophieKeyCmdReadKeyFileError !(FileError InputDecodeError)
| SophieKeyCmdWriteFileError !(FileError ())
| SophieKeyCmdColeKeyFailure !Cole.ColeKeyFailure
| SophieKeyCmdColeKeyParseError
!Text
| SophieKeyCmdItnKeyConvError !ItnKeyConversionError
| SophieKeyCmdWrongKeyTypeError
| SophieKeyCmdBccAddressSigningKeyFileError
!(FileError BccAddressSigningKeyConversionError)
| SophieKeyCmdNonLegacyKey !FilePath
deriving Int -> SophieKeyCmdError -> ShowS
[SophieKeyCmdError] -> ShowS
SophieKeyCmdError -> String
(Int -> SophieKeyCmdError -> ShowS)
-> (SophieKeyCmdError -> String)
-> ([SophieKeyCmdError] -> ShowS)
-> Show SophieKeyCmdError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SophieKeyCmdError] -> ShowS
$cshowList :: [SophieKeyCmdError] -> ShowS
show :: SophieKeyCmdError -> String
$cshow :: SophieKeyCmdError -> String
showsPrec :: Int -> SophieKeyCmdError -> ShowS
$cshowsPrec :: Int -> SophieKeyCmdError -> ShowS
Show
renderSophieKeyCmdError :: SophieKeyCmdError -> Text
renderSophieKeyCmdError :: SophieKeyCmdError -> Text
renderSophieKeyCmdError SophieKeyCmdError
err =
case SophieKeyCmdError
err of
SophieKeyCmdReadFileError FileError TextEnvelopeError
fileErr -> String -> Text
Text.pack (FileError TextEnvelopeError -> String
forall e. Error e => e -> String
displayError FileError TextEnvelopeError
fileErr)
SophieKeyCmdReadKeyFileError FileError InputDecodeError
fileErr -> String -> Text
Text.pack (FileError InputDecodeError -> String
forall e. Error e => e -> String
displayError FileError InputDecodeError
fileErr)
SophieKeyCmdWriteFileError FileError ()
fileErr -> String -> Text
Text.pack (FileError () -> String
forall e. Error e => e -> String
displayError FileError ()
fileErr)
SophieKeyCmdColeKeyFailure ColeKeyFailure
e -> ColeKeyFailure -> Text
Cole.renderColeKeyFailure ColeKeyFailure
e
SophieKeyCmdColeKeyParseError Text
errTxt -> Text
errTxt
SophieKeyCmdItnKeyConvError ItnKeyConversionError
convErr -> ItnKeyConversionError -> Text
renderConversionError ItnKeyConversionError
convErr
SophieKeyCmdError
SophieKeyCmdWrongKeyTypeError -> String -> Text
Text.pack String
"Please use a signing key file \
\when converting ITN BIP32 or Extended keys"
SophieKeyCmdBccAddressSigningKeyFileError FileError BccAddressSigningKeyConversionError
fileErr ->
String -> Text
Text.pack (FileError BccAddressSigningKeyConversionError -> String
forall e. Error e => e -> String
displayError FileError BccAddressSigningKeyConversionError
fileErr)
SophieKeyCmdNonLegacyKey String
fp -> Text
"Signing key at: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack String
fp Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a legacy Cole signing key and should \
\ not need to be converted."
runKeyCmd :: KeyCmd -> ExceptT SophieKeyCmdError IO ()
runKeyCmd :: KeyCmd -> ExceptT SophieKeyCmdError IO ()
runKeyCmd KeyCmd
cmd =
case KeyCmd
cmd of
KeyGetVerificationKey SigningKeyFile
skf VerificationKeyFile
vkf ->
SigningKeyFile
-> VerificationKeyFile -> ExceptT SophieKeyCmdError IO ()
runGetVerificationKey SigningKeyFile
skf VerificationKeyFile
vkf
KeyNonExtendedKey VerificationKeyFile
evkf VerificationKeyFile
vkf ->
VerificationKeyFile
-> VerificationKeyFile -> ExceptT SophieKeyCmdError IO ()
runNonExtendedKey VerificationKeyFile
evkf VerificationKeyFile
vkf
KeyConvertColeKey Maybe Text
mPassword ColeKeyType
keytype SomeKeyFile
skfOld OutputFile
skfNew ->
Maybe Text
-> ColeKeyType
-> SomeKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
runConvertColeKey Maybe Text
mPassword ColeKeyType
keytype SomeKeyFile
skfOld OutputFile
skfNew
KeyConvertColeGenesisVKey VerificationKeyBase64
oldVk OutputFile
newVkf ->
VerificationKeyBase64
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertColeGenesisVerificationKey VerificationKeyBase64
oldVk OutputFile
newVkf
KeyConvertColeVestedVKey VerificationKeyBase64
oldVk OutputFile
newVkf ->
VerificationKeyBase64
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertColeVestedVerificationKey VerificationKeyBase64
oldVk OutputFile
newVkf
KeyConvertITNStakeKey SomeKeyFile
itnKeyFile OutputFile
outFile ->
SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNStakeKey SomeKeyFile
itnKeyFile OutputFile
outFile
KeyConvertITNExtendedToStakeKey SomeKeyFile
itnPrivKeyFile OutputFile
outFile ->
SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNExtendedToStakeKey SomeKeyFile
itnPrivKeyFile OutputFile
outFile
KeyConvertITNBip32ToStakeKey SomeKeyFile
itnPrivKeyFile OutputFile
outFile ->
SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNBip32ToStakeKey SomeKeyFile
itnPrivKeyFile OutputFile
outFile
KeyConvertBccAddressSigningKey BccAddressKeyType
keyType SigningKeyFile
skfOld OutputFile
skfNew ->
BccAddressKeyType
-> SigningKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertBccAddressSigningKey BccAddressKeyType
keyType SigningKeyFile
skfOld OutputFile
skfNew
runGetVerificationKey :: SigningKeyFile
-> VerificationKeyFile
-> ExceptT SophieKeyCmdError IO ()
runGetVerificationKey :: SigningKeyFile
-> VerificationKeyFile -> ExceptT SophieKeyCmdError IO ()
runGetVerificationKey SigningKeyFile
skf (VerificationKeyFile String
vkf) = do
SomeSigningKey
ssk <- (FileError InputDecodeError -> SophieKeyCmdError)
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
-> ExceptT SophieKeyCmdError IO SomeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError InputDecodeError -> SophieKeyCmdError
SophieKeyCmdReadKeyFileError (ExceptT (FileError InputDecodeError) IO SomeSigningKey
-> ExceptT SophieKeyCmdError IO SomeSigningKey)
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
-> ExceptT SophieKeyCmdError IO SomeSigningKey
forall a b. (a -> b) -> a -> b
$
SigningKeyFile
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
readSigningKeyFile SigningKeyFile
skf
SomeSigningKey
-> (forall keyrole.
Key keyrole =>
SigningKey keyrole -> ExceptT SophieKeyCmdError IO ())
-> ExceptT SophieKeyCmdError IO ()
forall a.
SomeSigningKey
-> (forall keyrole. Key keyrole => SigningKey keyrole -> a) -> a
withSomeSigningKey SomeSigningKey
ssk ((forall keyrole.
Key keyrole =>
SigningKey keyrole -> ExceptT SophieKeyCmdError IO ())
-> ExceptT SophieKeyCmdError IO ())
-> (forall keyrole.
Key keyrole =>
SigningKey keyrole -> ExceptT SophieKeyCmdError IO ())
-> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$ \SigningKey keyrole
sk ->
let vk :: VerificationKey keyrole
vk = SigningKey keyrole -> VerificationKey keyrole
forall keyrole.
Key keyrole =>
SigningKey keyrole -> VerificationKey keyrole
getVerificationKey SigningKey keyrole
sk in
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError 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
vkf Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey keyrole
vk
data SomeSigningKey
= AColeSigningKey (SigningKey ColeKey)
| APaymentSigningKey (SigningKey PaymentKey)
| APaymentExtendedSigningKey (SigningKey PaymentExtendedKey)
| AStakeSigningKey (SigningKey StakeKey)
| AStakeExtendedSigningKey (SigningKey StakeExtendedKey)
| AStakePoolSigningKey (SigningKey StakePoolKey)
| AGenesisSigningKey (SigningKey GenesisKey)
| AGenesisExtendedSigningKey (SigningKey GenesisExtendedKey)
| AGenesisDelegateSigningKey (SigningKey GenesisDelegateKey)
| AGenesisDelegateExtendedSigningKey (SigningKey GenesisDelegateExtendedKey)
| AGenesisVestedSigningKey (SigningKey GenesisVestedKey)
| AGenesisVestedExtendedSigningKey (SigningKey GenesisVestedExtendedKey)
| AGenesisVestedDelegateSigningKey (SigningKey GenesisVestedDelegateKey)
| AGenesisVestedDelegateExtendedSigningKey (SigningKey GenesisVestedDelegateExtendedKey)
| AGenesisUTxOSigningKey (SigningKey GenesisUTxOKey)
| AVestedSigningKey (SigningKey VestedKey)
| AVestedExtendedSigningKey (SigningKey VestedExtendedKey)
| AVestedDelegateSigningKey (SigningKey VestedDelegateKey)
| AVestedDelegateExtendedSigningKey (SigningKey VestedDelegateExtendedKey)
| AVestedUTxOSigningKey (SigningKey VestedUTxOKey)
| AVrfSigningKey (SigningKey VrfKey)
| AKesSigningKey (SigningKey KesKey)
withSomeSigningKey :: SomeSigningKey
-> (forall keyrole. Key keyrole => SigningKey keyrole -> a)
-> a
withSomeSigningKey :: SomeSigningKey
-> (forall keyrole. Key keyrole => SigningKey keyrole -> a) -> a
withSomeSigningKey SomeSigningKey
ssk forall keyrole. Key keyrole => SigningKey keyrole -> a
f =
case SomeSigningKey
ssk of
AColeSigningKey SigningKey ColeKey
sk -> SigningKey ColeKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey ColeKey
sk
APaymentSigningKey SigningKey PaymentKey
sk -> SigningKey PaymentKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey PaymentKey
sk
APaymentExtendedSigningKey SigningKey PaymentExtendedKey
sk -> SigningKey PaymentExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey PaymentExtendedKey
sk
AStakeSigningKey SigningKey StakeKey
sk -> SigningKey StakeKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey StakeKey
sk
AStakeExtendedSigningKey SigningKey StakeExtendedKey
sk -> SigningKey StakeExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey StakeExtendedKey
sk
AStakePoolSigningKey SigningKey StakePoolKey
sk -> SigningKey StakePoolKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey StakePoolKey
sk
AGenesisSigningKey SigningKey GenesisKey
sk -> SigningKey GenesisKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisKey
sk
AGenesisExtendedSigningKey SigningKey GenesisExtendedKey
sk -> SigningKey GenesisExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisExtendedKey
sk
AGenesisDelegateSigningKey SigningKey GenesisDelegateKey
sk -> SigningKey GenesisDelegateKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisDelegateKey
sk
AGenesisDelegateExtendedSigningKey SigningKey GenesisDelegateExtendedKey
sk -> SigningKey GenesisDelegateExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisDelegateExtendedKey
sk
AGenesisVestedSigningKey SigningKey GenesisVestedKey
sk -> SigningKey GenesisVestedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisVestedKey
sk
AGenesisVestedExtendedSigningKey SigningKey GenesisVestedExtendedKey
sk -> SigningKey GenesisVestedExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisVestedExtendedKey
sk
AGenesisVestedDelegateSigningKey SigningKey GenesisVestedDelegateKey
sk -> SigningKey GenesisVestedDelegateKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisVestedDelegateKey
sk
AGenesisVestedDelegateExtendedSigningKey SigningKey GenesisVestedDelegateExtendedKey
sk -> SigningKey GenesisVestedDelegateExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisVestedDelegateExtendedKey
sk
AGenesisUTxOSigningKey SigningKey GenesisUTxOKey
sk -> SigningKey GenesisUTxOKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey GenesisUTxOKey
sk
AVestedSigningKey SigningKey VestedKey
sk -> SigningKey VestedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey VestedKey
sk
AVestedExtendedSigningKey SigningKey VestedExtendedKey
sk -> SigningKey VestedExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey VestedExtendedKey
sk
AVestedDelegateSigningKey SigningKey VestedDelegateKey
sk -> SigningKey VestedDelegateKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey VestedDelegateKey
sk
AVestedDelegateExtendedSigningKey SigningKey VestedDelegateExtendedKey
sk -> SigningKey VestedDelegateExtendedKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey VestedDelegateExtendedKey
sk
AVestedUTxOSigningKey SigningKey VestedUTxOKey
sk -> SigningKey VestedUTxOKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey VestedUTxOKey
sk
AVrfSigningKey SigningKey VrfKey
sk -> SigningKey VrfKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey VrfKey
sk
AKesSigningKey SigningKey KesKey
sk -> SigningKey KesKey -> a
forall keyrole. Key keyrole => SigningKey keyrole -> a
f SigningKey KesKey
sk
readSigningKeyFile
:: SigningKeyFile
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
readSigningKeyFile :: SigningKeyFile
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
readSigningKeyFile SigningKeyFile
skFile =
IO (Either (FileError InputDecodeError) SomeSigningKey)
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError InputDecodeError) SomeSigningKey)
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey)
-> IO (Either (FileError InputDecodeError) SomeSigningKey)
-> ExceptT (FileError InputDecodeError) IO SomeSigningKey
forall a b. (a -> b) -> a -> b
$
[FromSomeType SerialiseAsBech32 SomeSigningKey]
-> [FromSomeType HasTextEnvelope SomeSigningKey]
-> SigningKeyFile
-> IO (Either (FileError InputDecodeError) SomeSigningKey)
forall b.
[FromSomeType SerialiseAsBech32 b]
-> [FromSomeType HasTextEnvelope b]
-> SigningKeyFile
-> IO (Either (FileError InputDecodeError) b)
readSigningKeyFileAnyOf [FromSomeType SerialiseAsBech32 SomeSigningKey]
bech32FileTypes [FromSomeType HasTextEnvelope SomeSigningKey]
textEnvFileTypes SigningKeyFile
skFile
where
textEnvFileTypes :: [FromSomeType HasTextEnvelope SomeSigningKey]
textEnvFileTypes =
[ AsType (SigningKey ColeKey)
-> (SigningKey ColeKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType ColeKey -> AsType (SigningKey ColeKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType ColeKey
AsColeKey)
SigningKey ColeKey -> SomeSigningKey
AColeSigningKey
, AsType (SigningKey PaymentKey)
-> (SigningKey PaymentKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentKey -> AsType (SigningKey PaymentKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType PaymentKey
AsPaymentKey)
SigningKey PaymentKey -> SomeSigningKey
APaymentSigningKey
, AsType (SigningKey PaymentExtendedKey)
-> (SigningKey PaymentExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentExtendedKey -> AsType (SigningKey PaymentExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType PaymentExtendedKey
AsPaymentExtendedKey)
SigningKey PaymentExtendedKey -> SomeSigningKey
APaymentExtendedSigningKey
, AsType (SigningKey StakeKey)
-> (SigningKey StakeKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeKey -> AsType (SigningKey StakeKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType StakeKey
AsStakeKey)
SigningKey StakeKey -> SomeSigningKey
AStakeSigningKey
, AsType (SigningKey StakeExtendedKey)
-> (SigningKey StakeExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeExtendedKey -> AsType (SigningKey StakeExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType StakeExtendedKey
AsStakeExtendedKey)
SigningKey StakeExtendedKey -> SomeSigningKey
AStakeExtendedSigningKey
, AsType (SigningKey StakePoolKey)
-> (SigningKey StakePoolKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakePoolKey -> AsType (SigningKey StakePoolKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType StakePoolKey
AsStakePoolKey)
SigningKey StakePoolKey -> SomeSigningKey
AStakePoolSigningKey
, AsType (SigningKey GenesisKey)
-> (SigningKey GenesisKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisKey -> AsType (SigningKey GenesisKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisKey
AsGenesisKey)
SigningKey GenesisKey -> SomeSigningKey
AGenesisSigningKey
, AsType (SigningKey GenesisExtendedKey)
-> (SigningKey GenesisExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisExtendedKey -> AsType (SigningKey GenesisExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisExtendedKey
AsGenesisExtendedKey)
SigningKey GenesisExtendedKey -> SomeSigningKey
AGenesisExtendedSigningKey
, AsType (SigningKey GenesisDelegateKey)
-> (SigningKey GenesisDelegateKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisDelegateKey -> AsType (SigningKey GenesisDelegateKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisDelegateKey
AsGenesisDelegateKey)
SigningKey GenesisDelegateKey -> SomeSigningKey
AGenesisDelegateSigningKey
, AsType (SigningKey GenesisDelegateExtendedKey)
-> (SigningKey GenesisDelegateExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisDelegateExtendedKey
-> AsType (SigningKey GenesisDelegateExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey)
SigningKey GenesisDelegateExtendedKey -> SomeSigningKey
AGenesisDelegateExtendedSigningKey
, AsType (SigningKey GenesisVestedKey)
-> (SigningKey GenesisVestedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisVestedKey -> AsType (SigningKey GenesisVestedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisVestedKey
AsGenesisVestedKey)
SigningKey GenesisVestedKey -> SomeSigningKey
AGenesisVestedSigningKey
, AsType (SigningKey GenesisVestedExtendedKey)
-> (SigningKey GenesisVestedExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisVestedExtendedKey
-> AsType (SigningKey GenesisVestedExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisVestedExtendedKey
AsGenesisVestedExtendedKey)
SigningKey GenesisVestedExtendedKey -> SomeSigningKey
AGenesisVestedExtendedSigningKey
, AsType (SigningKey GenesisVestedDelegateKey)
-> (SigningKey GenesisVestedDelegateKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisVestedDelegateKey
-> AsType (SigningKey GenesisVestedDelegateKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisVestedDelegateKey
AsGenesisVestedDelegateKey)
SigningKey GenesisVestedDelegateKey -> SomeSigningKey
AGenesisVestedDelegateSigningKey
, AsType (SigningKey GenesisVestedDelegateExtendedKey)
-> (SigningKey GenesisVestedDelegateExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisVestedDelegateExtendedKey
-> AsType (SigningKey GenesisVestedDelegateExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisVestedDelegateExtendedKey
AsGenesisVestedDelegateExtendedKey)
SigningKey GenesisVestedDelegateExtendedKey -> SomeSigningKey
AGenesisVestedDelegateExtendedSigningKey
, AsType (SigningKey GenesisUTxOKey)
-> (SigningKey GenesisUTxOKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisUTxOKey -> AsType (SigningKey GenesisUTxOKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType GenesisUTxOKey
AsGenesisUTxOKey)
SigningKey GenesisUTxOKey -> SomeSigningKey
AGenesisUTxOSigningKey
, AsType (SigningKey VestedKey)
-> (SigningKey VestedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VestedKey -> AsType (SigningKey VestedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType VestedKey
AsVestedKey)
SigningKey VestedKey -> SomeSigningKey
AVestedSigningKey
, AsType (SigningKey VestedExtendedKey)
-> (SigningKey VestedExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VestedExtendedKey -> AsType (SigningKey VestedExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType VestedExtendedKey
AsVestedExtendedKey)
SigningKey VestedExtendedKey -> SomeSigningKey
AVestedExtendedSigningKey
, AsType (SigningKey VestedDelegateKey)
-> (SigningKey VestedDelegateKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VestedDelegateKey -> AsType (SigningKey VestedDelegateKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType VestedDelegateKey
AsVestedDelegateKey)
SigningKey VestedDelegateKey -> SomeSigningKey
AVestedDelegateSigningKey
, AsType (SigningKey VestedDelegateExtendedKey)
-> (SigningKey VestedDelegateExtendedKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VestedDelegateExtendedKey
-> AsType (SigningKey VestedDelegateExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType VestedDelegateExtendedKey
AsVestedDelegateExtendedKey)
SigningKey VestedDelegateExtendedKey -> SomeSigningKey
AVestedDelegateExtendedSigningKey
, AsType (SigningKey VestedUTxOKey)
-> (SigningKey VestedUTxOKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VestedUTxOKey -> AsType (SigningKey VestedUTxOKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType VestedUTxOKey
AsVestedUTxOKey)
SigningKey VestedUTxOKey -> SomeSigningKey
AVestedUTxOSigningKey
, AsType (SigningKey VrfKey)
-> (SigningKey VrfKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VrfKey -> AsType (SigningKey VrfKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType VrfKey
AsVrfKey)
SigningKey VrfKey -> SomeSigningKey
AVrfSigningKey
, AsType (SigningKey KesKey)
-> (SigningKey KesKey -> SomeSigningKey)
-> FromSomeType HasTextEnvelope SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType KesKey -> AsType (SigningKey KesKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType KesKey
AsKesKey)
SigningKey KesKey -> SomeSigningKey
AKesSigningKey
]
bech32FileTypes :: [FromSomeType SerialiseAsBech32 SomeSigningKey]
bech32FileTypes =
[ AsType (SigningKey PaymentKey)
-> (SigningKey PaymentKey -> SomeSigningKey)
-> FromSomeType SerialiseAsBech32 SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentKey -> AsType (SigningKey PaymentKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType PaymentKey
AsPaymentKey)
SigningKey PaymentKey -> SomeSigningKey
APaymentSigningKey
, AsType (SigningKey PaymentExtendedKey)
-> (SigningKey PaymentExtendedKey -> SomeSigningKey)
-> FromSomeType SerialiseAsBech32 SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentExtendedKey -> AsType (SigningKey PaymentExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType PaymentExtendedKey
AsPaymentExtendedKey)
SigningKey PaymentExtendedKey -> SomeSigningKey
APaymentExtendedSigningKey
, AsType (SigningKey StakeKey)
-> (SigningKey StakeKey -> SomeSigningKey)
-> FromSomeType SerialiseAsBech32 SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeKey -> AsType (SigningKey StakeKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType StakeKey
AsStakeKey)
SigningKey StakeKey -> SomeSigningKey
AStakeSigningKey
, AsType (SigningKey StakeExtendedKey)
-> (SigningKey StakeExtendedKey -> SomeSigningKey)
-> FromSomeType SerialiseAsBech32 SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeExtendedKey -> AsType (SigningKey StakeExtendedKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType StakeExtendedKey
AsStakeExtendedKey)
SigningKey StakeExtendedKey -> SomeSigningKey
AStakeExtendedSigningKey
, AsType (SigningKey StakePoolKey)
-> (SigningKey StakePoolKey -> SomeSigningKey)
-> FromSomeType SerialiseAsBech32 SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakePoolKey -> AsType (SigningKey StakePoolKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType StakePoolKey
AsStakePoolKey)
SigningKey StakePoolKey -> SomeSigningKey
AStakePoolSigningKey
, AsType (SigningKey VrfKey)
-> (SigningKey VrfKey -> SomeSigningKey)
-> FromSomeType SerialiseAsBech32 SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VrfKey -> AsType (SigningKey VrfKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType VrfKey
AsVrfKey)
SigningKey VrfKey -> SomeSigningKey
AVrfSigningKey
, AsType (SigningKey KesKey)
-> (SigningKey KesKey -> SomeSigningKey)
-> FromSomeType SerialiseAsBech32 SomeSigningKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType KesKey -> AsType (SigningKey KesKey)
forall a. AsType a -> AsType (SigningKey a)
AsSigningKey AsType KesKey
AsKesKey)
SigningKey KesKey -> SomeSigningKey
AKesSigningKey
]
runNonExtendedKey :: VerificationKeyFile
-> VerificationKeyFile
-> ExceptT SophieKeyCmdError IO ()
runNonExtendedKey :: VerificationKeyFile
-> VerificationKeyFile -> ExceptT SophieKeyCmdError IO ()
runNonExtendedKey VerificationKeyFile
evkf (VerificationKeyFile String
vkf) = do
SomeExtendedVerificationKey
evk <- (FileError TextEnvelopeError -> SophieKeyCmdError)
-> ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey
-> ExceptT SophieKeyCmdError IO SomeExtendedVerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError TextEnvelopeError -> SophieKeyCmdError
SophieKeyCmdReadFileError (ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey
-> ExceptT SophieKeyCmdError IO SomeExtendedVerificationKey)
-> ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey
-> ExceptT SophieKeyCmdError IO SomeExtendedVerificationKey
forall a b. (a -> b) -> a -> b
$
VerificationKeyFile
-> ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey
readExtendedVerificationKeyFile VerificationKeyFile
evkf
SomeExtendedVerificationKey
-> (forall keyrole.
Key keyrole =>
VerificationKey keyrole -> ExceptT SophieKeyCmdError IO ())
-> ExceptT SophieKeyCmdError IO ()
forall a.
SomeExtendedVerificationKey
-> (forall keyrole. Key keyrole => VerificationKey keyrole -> a)
-> a
withNonExtendedKey SomeExtendedVerificationKey
evk ((forall keyrole.
Key keyrole =>
VerificationKey keyrole -> ExceptT SophieKeyCmdError IO ())
-> ExceptT SophieKeyCmdError IO ())
-> (forall keyrole.
Key keyrole =>
VerificationKey keyrole -> ExceptT SophieKeyCmdError IO ())
-> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$ \VerificationKey keyrole
vk ->
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError 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
vkf Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey keyrole
vk
withNonExtendedKey :: SomeExtendedVerificationKey
-> (forall keyrole. Key keyrole => VerificationKey keyrole -> a)
-> a
withNonExtendedKey :: SomeExtendedVerificationKey
-> (forall keyrole. Key keyrole => VerificationKey keyrole -> a)
-> a
withNonExtendedKey (APaymentExtendedVerificationKey VerificationKey PaymentExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey PaymentKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey PaymentExtendedKey -> VerificationKey PaymentKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey PaymentExtendedKey
vk :: VerificationKey PaymentKey)
withNonExtendedKey (AStakeExtendedVerificationKey VerificationKey StakeExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey StakeKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey StakeExtendedKey -> VerificationKey StakeKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey StakeExtendedKey
vk :: VerificationKey StakeKey)
withNonExtendedKey (AGenesisExtendedVerificationKey VerificationKey GenesisExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey GenesisKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey GenesisExtendedKey -> VerificationKey GenesisKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisExtendedKey
vk :: VerificationKey GenesisKey)
withNonExtendedKey (AGenesisDelegateExtendedVerificationKey VerificationKey GenesisDelegateExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey GenesisDelegateKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey GenesisDelegateExtendedKey
-> VerificationKey GenesisDelegateKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisDelegateExtendedKey
vk :: VerificationKey GenesisDelegateKey)
withNonExtendedKey (AGenesisVestedExtendedVerificationKey VerificationKey GenesisVestedExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey GenesisVestedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey GenesisVestedExtendedKey
-> VerificationKey GenesisVestedKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisVestedExtendedKey
vk :: VerificationKey GenesisVestedKey)
withNonExtendedKey (AGenesisVestedDelegateExtendedVerificationKey VerificationKey GenesisVestedDelegateExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey GenesisVestedDelegateKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey GenesisVestedDelegateExtendedKey
-> VerificationKey GenesisVestedDelegateKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey GenesisVestedDelegateExtendedKey
vk :: VerificationKey GenesisVestedDelegateKey)
withNonExtendedKey (AVestedExtendedVerificationKey VerificationKey VestedExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey VestedKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey VestedExtendedKey -> VerificationKey VestedKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey VestedExtendedKey
vk :: VerificationKey VestedKey)
withNonExtendedKey (AVestedDelegateExtendedVerificationKey VerificationKey VestedDelegateExtendedKey
vk) forall keyrole. Key keyrole => VerificationKey keyrole -> a
f =
VerificationKey VestedDelegateKey -> a
forall keyrole. Key keyrole => VerificationKey keyrole -> a
f (VerificationKey VestedDelegateExtendedKey
-> VerificationKey VestedDelegateKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey VerificationKey VestedDelegateExtendedKey
vk :: VerificationKey VestedDelegateKey)
data SomeExtendedVerificationKey
= APaymentExtendedVerificationKey (VerificationKey PaymentExtendedKey)
| AStakeExtendedVerificationKey (VerificationKey StakeExtendedKey)
| AGenesisExtendedVerificationKey (VerificationKey GenesisExtendedKey)
| AGenesisDelegateExtendedVerificationKey (VerificationKey GenesisDelegateExtendedKey)
| AGenesisVestedExtendedVerificationKey (VerificationKey GenesisVestedExtendedKey)
| AGenesisVestedDelegateExtendedVerificationKey (VerificationKey GenesisVestedDelegateExtendedKey)
| AVestedExtendedVerificationKey (VerificationKey VestedExtendedKey)
| AVestedDelegateExtendedVerificationKey (VerificationKey VestedDelegateExtendedKey)
readExtendedVerificationKeyFile
:: VerificationKeyFile
-> ExceptT (FileError TextEnvelopeError) IO SomeExtendedVerificationKey
readExtendedVerificationKeyFile :: VerificationKeyFile
-> ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey
readExtendedVerificationKeyFile (VerificationKeyFile String
evkfile) =
IO
(Either (FileError TextEnvelopeError) SomeExtendedVerificationKey)
-> ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO
(Either (FileError TextEnvelopeError) SomeExtendedVerificationKey)
-> ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey)
-> IO
(Either (FileError TextEnvelopeError) SomeExtendedVerificationKey)
-> ExceptT
(FileError TextEnvelopeError) IO SomeExtendedVerificationKey
forall a b. (a -> b) -> a -> b
$ [FromSomeType HasTextEnvelope SomeExtendedVerificationKey]
-> String
-> IO
(Either (FileError TextEnvelopeError) SomeExtendedVerificationKey)
forall b.
[FromSomeType HasTextEnvelope b]
-> String -> IO (Either (FileError TextEnvelopeError) b)
readFileTextEnvelopeAnyOf [FromSomeType HasTextEnvelope SomeExtendedVerificationKey]
fileTypes String
evkfile
where
fileTypes :: [FromSomeType HasTextEnvelope SomeExtendedVerificationKey]
fileTypes =
[ AsType (VerificationKey PaymentExtendedKey)
-> (VerificationKey PaymentExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType PaymentExtendedKey
-> AsType (VerificationKey PaymentExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType PaymentExtendedKey
AsPaymentExtendedKey)
VerificationKey PaymentExtendedKey -> SomeExtendedVerificationKey
APaymentExtendedVerificationKey
, AsType (VerificationKey StakeExtendedKey)
-> (VerificationKey StakeExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType StakeExtendedKey
-> AsType (VerificationKey StakeExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType StakeExtendedKey
AsStakeExtendedKey)
VerificationKey StakeExtendedKey -> SomeExtendedVerificationKey
AStakeExtendedVerificationKey
, AsType (VerificationKey GenesisExtendedKey)
-> (VerificationKey GenesisExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisExtendedKey
-> AsType (VerificationKey GenesisExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType GenesisExtendedKey
AsGenesisExtendedKey)
VerificationKey GenesisExtendedKey -> SomeExtendedVerificationKey
AGenesisExtendedVerificationKey
, AsType (VerificationKey GenesisDelegateExtendedKey)
-> (VerificationKey GenesisDelegateExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisDelegateExtendedKey
-> AsType (VerificationKey GenesisDelegateExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType GenesisDelegateExtendedKey
AsGenesisDelegateExtendedKey)
VerificationKey GenesisDelegateExtendedKey
-> SomeExtendedVerificationKey
AGenesisDelegateExtendedVerificationKey
, AsType (VerificationKey GenesisVestedExtendedKey)
-> (VerificationKey GenesisVestedExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisVestedExtendedKey
-> AsType (VerificationKey GenesisVestedExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType GenesisVestedExtendedKey
AsGenesisVestedExtendedKey)
VerificationKey GenesisVestedExtendedKey
-> SomeExtendedVerificationKey
AGenesisVestedExtendedVerificationKey
, AsType (VerificationKey GenesisVestedDelegateExtendedKey)
-> (VerificationKey GenesisVestedDelegateExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType GenesisVestedDelegateExtendedKey
-> AsType (VerificationKey GenesisVestedDelegateExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType GenesisVestedDelegateExtendedKey
AsGenesisVestedDelegateExtendedKey)
VerificationKey GenesisVestedDelegateExtendedKey
-> SomeExtendedVerificationKey
AGenesisVestedDelegateExtendedVerificationKey
, AsType (VerificationKey VestedExtendedKey)
-> (VerificationKey VestedExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VestedExtendedKey
-> AsType (VerificationKey VestedExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType VestedExtendedKey
AsVestedExtendedKey)
VerificationKey VestedExtendedKey -> SomeExtendedVerificationKey
AVestedExtendedVerificationKey
, AsType (VerificationKey VestedDelegateExtendedKey)
-> (VerificationKey VestedDelegateExtendedKey
-> SomeExtendedVerificationKey)
-> FromSomeType HasTextEnvelope SomeExtendedVerificationKey
forall (c :: * -> Constraint) a b.
c a =>
AsType a -> (a -> b) -> FromSomeType c b
FromSomeType (AsType VestedDelegateExtendedKey
-> AsType (VerificationKey VestedDelegateExtendedKey)
forall a. AsType a -> AsType (VerificationKey a)
AsVerificationKey AsType VestedDelegateExtendedKey
AsVestedDelegateExtendedKey)
VerificationKey VestedDelegateExtendedKey
-> SomeExtendedVerificationKey
AVestedDelegateExtendedVerificationKey
]
runConvertColeKey
:: Maybe Text
-> ColeKeyType
-> SomeKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
runConvertColeKey :: Maybe Text
-> ColeKeyType
-> SomeKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
runConvertColeKey Maybe Text
mPwd (ColePaymentKey ColeKeyFormat
format) (ASigningKeyFile SigningKeyFile
skeyPathOld) =
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey ColeKey)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey Maybe Text
mPwd ColeKeyFormat
format SigningKey -> SigningKey ColeKey
convert SigningKeyFile
skeyPathOld
where
convert :: Cole.SigningKey -> SigningKey ColeKey
convert :: SigningKey -> SigningKey ColeKey
convert = SigningKey -> SigningKey ColeKey
ColeSigningKey
runConvertColeKey Maybe Text
mPwd (ColeGenesisKey ColeKeyFormat
format) (ASigningKeyFile SigningKeyFile
skeyPathOld) =
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey GenesisExtendedKey)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey Maybe Text
mPwd ColeKeyFormat
format SigningKey -> SigningKey GenesisExtendedKey
convert SigningKeyFile
skeyPathOld
where
convert :: Cole.SigningKey -> SigningKey GenesisExtendedKey
convert :: SigningKey -> SigningKey GenesisExtendedKey
convert (Cole.SigningKey XPrv
xsk) = XPrv -> SigningKey GenesisExtendedKey
GenesisExtendedSigningKey XPrv
xsk
runConvertColeKey Maybe Text
mPwd (ColeGenesisVestedKey ColeKeyFormat
format) (ASigningKeyFile SigningKeyFile
skeyPathOld) =
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey GenesisVestedExtendedKey)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey Maybe Text
mPwd ColeKeyFormat
format SigningKey -> SigningKey GenesisVestedExtendedKey
convert SigningKeyFile
skeyPathOld
where
convert :: Cole.SigningKey -> SigningKey GenesisVestedExtendedKey
convert :: SigningKey -> SigningKey GenesisVestedExtendedKey
convert (Cole.SigningKey XPrv
xsk) = XPrv -> SigningKey GenesisVestedExtendedKey
GenesisVestedExtendedSigningKey XPrv
xsk
runConvertColeKey Maybe Text
mPwd (ColeVestedKey ColeKeyFormat
format) (ASigningKeyFile SigningKeyFile
skeyPathOld) =
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey VestedExtendedKey)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey Maybe Text
mPwd ColeKeyFormat
format SigningKey -> SigningKey VestedExtendedKey
convert SigningKeyFile
skeyPathOld
where
convert :: Cole.SigningKey -> SigningKey VestedExtendedKey
convert :: SigningKey -> SigningKey VestedExtendedKey
convert (Cole.SigningKey XPrv
xsk) = XPrv -> SigningKey VestedExtendedKey
VestedExtendedSigningKey XPrv
xsk
runConvertColeKey Maybe Text
mPwd (ColeDelegateKey ColeKeyFormat
format) (ASigningKeyFile SigningKeyFile
skeyPathOld) =
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey GenesisDelegateExtendedKey)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey Maybe Text
mPwd ColeKeyFormat
format SigningKey -> SigningKey GenesisDelegateExtendedKey
convert SigningKeyFile
skeyPathOld
where
convert :: Cole.SigningKey -> SigningKey GenesisDelegateExtendedKey
convert :: SigningKey -> SigningKey GenesisDelegateExtendedKey
convert (Cole.SigningKey XPrv
xsk) = XPrv -> SigningKey GenesisDelegateExtendedKey
GenesisDelegateExtendedSigningKey XPrv
xsk
runConvertColeKey Maybe Text
mPwd (ColeVestedDelegateKey ColeKeyFormat
format) (ASigningKeyFile SigningKeyFile
skeyPathOld) =
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey VestedDelegateExtendedKey)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey Maybe Text
mPwd ColeKeyFormat
format SigningKey -> SigningKey VestedDelegateExtendedKey
convert SigningKeyFile
skeyPathOld
where
convert :: Cole.SigningKey -> SigningKey VestedDelegateExtendedKey
convert :: SigningKey -> SigningKey VestedDelegateExtendedKey
convert (Cole.SigningKey XPrv
xsk) = XPrv -> SigningKey VestedDelegateExtendedKey
VestedDelegateExtendedSigningKey XPrv
xsk
runConvertColeKey Maybe Text
_ (ColePaymentKey ColeKeyFormat
NonLegacyColeKeyFormat)
(AVerificationKeyFile VerificationKeyFile
vkeyPathOld) =
(VerificationKey -> VerificationKey ColeKey)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey VerificationKey -> VerificationKey ColeKey
convert VerificationKeyFile
vkeyPathOld
where
convert :: Cole.VerificationKey -> VerificationKey ColeKey
convert :: VerificationKey -> VerificationKey ColeKey
convert = VerificationKey -> VerificationKey ColeKey
ColeVerificationKey
runConvertColeKey Maybe Text
_ (ColeGenesisKey ColeKeyFormat
NonLegacyColeKeyFormat)
(AVerificationKeyFile VerificationKeyFile
vkeyPathOld) =
(VerificationKey -> VerificationKey GenesisExtendedKey)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey VerificationKey -> VerificationKey GenesisExtendedKey
convert VerificationKeyFile
vkeyPathOld
where
convert :: Cole.VerificationKey -> VerificationKey GenesisExtendedKey
convert :: VerificationKey -> VerificationKey GenesisExtendedKey
convert (Cole.VerificationKey XPub
xvk) = XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey XPub
xvk
runConvertColeKey Maybe Text
_ (ColeGenesisVestedKey ColeKeyFormat
NonLegacyColeKeyFormat)
(AVerificationKeyFile VerificationKeyFile
vkeyPathOld) =
(VerificationKey -> VerificationKey GenesisVestedExtendedKey)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey VerificationKey -> VerificationKey GenesisVestedExtendedKey
convert VerificationKeyFile
vkeyPathOld
where
convert :: Cole.VerificationKey -> VerificationKey GenesisVestedExtendedKey
convert :: VerificationKey -> VerificationKey GenesisVestedExtendedKey
convert (Cole.VerificationKey XPub
xvk) = XPub -> VerificationKey GenesisVestedExtendedKey
GenesisVestedExtendedVerificationKey XPub
xvk
runConvertColeKey Maybe Text
_ (ColeVestedKey ColeKeyFormat
NonLegacyColeKeyFormat)
(AVerificationKeyFile VerificationKeyFile
vkeyPathOld) =
(VerificationKey -> VerificationKey VestedExtendedKey)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey VerificationKey -> VerificationKey VestedExtendedKey
convert VerificationKeyFile
vkeyPathOld
where
convert :: Cole.VerificationKey -> VerificationKey VestedExtendedKey
convert :: VerificationKey -> VerificationKey VestedExtendedKey
convert (Cole.VerificationKey XPub
xvk) = XPub -> VerificationKey VestedExtendedKey
VestedExtendedVerificationKey XPub
xvk
runConvertColeKey Maybe Text
_ (ColeDelegateKey ColeKeyFormat
NonLegacyColeKeyFormat)
(AVerificationKeyFile VerificationKeyFile
vkeyPathOld) =
(VerificationKey -> VerificationKey GenesisDelegateExtendedKey)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey VerificationKey -> VerificationKey GenesisDelegateExtendedKey
convert VerificationKeyFile
vkeyPathOld
where
convert :: Cole.VerificationKey
-> VerificationKey GenesisDelegateExtendedKey
convert :: VerificationKey -> VerificationKey GenesisDelegateExtendedKey
convert (Cole.VerificationKey XPub
xvk) =
XPub -> VerificationKey GenesisDelegateExtendedKey
GenesisDelegateExtendedVerificationKey XPub
xvk
runConvertColeKey Maybe Text
_ (ColeVestedDelegateKey ColeKeyFormat
NonLegacyColeKeyFormat)
(AVerificationKeyFile VerificationKeyFile
vkeyPathOld) =
(VerificationKey -> VerificationKey VestedDelegateExtendedKey)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
forall keyrole.
Key keyrole =>
(VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey VerificationKey -> VerificationKey VestedDelegateExtendedKey
convert VerificationKeyFile
vkeyPathOld
where
convert :: Cole.VerificationKey
-> VerificationKey VestedDelegateExtendedKey
convert :: VerificationKey -> VerificationKey VestedDelegateExtendedKey
convert (Cole.VerificationKey XPub
xvk) =
XPub -> VerificationKey VestedDelegateExtendedKey
VestedDelegateExtendedVerificationKey XPub
xvk
runConvertColeKey Maybe Text
_ (ColePaymentKey ColeKeyFormat
LegacyColeKeyFormat)
AVerificationKeyFile{} =
ExceptT SophieKeyCmdError IO ()
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
forall a b. a -> b -> a
const ExceptT SophieKeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
runConvertColeKey Maybe Text
_ (ColeGenesisKey ColeKeyFormat
LegacyColeKeyFormat)
AVerificationKeyFile{} =
ExceptT SophieKeyCmdError IO ()
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
forall a b. a -> b -> a
const ExceptT SophieKeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
runConvertColeKey Maybe Text
_ (ColeGenesisVestedKey ColeKeyFormat
LegacyColeKeyFormat)
AVerificationKeyFile{} =
ExceptT SophieKeyCmdError IO ()
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
forall a b. a -> b -> a
const ExceptT SophieKeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
runConvertColeKey Maybe Text
_ (ColeVestedKey ColeKeyFormat
LegacyColeKeyFormat)
AVerificationKeyFile{} =
ExceptT SophieKeyCmdError IO ()
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
forall a b. a -> b -> a
const ExceptT SophieKeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
runConvertColeKey Maybe Text
_ (ColeDelegateKey ColeKeyFormat
LegacyColeKeyFormat)
AVerificationKeyFile{} =
ExceptT SophieKeyCmdError IO ()
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
forall a b. a -> b -> a
const ExceptT SophieKeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
runConvertColeKey Maybe Text
_ (ColeVestedDelegateKey ColeKeyFormat
LegacyColeKeyFormat)
AVerificationKeyFile{} =
ExceptT SophieKeyCmdError IO ()
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
forall a b. a -> b -> a
const ExceptT SophieKeyCmdError IO ()
forall e a. ExceptT e IO a
legacyVerificationKeysNotSupported
legacyVerificationKeysNotSupported :: ExceptT e IO a
legacyVerificationKeysNotSupported :: ExceptT e IO a
legacyVerificationKeysNotSupported =
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
String -> IO ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"convert keys: cole legacy format not supported for "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"verification keys. Convert the signing key and then get the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"verification key."
IO a
forall a. IO a
exitFailure
convertColeSigningKey
:: forall keyrole.
Key keyrole
=> Maybe Text
-> ColeKeyFormat
-> (Cole.SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey :: Maybe Text
-> ColeKeyFormat
-> (SigningKey -> SigningKey keyrole)
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeSigningKey Maybe Text
mPwd ColeKeyFormat
coleFormat SigningKey -> SigningKey keyrole
convert
SigningKeyFile
skeyPathOld
(OutputFile String
skeyPathNew) = do
SomeColeSigningKey
sKey <- (ColeKeyFailure -> SophieKeyCmdError)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT SophieKeyCmdError IO SomeColeSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> SophieKeyCmdError
SophieKeyCmdColeKeyFailure
(ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT SophieKeyCmdError IO SomeColeSigningKey)
-> ExceptT ColeKeyFailure IO SomeColeSigningKey
-> ExceptT SophieKeyCmdError IO SomeColeSigningKey
forall a b. (a -> b) -> a -> b
$ ColeKeyFormat
-> SigningKeyFile -> ExceptT ColeKeyFailure IO SomeColeSigningKey
Cole.readColeSigningKey ColeKeyFormat
coleFormat SigningKeyFile
skeyPathOld
SigningKey
unprotectedSk <- case SomeColeSigningKey
sKey of
ColeApi.AColeSigningKeyLegacy (ColeSigningKeyLegacy sk@(Crypto.SigningKey xprv)) ->
case Maybe Text
mPwd of
Just Text
pwd -> SigningKey -> ExceptT SophieKeyCmdError IO SigningKey
forall (m :: * -> *) a. Monad m => a -> m a
return (SigningKey -> ExceptT SophieKeyCmdError IO SigningKey)
-> (XPrv -> SigningKey)
-> XPrv
-> ExceptT SophieKeyCmdError IO SigningKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. XPrv -> SigningKey
Crypto.SigningKey
(XPrv -> ExceptT SophieKeyCmdError IO SigningKey)
-> XPrv -> ExceptT SophieKeyCmdError 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
encodeUtf8 Text
pwd) (Text -> ByteString
encodeUtf8 Text
"") XPrv
xprv
Maybe Text
Nothing -> SigningKey -> ExceptT SophieKeyCmdError IO SigningKey
forall (m :: * -> *) a. Monad m => a -> m a
return SigningKey
sk
ColeApi.AColeSigningKey (ColeSigningKey sk) -> SigningKey -> ExceptT SophieKeyCmdError IO SigningKey
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 () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError 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
skeyPathNew Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey keyrole
sk'
convertColeVerificationKey
:: forall keyrole.
Key keyrole
=> (Cole.VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey :: (VerificationKey -> VerificationKey keyrole)
-> VerificationKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
convertColeVerificationKey VerificationKey -> VerificationKey keyrole
convert
(VerificationKeyFile String
vkeyPathOld)
(OutputFile String
vkeyPathNew) = do
VerificationKey
vk <- (ColeKeyFailure -> SophieKeyCmdError)
-> ExceptT ColeKeyFailure IO VerificationKey
-> ExceptT SophieKeyCmdError IO VerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ColeKeyFailure -> SophieKeyCmdError
SophieKeyCmdColeKeyFailure (ExceptT ColeKeyFailure IO VerificationKey
-> ExceptT SophieKeyCmdError IO VerificationKey)
-> ExceptT ColeKeyFailure IO VerificationKey
-> ExceptT SophieKeyCmdError IO VerificationKey
forall a b. (a -> b) -> a -> b
$
VerificationKeyFile -> ExceptT ColeKeyFailure IO VerificationKey
Cole.readPaymentVerificationKey (String -> VerificationKeyFile
Cole.VerificationKeyFile String
vkeyPathOld)
let vk' :: VerificationKey keyrole
vk' :: VerificationKey keyrole
vk' = VerificationKey -> VerificationKey keyrole
convert VerificationKey
vk
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError 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
vkeyPathNew Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey keyrole
vk'
runConvertColeGenesisVerificationKey
:: VerificationKeyBase64
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
runConvertColeGenesisVerificationKey :: VerificationKeyBase64
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertColeGenesisVerificationKey (VerificationKeyBase64 String
b64ColeVKey)
(OutputFile String
vkeyPathNew) = do
VerificationKey
vk <- (VerificationKeyParseError -> SophieKeyCmdError)
-> ExceptT VerificationKeyParseError IO VerificationKey
-> ExceptT SophieKeyCmdError IO VerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (Text -> SophieKeyCmdError
SophieKeyCmdColeKeyParseError (Text -> SophieKeyCmdError)
-> (VerificationKeyParseError -> Text)
-> VerificationKeyParseError
-> SophieKeyCmdError
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. VerificationKeyParseError -> Text
forall a b. (Show a, ConvertText String b) => a -> b
show)
(ExceptT VerificationKeyParseError IO VerificationKey
-> ExceptT SophieKeyCmdError IO VerificationKey)
-> (String -> ExceptT VerificationKeyParseError IO VerificationKey)
-> String
-> ExceptT SophieKeyCmdError IO VerificationKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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)
-> (String -> Either VerificationKeyParseError VerificationKey)
-> String
-> ExceptT VerificationKeyParseError IO VerificationKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> Either VerificationKeyParseError VerificationKey
Cole.Crypto.parseFullVerificationKey
(Text -> Either VerificationKeyParseError VerificationKey)
-> (String -> Text)
-> String
-> Either VerificationKeyParseError VerificationKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Text
Text.pack
(String -> ExceptT SophieKeyCmdError IO VerificationKey)
-> String -> ExceptT SophieKeyCmdError IO VerificationKey
forall a b. (a -> b) -> a -> b
$ String
b64ColeVKey
let vk' :: VerificationKey GenesisKey
vk' :: VerificationKey GenesisKey
vk' = VerificationKey -> VerificationKey GenesisKey
convert VerificationKey
vk
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
String
-> Maybe TextEnvelopeDescr
-> VerificationKey GenesisKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
vkeyPathNew Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey GenesisKey
vk'
where
convert :: Cole.VerificationKey -> VerificationKey GenesisKey
convert :: VerificationKey -> VerificationKey GenesisKey
convert (Cole.VerificationKey XPub
xvk) =
VerificationKey GenesisExtendedKey -> VerificationKey GenesisKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey (XPub -> VerificationKey GenesisExtendedKey
GenesisExtendedVerificationKey XPub
xvk)
runConvertColeVestedVerificationKey
:: VerificationKeyBase64
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
runConvertColeVestedVerificationKey :: VerificationKeyBase64
-> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertColeVestedVerificationKey (VerificationKeyBase64 String
b64ColeVKey)
(OutputFile String
vkeyPathNew) = do
VerificationKey
vk <- (VerificationKeyParseError -> SophieKeyCmdError)
-> ExceptT VerificationKeyParseError IO VerificationKey
-> ExceptT SophieKeyCmdError IO VerificationKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (Text -> SophieKeyCmdError
SophieKeyCmdColeKeyParseError (Text -> SophieKeyCmdError)
-> (VerificationKeyParseError -> Text)
-> VerificationKeyParseError
-> SophieKeyCmdError
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. VerificationKeyParseError -> Text
forall a b. (Show a, ConvertText String b) => a -> b
show)
(ExceptT VerificationKeyParseError IO VerificationKey
-> ExceptT SophieKeyCmdError IO VerificationKey)
-> (String -> ExceptT VerificationKeyParseError IO VerificationKey)
-> String
-> ExceptT SophieKeyCmdError IO VerificationKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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)
-> (String -> Either VerificationKeyParseError VerificationKey)
-> String
-> ExceptT VerificationKeyParseError IO VerificationKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> Either VerificationKeyParseError VerificationKey
Cole.Crypto.parseFullVerificationKey
(Text -> Either VerificationKeyParseError VerificationKey)
-> (String -> Text)
-> String
-> Either VerificationKeyParseError VerificationKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Text
Text.pack
(String -> ExceptT SophieKeyCmdError IO VerificationKey)
-> String -> ExceptT SophieKeyCmdError IO VerificationKey
forall a b. (a -> b) -> a -> b
$ String
b64ColeVKey
let vk' :: VerificationKey VestedKey
vk' :: VerificationKey VestedKey
vk' = VerificationKey -> VerificationKey VestedKey
convert VerificationKey
vk
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
String
-> Maybe TextEnvelopeDescr
-> VerificationKey VestedKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
vkeyPathNew Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey VestedKey
vk'
where
convert :: Cole.VerificationKey -> VerificationKey VestedKey
convert :: VerificationKey -> VerificationKey VestedKey
convert (Cole.VerificationKey XPub
xvk) =
VerificationKey VestedExtendedKey -> VerificationKey VestedKey
forall keyroleA keyroleB.
CastVerificationKeyRole keyroleA keyroleB =>
VerificationKey keyroleA -> VerificationKey keyroleB
castVerificationKey (XPub -> VerificationKey VestedExtendedKey
VestedExtendedVerificationKey XPub
xvk)
runConvertITNStakeKey
:: SomeKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
runConvertITNStakeKey :: SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNStakeKey (AVerificationKeyFile (VerificationKeyFile String
vk)) (OutputFile String
outFile) = do
Text
bech32publicKey <- (ItnKeyConversionError -> SophieKeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$
String -> IO (Either ItnKeyConversionError Text)
readFileITNKey String
vk
VerificationKey StakeKey
vkey <- Either SophieKeyCmdError (VerificationKey StakeKey)
-> ExceptT SophieKeyCmdError IO (VerificationKey StakeKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither
(Either SophieKeyCmdError (VerificationKey StakeKey)
-> ExceptT SophieKeyCmdError IO (VerificationKey StakeKey))
-> (Either ItnKeyConversionError (VerificationKey StakeKey)
-> Either SophieKeyCmdError (VerificationKey StakeKey))
-> Either ItnKeyConversionError (VerificationKey StakeKey)
-> ExceptT SophieKeyCmdError IO (VerificationKey StakeKey)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ItnKeyConversionError -> SophieKeyCmdError)
-> Either ItnKeyConversionError (VerificationKey StakeKey)
-> Either SophieKeyCmdError (VerificationKey StakeKey)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError
(Either ItnKeyConversionError (VerificationKey StakeKey)
-> ExceptT SophieKeyCmdError IO (VerificationKey StakeKey))
-> Either ItnKeyConversionError (VerificationKey StakeKey)
-> ExceptT SophieKeyCmdError IO (VerificationKey StakeKey)
forall a b. (a -> b) -> a -> b
$ Text -> Either ItnKeyConversionError (VerificationKey StakeKey)
convertITNVerificationKey Text
bech32publicKey
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
String
-> Maybe TextEnvelopeDescr
-> VerificationKey StakeKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VerificationKey StakeKey
vkey
runConvertITNStakeKey (ASigningKeyFile (SigningKeyFile String
sk)) (OutputFile String
outFile) = do
Text
bech32privateKey <- (ItnKeyConversionError -> SophieKeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$
String -> IO (Either ItnKeyConversionError Text)
readFileITNKey String
sk
SigningKey StakeKey
skey <- Either SophieKeyCmdError (SigningKey StakeKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither
(Either SophieKeyCmdError (SigningKey StakeKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeKey))
-> (Either ItnKeyConversionError (SigningKey StakeKey)
-> Either SophieKeyCmdError (SigningKey StakeKey))
-> Either ItnKeyConversionError (SigningKey StakeKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeKey)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ItnKeyConversionError -> SophieKeyCmdError)
-> Either ItnKeyConversionError (SigningKey StakeKey)
-> Either SophieKeyCmdError (SigningKey StakeKey)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError
(Either ItnKeyConversionError (SigningKey StakeKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeKey))
-> Either ItnKeyConversionError (SigningKey StakeKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeKey)
forall a b. (a -> b) -> a -> b
$ Text -> Either ItnKeyConversionError (SigningKey StakeKey)
convertITNSigningKey Text
bech32privateKey
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$
String
-> Maybe TextEnvelopeDescr
-> SigningKey StakeKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeKey
skey
runConvertITNExtendedToStakeKey :: SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNExtendedToStakeKey :: SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNExtendedToStakeKey (AVerificationKeyFile VerificationKeyFile
_) OutputFile
_ = SophieKeyCmdError -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left SophieKeyCmdError
SophieKeyCmdWrongKeyTypeError
runConvertITNExtendedToStakeKey (ASigningKeyFile (SigningKeyFile String
sk)) (OutputFile String
outFile) = do
Text
bech32privateKey <- (ItnKeyConversionError -> SophieKeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$ String -> IO (Either ItnKeyConversionError Text)
readFileITNKey String
sk
SigningKey StakeExtendedKey
skey <- Either SophieKeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either SophieKeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey))
-> (Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either SophieKeyCmdError (SigningKey StakeExtendedKey))
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ItnKeyConversionError -> SophieKeyCmdError)
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either SophieKeyCmdError (SigningKey StakeExtendedKey)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError
(Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey))
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNExtendedSigningKey Text
bech32privateKey
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$ String
-> Maybe TextEnvelopeDescr
-> SigningKey StakeExtendedKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeExtendedKey
skey
runConvertITNBip32ToStakeKey :: SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNBip32ToStakeKey :: SomeKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertITNBip32ToStakeKey (AVerificationKeyFile VerificationKeyFile
_) OutputFile
_ = SophieKeyCmdError -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left SophieKeyCmdError
SophieKeyCmdWrongKeyTypeError
runConvertITNBip32ToStakeKey (ASigningKeyFile (SigningKeyFile String
sk)) (OutputFile String
outFile) = do
Text
bech32privateKey <- (ItnKeyConversionError -> SophieKeyCmdError)
-> ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError (ExceptT ItnKeyConversionError IO Text
-> ExceptT SophieKeyCmdError IO Text)
-> (IO (Either ItnKeyConversionError Text)
-> ExceptT ItnKeyConversionError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO Text)
-> IO (Either ItnKeyConversionError Text)
-> ExceptT SophieKeyCmdError IO Text
forall a b. (a -> b) -> a -> b
$ String -> IO (Either ItnKeyConversionError Text)
readFileITNKey String
sk
SigningKey StakeExtendedKey
skey <- Either SophieKeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey)
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either SophieKeyCmdError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey))
-> (Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either SophieKeyCmdError (SigningKey StakeExtendedKey))
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ItnKeyConversionError -> SophieKeyCmdError)
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> Either SophieKeyCmdError (SigningKey StakeExtendedKey)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ItnKeyConversionError -> SophieKeyCmdError
SophieKeyCmdItnKeyConvError
(Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey))
-> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
-> ExceptT SophieKeyCmdError IO (SigningKey StakeExtendedKey)
forall a b. (a -> b) -> a -> b
$ Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNBIP32SigningKey Text
bech32privateKey
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$ String
-> Maybe TextEnvelopeDescr
-> SigningKey StakeExtendedKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeExtendedKey
skey
data ItnKeyConversionError
= ItnKeyBech32DecodeError !Bech32DecodeError
| ItnReadBech32FileError !FilePath !IOException
| ItnSigningKeyDeserialisationError !ByteString
| ItnVerificationKeyDeserialisationError !ByteString
deriving Int -> ItnKeyConversionError -> ShowS
[ItnKeyConversionError] -> ShowS
ItnKeyConversionError -> String
(Int -> ItnKeyConversionError -> ShowS)
-> (ItnKeyConversionError -> String)
-> ([ItnKeyConversionError] -> ShowS)
-> Show ItnKeyConversionError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ItnKeyConversionError] -> ShowS
$cshowList :: [ItnKeyConversionError] -> ShowS
show :: ItnKeyConversionError -> String
$cshow :: ItnKeyConversionError -> String
showsPrec :: Int -> ItnKeyConversionError -> ShowS
$cshowsPrec :: Int -> ItnKeyConversionError -> ShowS
Show
renderConversionError :: ItnKeyConversionError -> Text
renderConversionError :: ItnKeyConversionError -> Text
renderConversionError ItnKeyConversionError
err =
case ItnKeyConversionError
err of
ItnKeyBech32DecodeError Bech32DecodeError
decErr ->
Text
"Error decoding Bech32 key: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (Bech32DecodeError -> String
forall e. Error e => e -> String
displayError Bech32DecodeError
decErr)
ItnReadBech32FileError String
fp IOException
readErr ->
Text
"Error reading Bech32 key at: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
forall a. Show a => a -> Text
textShow String
fp
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" Error: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (IOException -> String
forall e. Exception e => e -> String
displayException IOException
readErr)
ItnSigningKeyDeserialisationError ByteString
_sKey ->
Text
"Error deserialising signing key."
ItnVerificationKeyDeserialisationError ByteString
vKey ->
Text
"Error deserialising verification key: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
forall a. Show a => a -> Text
textShow (ByteString -> String
BSC.unpack ByteString
vKey)
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 (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 k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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) crypto.
VerKeyDSIGN (DSIGN crypto) -> VKey kd crypto
Sophie.VKey VerKeyDSIGN (DSIGN StandardCrypto)
VerKeyDSIGN Ed25519DSIGN
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 (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 StandardCrypto
SignKeyDSIGN Ed25519DSIGN
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 (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 (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 :: String -> IO (Either ItnKeyConversionError Text)
readFileITNKey String
fp = do
Either IOException Text
eStr <- IO Text -> IO (Either IOException Text)
forall e a. Exception e => IO a -> IO (Either e a)
Exception.try (IO Text -> IO (Either IOException Text))
-> IO Text -> IO (Either IOException Text)
forall a b. (a -> b) -> a -> b
$ String -> IO Text
readFile String
fp
case Either IOException Text
eStr of
Left IOException
e -> Either ItnKeyConversionError Text
-> IO (Either ItnKeyConversionError Text)
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 k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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
$ String -> IOException -> ItnKeyConversionError
ItnReadBech32FileError String
fp IOException
e
Right Text
str -> Either ItnKeyConversionError Text
-> IO (Either ItnKeyConversionError Text)
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 k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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
str
runConvertBccAddressSigningKey
:: BccAddressKeyType
-> SigningKeyFile
-> OutputFile
-> ExceptT SophieKeyCmdError IO ()
runConvertBccAddressSigningKey :: BccAddressKeyType
-> SigningKeyFile -> OutputFile -> ExceptT SophieKeyCmdError IO ()
runConvertBccAddressSigningKey BccAddressKeyType
keyType SigningKeyFile
skFile (OutputFile String
outFile) = do
SomeBccAddressSigningKey
sKey <- (FileError BccAddressSigningKeyConversionError
-> SophieKeyCmdError)
-> ExceptT
(FileError BccAddressSigningKeyConversionError)
IO
SomeBccAddressSigningKey
-> ExceptT SophieKeyCmdError IO SomeBccAddressSigningKey
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError BccAddressSigningKeyConversionError -> SophieKeyCmdError
SophieKeyCmdBccAddressSigningKeyFileError
(ExceptT
(FileError BccAddressSigningKeyConversionError)
IO
SomeBccAddressSigningKey
-> ExceptT SophieKeyCmdError IO SomeBccAddressSigningKey)
-> (IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
-> ExceptT
(FileError BccAddressSigningKeyConversionError)
IO
SomeBccAddressSigningKey)
-> IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
-> ExceptT SophieKeyCmdError IO SomeBccAddressSigningKey
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
-> ExceptT
(FileError BccAddressSigningKeyConversionError)
IO
SomeBccAddressSigningKey
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT
(IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
-> ExceptT SophieKeyCmdError IO SomeBccAddressSigningKey)
-> IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
-> ExceptT SophieKeyCmdError IO SomeBccAddressSigningKey
forall a b. (a -> b) -> a -> b
$ BccAddressKeyType
-> SigningKeyFile
-> IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
readSomeBccAddressSigningKeyFile BccAddressKeyType
keyType SigningKeyFile
skFile
(FileError () -> SophieKeyCmdError)
-> ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> SophieKeyCmdError
SophieKeyCmdWriteFileError (ExceptT (FileError ()) IO () -> ExceptT SophieKeyCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT SophieKeyCmdError IO ()
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat 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 SophieKeyCmdError IO ())
-> IO (Either (FileError ()) ()) -> ExceptT SophieKeyCmdError IO ()
forall a b. (a -> b) -> a -> b
$ String -> SomeBccAddressSigningKey -> IO (Either (FileError ()) ())
writeSomeBccAddressSigningKeyFile String
outFile SomeBccAddressSigningKey
sKey
data SomeBccAddressSigningKey
= ABccAddrSophiePaymentSigningKey !(SigningKey PaymentExtendedKey)
| ABccAddrSophieStakeSigningKey !(SigningKey StakeExtendedKey)
| ABccAddrColeSigningKey !(SigningKey ColeKey)
data BccAddressSigningKeyConversionError
= BccAddressSigningKeyBech32DecodeError !Bech32DecodeError
| BccAddressSigningKeyDeserialisationError !ByteString
deriving (Int -> BccAddressSigningKeyConversionError -> ShowS
[BccAddressSigningKeyConversionError] -> ShowS
BccAddressSigningKeyConversionError -> String
(Int -> BccAddressSigningKeyConversionError -> ShowS)
-> (BccAddressSigningKeyConversionError -> String)
-> ([BccAddressSigningKeyConversionError] -> ShowS)
-> Show BccAddressSigningKeyConversionError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BccAddressSigningKeyConversionError] -> ShowS
$cshowList :: [BccAddressSigningKeyConversionError] -> ShowS
show :: BccAddressSigningKeyConversionError -> String
$cshow :: BccAddressSigningKeyConversionError -> String
showsPrec :: Int -> BccAddressSigningKeyConversionError -> ShowS
$cshowsPrec :: Int -> BccAddressSigningKeyConversionError -> ShowS
Show, BccAddressSigningKeyConversionError
-> BccAddressSigningKeyConversionError -> Bool
(BccAddressSigningKeyConversionError
-> BccAddressSigningKeyConversionError -> Bool)
-> (BccAddressSigningKeyConversionError
-> BccAddressSigningKeyConversionError -> Bool)
-> Eq BccAddressSigningKeyConversionError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BccAddressSigningKeyConversionError
-> BccAddressSigningKeyConversionError -> Bool
$c/= :: BccAddressSigningKeyConversionError
-> BccAddressSigningKeyConversionError -> Bool
== :: BccAddressSigningKeyConversionError
-> BccAddressSigningKeyConversionError -> Bool
$c== :: BccAddressSigningKeyConversionError
-> BccAddressSigningKeyConversionError -> Bool
Eq)
instance Error BccAddressSigningKeyConversionError where
displayError :: BccAddressSigningKeyConversionError -> String
displayError = Text -> String
Text.unpack (Text -> String)
-> (BccAddressSigningKeyConversionError -> Text)
-> BccAddressSigningKeyConversionError
-> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. BccAddressSigningKeyConversionError -> Text
renderBccAddressSigningKeyConversionError
renderBccAddressSigningKeyConversionError
:: BccAddressSigningKeyConversionError
-> Text
renderBccAddressSigningKeyConversionError :: BccAddressSigningKeyConversionError -> Text
renderBccAddressSigningKeyConversionError BccAddressSigningKeyConversionError
err =
case BccAddressSigningKeyConversionError
err of
BccAddressSigningKeyBech32DecodeError Bech32DecodeError
decErr ->
String -> Text
Text.pack (Bech32DecodeError -> String
forall e. Error e => e -> String
displayError Bech32DecodeError
decErr)
BccAddressSigningKeyDeserialisationError ByteString
_bs ->
Text
"Error deserialising bcc-address signing key."
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 BccAddressSigningKeyConversionError Crypto.XPrv
convertBip32SigningKey :: ByteString -> Either BccAddressSigningKeyConversionError XPrv
convertBip32SigningKey ByteString
signingKeyBs =
case ByteString -> Maybe XPrv
xPrvFromBytes ByteString
signingKeyBs of
Just XPrv
xPrv -> XPrv -> Either BccAddressSigningKeyConversionError XPrv
forall a b. b -> Either a b
Right XPrv
xPrv
Maybe XPrv
Nothing ->
BccAddressSigningKeyConversionError
-> Either BccAddressSigningKeyConversionError XPrv
forall a b. a -> Either a b
Left (BccAddressSigningKeyConversionError
-> Either BccAddressSigningKeyConversionError XPrv)
-> BccAddressSigningKeyConversionError
-> Either BccAddressSigningKeyConversionError XPrv
forall a b. (a -> b) -> a -> b
$ ByteString -> BccAddressSigningKeyConversionError
BccAddressSigningKeyDeserialisationError ByteString
signingKeyBs
readBech32Bip32SigningKeyFile
:: SigningKeyFile
-> IO (Either (FileError BccAddressSigningKeyConversionError) Crypto.XPrv)
readBech32Bip32SigningKeyFile :: SigningKeyFile
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
readBech32Bip32SigningKeyFile (SigningKeyFile String
fp) = do
Either IOException Text
eStr <- IO Text -> IO (Either IOException Text)
forall e a. Exception e => IO a -> IO (Either e a)
Exception.try (IO Text -> IO (Either IOException Text))
-> IO Text -> IO (Either IOException Text)
forall a b. (a -> b) -> a -> b
$ String -> IO Text
readFile String
fp
case Either IOException Text
eStr of
Left IOException
e -> Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError BccAddressSigningKeyConversionError) XPrv))
-> (FileError BccAddressSigningKeyConversionError
-> Either (FileError BccAddressSigningKeyConversionError) XPrv)
-> FileError BccAddressSigningKeyConversionError
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. FileError BccAddressSigningKeyConversionError
-> Either (FileError BccAddressSigningKeyConversionError) XPrv
forall a b. a -> Either a b
Left (FileError BccAddressSigningKeyConversionError
-> IO
(Either (FileError BccAddressSigningKeyConversionError) XPrv))
-> FileError BccAddressSigningKeyConversionError
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
forall a b. (a -> b) -> a -> b
$ String
-> IOException -> FileError BccAddressSigningKeyConversionError
forall e. String -> IOException -> FileError e
FileIOError String
fp IOException
e
Right Text
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
str) of
Left Bech32DecodeError
err ->
Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError BccAddressSigningKeyConversionError) XPrv))
-> Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
forall a b. (a -> b) -> a -> b
$ FileError BccAddressSigningKeyConversionError
-> Either (FileError BccAddressSigningKeyConversionError) XPrv
forall a b. a -> Either a b
Left (FileError BccAddressSigningKeyConversionError
-> Either (FileError BccAddressSigningKeyConversionError) XPrv)
-> FileError BccAddressSigningKeyConversionError
-> Either (FileError BccAddressSigningKeyConversionError) XPrv
forall a b. (a -> b) -> a -> b
$
String
-> BccAddressSigningKeyConversionError
-> FileError BccAddressSigningKeyConversionError
forall e. String -> e -> FileError e
FileError String
fp (Bech32DecodeError -> BccAddressSigningKeyConversionError
BccAddressSigningKeyBech32DecodeError Bech32DecodeError
err)
Right (HumanReadablePart
_hrPart, DataPart
_dataPart, ByteString
bs) ->
Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO
(Either (FileError BccAddressSigningKeyConversionError) XPrv))
-> Either (FileError BccAddressSigningKeyConversionError) XPrv
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
forall a b. (a -> b) -> a -> b
$ (BccAddressSigningKeyConversionError
-> FileError BccAddressSigningKeyConversionError)
-> Either BccAddressSigningKeyConversionError XPrv
-> Either (FileError BccAddressSigningKeyConversionError) XPrv
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String
-> BccAddressSigningKeyConversionError
-> FileError BccAddressSigningKeyConversionError
forall e. String -> e -> FileError e
FileError String
fp) (ByteString -> Either BccAddressSigningKeyConversionError XPrv
convertBip32SigningKey ByteString
bs)
readSomeBccAddressSigningKeyFile
:: BccAddressKeyType
-> SigningKeyFile
-> IO (Either (FileError BccAddressSigningKeyConversionError) SomeBccAddressSigningKey)
readSomeBccAddressSigningKeyFile :: BccAddressKeyType
-> SigningKeyFile
-> IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
readSomeBccAddressSigningKeyFile BccAddressKeyType
keyType SigningKeyFile
skFile = do
Either (FileError BccAddressSigningKeyConversionError) XPrv
xPrv <- SigningKeyFile
-> IO (Either (FileError BccAddressSigningKeyConversionError) XPrv)
readBech32Bip32SigningKeyFile SigningKeyFile
skFile
Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey
-> IO
(Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (XPrv -> SomeBccAddressSigningKey
toSomeBccAddressSigningKey (XPrv -> SomeBccAddressSigningKey)
-> Either (FileError BccAddressSigningKeyConversionError) XPrv
-> Either
(FileError BccAddressSigningKeyConversionError)
SomeBccAddressSigningKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either (FileError BccAddressSigningKeyConversionError) XPrv
xPrv)
where
toSomeBccAddressSigningKey :: Crypto.XPrv -> SomeBccAddressSigningKey
toSomeBccAddressSigningKey :: XPrv -> SomeBccAddressSigningKey
toSomeBccAddressSigningKey XPrv
xPrv =
case BccAddressKeyType
keyType of
BccAddressKeyType
BccAddressSophiePaymentKey ->
SigningKey PaymentExtendedKey -> SomeBccAddressSigningKey
ABccAddrSophiePaymentSigningKey
(XPrv -> SigningKey PaymentExtendedKey
PaymentExtendedSigningKey XPrv
xPrv)
BccAddressKeyType
BccAddressSophieStakeKey ->
SigningKey StakeExtendedKey -> SomeBccAddressSigningKey
ABccAddrSophieStakeSigningKey (XPrv -> SigningKey StakeExtendedKey
StakeExtendedSigningKey XPrv
xPrv)
BccAddressKeyType
BccAddressIcarusPaymentKey ->
SigningKey ColeKey -> SomeBccAddressSigningKey
ABccAddrColeSigningKey (SigningKey ColeKey -> SomeBccAddressSigningKey)
-> SigningKey ColeKey -> SomeBccAddressSigningKey
forall a b. (a -> b) -> a -> b
$
SigningKey -> SigningKey ColeKey
ColeSigningKey (XPrv -> SigningKey
Cole.SigningKey XPrv
xPrv)
BccAddressKeyType
BccAddressColePaymentKey ->
SigningKey ColeKey -> SomeBccAddressSigningKey
ABccAddrColeSigningKey (SigningKey ColeKey -> SomeBccAddressSigningKey)
-> SigningKey ColeKey -> SomeBccAddressSigningKey
forall a b. (a -> b) -> a -> b
$
SigningKey -> SigningKey ColeKey
ColeSigningKey (XPrv -> SigningKey
Cole.SigningKey XPrv
xPrv)
writeSomeBccAddressSigningKeyFile
:: FilePath
-> SomeBccAddressSigningKey
-> IO (Either (FileError ()) ())
writeSomeBccAddressSigningKeyFile :: String -> SomeBccAddressSigningKey -> IO (Either (FileError ()) ())
writeSomeBccAddressSigningKeyFile String
outFile SomeBccAddressSigningKey
skey =
case SomeBccAddressSigningKey
skey of
ABccAddrSophiePaymentSigningKey SigningKey PaymentExtendedKey
sk ->
String
-> Maybe TextEnvelopeDescr
-> SigningKey PaymentExtendedKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey PaymentExtendedKey
sk
ABccAddrSophieStakeSigningKey SigningKey StakeExtendedKey
sk ->
String
-> Maybe TextEnvelopeDescr
-> SigningKey StakeExtendedKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey StakeExtendedKey
sk
ABccAddrColeSigningKey SigningKey ColeKey
sk ->
String
-> Maybe TextEnvelopeDescr
-> SigningKey ColeKey
-> IO (Either (FileError ()) ())
forall a.
HasTextEnvelope a =>
String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing SigningKey ColeKey
sk