diff --git a/src/BotPlutusInterface/CardanoCLI.hs b/src/BotPlutusInterface/CardanoCLI.hs index 3a932cc5..1b376574 100644 --- a/src/BotPlutusInterface/CardanoCLI.hs +++ b/src/BotPlutusInterface/CardanoCLI.hs @@ -16,8 +16,9 @@ module BotPlutusInterface.CardanoCLI ( queryTip, ) where -import BotPlutusInterface.Effects (PABEffect, ShellArgs (..), callCommand, uploadDir) +import BotPlutusInterface.Effects (PABEffect, ShellArgs (..), callCommand, printLog, uploadDir) import BotPlutusInterface.Files ( + DummyPrivKey (FromSKey, FromVKey), datumJsonFilePath, policyScriptFilePath, redeemerJsonFilePath, @@ -25,7 +26,7 @@ import BotPlutusInterface.Files ( txFilePath, validatorScriptFilePath, ) -import BotPlutusInterface.Types (PABConfig, Tip) +import BotPlutusInterface.Types (LogLevel (Warn), PABConfig, Tip) import BotPlutusInterface.UtxoParser qualified as UtxoParser import Cardano.Api.Shelley (NetworkId (Mainnet, Testnet), NetworkMagic (..), serialiseAddress) import Codec.Serialise qualified as Codec @@ -54,7 +55,7 @@ import Ledger (Slot (Slot), SlotRange) import Ledger qualified import Ledger.Ada qualified as Ada import Ledger.Address (Address (..)) -import Ledger.Crypto (PubKey, PubKeyHash) +import Ledger.Crypto (PubKey, PubKeyHash (getPubKeyHash)) import Ledger.Interval ( Extended (Finite), Interval (Interval), @@ -198,17 +199,27 @@ buildTx :: forall (w :: Type) (effs :: [Type -> Type]). Member (PABEffect w) effs => PABConfig -> + Map PubKeyHash DummyPrivKey -> PubKeyHash -> BuildMode -> Tx -> Eff effs () -buildTx pabConf ownPkh buildMode tx = +buildTx pabConf privKeys ownPkh buildMode tx = callCommand @w $ ShellArgs "cardano-cli" opts (const ()) where ownAddr = Ledger.pubKeyHashAddress (Ledger.PaymentPubKeyHash ownPkh) Nothing requiredSigners = concatMap - (\pubKey -> ["--required-signer", signingKeyFilePath pabConf (Ledger.pubKeyHash pubKey)]) + ( \pubKey -> + let pkh = Ledger.pubKeyHash pubKey + in case Map.lookup pkh privKeys of + Just (FromSKey _) -> + ["--required-signer", signingKeyFilePath pabConf pkh] + Just (FromVKey _) -> + ["--required-signer-hash", encodeByteString $ fromBuiltin $ getPubKeyHash pkh] + Nothing -> + [] + ) (Map.keys (Ledger.txSignatures tx)) opts = mconcat @@ -237,27 +248,39 @@ signTx :: forall (w :: Type) (effs :: [Type -> Type]). Member (PABEffect w) effs => PABConfig -> + Map PubKeyHash DummyPrivKey -> Tx -> [PubKey] -> - Eff effs () -signTx pabConf tx pubKeys = - callCommand @w $ - ShellArgs - "cardano-cli" - ( mconcat - [ ["transaction", "sign"] - , ["--tx-body-file", txFilePath pabConf "raw" tx] - , signingKeyFiles - , ["--out-file", txFilePath pabConf "signed" tx] - ] - ) - (const ()) + Eff effs (Either Text ()) +signTx pabConf privKeys tx pubKeys = + let skeys = Map.filter (\case FromSKey _ -> True; FromVKey _ -> False) privKeys + in if all ((`Map.member` skeys) . Ledger.pubKeyHash) pubKeys + then callCommand @w $ ShellArgs "cardano-cli" opts (const (Right ())) + else do + let err = + Text.unlines + [ "Not all required signatures have signing key files. Please sign and submit the tx manually:" + , "Tx file: " <> txFilePath pabConf "raw" tx + , "Signatories (pkh): " + <> Text.unwords + (map (encodeByteString . fromBuiltin . getPubKeyHash . Ledger.pubKeyHash) pubKeys) + ] + printLog @w Warn (Text.unpack err) + pure $ Left err where signingKeyFiles = concatMap (\pubKey -> ["--signing-key-file", signingKeyFilePath pabConf (Ledger.pubKeyHash pubKey)]) pubKeys + opts = + mconcat + [ ["transaction", "sign"] + , ["--tx-body-file", txFilePath pabConf "raw" tx] + , signingKeyFiles + , ["--out-file", txFilePath pabConf "signed" tx] + ] + -- Signs and writes a tx (uses the tx body written to disk as input) submitTx :: forall (w :: Type) (effs :: [Type -> Type]). diff --git a/src/BotPlutusInterface/Contract.hs b/src/BotPlutusInterface/Contract.hs index a3b59fd7..be551d65 100644 --- a/src/BotPlutusInterface/Contract.hs +++ b/src/BotPlutusInterface/Contract.hs @@ -23,6 +23,7 @@ import Control.Monad.Freer.Extras.Log (handleLogIgnore) import Control.Monad.Freer.Extras.Modify (raiseEnd) import Control.Monad.Freer.Writer (Writer (Tell)) import Data.Aeson (ToJSON, Value) +import Data.Either (isRight) import Data.Kind (Type) import Data.Map qualified as Map import Data.Row (Row) @@ -193,14 +194,15 @@ writeBalancedTx contractEnv (Right tx) = do Right _ -> do let ownPkh = contractEnv.cePABConfig.pcOwnPubKeyHash let requiredSigners = Map.keys $ tx ^. Tx.signatures + privKeys <- either (error . Text.unpack) id <$> Files.readPrivateKeys @w contractEnv.cePABConfig CardanoCLI.uploadFiles @w contractEnv.cePABConfig - CardanoCLI.buildTx @w contractEnv.cePABConfig ownPkh CardanoCLI.BuildAuto tx - CardanoCLI.signTx @w contractEnv.cePABConfig tx requiredSigners + CardanoCLI.buildTx @w contractEnv.cePABConfig privKeys ownPkh CardanoCLI.BuildAuto tx + res <- CardanoCLI.signTx @w contractEnv.cePABConfig privKeys tx requiredSigners result <- - if contractEnv.cePABConfig.pcDryRun + if contractEnv.cePABConfig.pcDryRun || isRight res then pure Nothing else CardanoCLI.submitTx @w contractEnv.cePABConfig tx diff --git a/src/BotPlutusInterface/Files.hs b/src/BotPlutusInterface/Files.hs index ebbdadda..1ed5a39d 100644 --- a/src/BotPlutusInterface/Files.hs +++ b/src/BotPlutusInterface/Files.hs @@ -2,18 +2,21 @@ module BotPlutusInterface.Files ( policyScriptFilePath, + DummyPrivKey (FromSKey, FromVKey), + unDummyPrivateKey, validatorScriptFilePath, readPrivateKeys, signingKeyFilePath, txFilePath, - readPrivateKey, writeAll, writePolicyScriptFile, redeemerJsonFilePath, + mkDummyPrivateKey, writeRedeemerJsonFile, writeValidatorScriptFile, datumJsonFilePath, - fromCardanoPaymentKey, + skeyToDummyPrivKey, + vkeyToDummyPrivKey, writeDatumJsonFile, ) where @@ -27,8 +30,9 @@ import BotPlutusInterface.Effects ( ) import BotPlutusInterface.Types (PABConfig) import Cardano.Api ( - AsType (AsPaymentKey, AsSigningKey), + AsType (AsPaymentKey, AsSigningKey, AsVerificationKey), FileError, + Key (VerificationKey), PaymentKey, SigningKey, getVerificationKey, @@ -51,14 +55,15 @@ import Data.ByteString.Lazy qualified as LazyByteString import Data.ByteString.Short qualified as ShortByteString import Data.Either.Combinators (mapLeft) import Data.Kind (Type) +import Data.List (sortOn) import Data.Map (Map) import Data.Map qualified as Map -import Data.Maybe (mapMaybe) +import Data.Maybe (catMaybes, mapMaybe) import Data.Set qualified as Set import Data.Text (Text) import Data.Text qualified as Text import Ledger qualified -import Ledger.Crypto (PrivateKey, PubKeyHash (PubKeyHash)) +import Ledger.Crypto (PrivateKey, PubKey (PubKey), PubKeyHash (PubKeyHash)) import Ledger.Tx (Tx) import Ledger.Tx qualified as Tx import Ledger.TxId qualified as TxId @@ -67,16 +72,18 @@ import Plutus.V1.Ledger.Api ( CurrencySymbol, Datum (getDatum), DatumHash (..), + LedgerBytes (LedgerBytes), MintingPolicy, Redeemer (getRedeemer), RedeemerHash (..), Script, Validator, ValidatorHash (..), + toBuiltin, ) import PlutusTx (ToData, toData) import PlutusTx.Builtins (fromBuiltin) -import System.FilePath (isExtensionOf) +import System.FilePath (takeExtension, ()) import Prelude -- | Filename of a minting policy script @@ -167,50 +174,92 @@ readPrivateKeys :: forall (w :: Type) (effs :: [Type -> Type]). Member (PABEffect w) effs => PABConfig -> - Eff effs (Either Text (Map PubKeyHash PrivateKey)) + Eff effs (Either Text (Map PubKeyHash DummyPrivKey)) readPrivateKeys pabConf = do files <- listDirectory @w $ Text.unpack pabConf.pcSigningKeyFileDir - let sKeyFiles = - map (\filename -> Text.unpack pabConf.pcSigningKeyFileDir ++ "/" ++ filename) $ - filter ("skey" `isExtensionOf`) files - privKeys <- mapM (readPrivateKey @w) sKeyFiles + + privKeys <- + catMaybes + <$> mapM + ( \filename -> + let fullPath = Text.unpack pabConf.pcSigningKeyFileDir filename + in case takeExtension filename of + ".vkey" -> Just <$> readVerificationKey @w fullPath + ".skey" -> Just <$> readSigningKey @w fullPath + _ -> pure Nothing + ) + files + pure $ toPrivKeyMap <$> sequence privKeys where - toPrivKeyMap :: [PrivateKey] -> Map PubKeyHash PrivateKey + toPrivKeyMap :: [DummyPrivKey] -> Map PubKeyHash DummyPrivKey toPrivKeyMap = foldl ( \pKeyMap pKey -> - let pkh = Ledger.pubKeyHash $ Ledger.toPublicKey pKey + let pkh = Ledger.pubKeyHash $ Ledger.toPublicKey $ unDummyPrivateKey pKey in Map.insert pkh pKey pKeyMap ) Map.empty + . sortOn keyPriority + + keyPriority :: DummyPrivKey -> Int + keyPriority (FromSKey _) = 1 + keyPriority (FromVKey _) = 0 -readPrivateKey :: +data DummyPrivKey + = FromSKey PrivateKey + | FromVKey PrivateKey + +unDummyPrivateKey :: DummyPrivKey -> PrivateKey +unDummyPrivateKey (FromSKey key) = key +unDummyPrivateKey (FromVKey key) = key + +readSigningKey :: forall (w :: Type) (effs :: [Type -> Type]). Member (PABEffect w) effs => FilePath -> - Eff effs (Either Text PrivateKey) -readPrivateKey filePath = do + Eff effs (Either Text DummyPrivKey) +readSigningKey filePath = do pKey <- mapLeft (Text.pack . show) <$> readFileTextEnvelope @w (AsSigningKey AsPaymentKey) filePath - pure $ fromCardanoPaymentKey =<< pKey + pure $ skeyToDummyPrivKey =<< pKey + +readVerificationKey :: + forall (w :: Type) (effs :: [Type -> Type]). + Member (PABEffect w) effs => + FilePath -> + Eff effs (Either Text DummyPrivKey) +readVerificationKey filePath = do + pKey <- mapLeft (Text.pack . show) <$> readFileTextEnvelope @w (AsVerificationKey AsPaymentKey) filePath + pure $ vkeyToDummyPrivKey =<< pKey + +vkeyToDummyPrivKey :: VerificationKey PaymentKey -> Either Text DummyPrivKey +vkeyToDummyPrivKey = + fmap FromVKey . vkeyToDummyPrivKey' + +skeyToDummyPrivKey :: SigningKey PaymentKey -> Either Text DummyPrivKey +skeyToDummyPrivKey = + fmap FromSKey . vkeyToDummyPrivKey' . getVerificationKey {- | Warning! This implementation is not correct! This private key is derived from a normal signing key which uses a 32 byte private key compared to the extended key which is 64 bytes. Also, the extended key includes a chain index value - This keys sole purpose is to be able to derive a public key from it, which is then used for + This key's sole purpose is to be able to derive a public key from it, which is then used for mapping to a signing key file for the CLI -} -fromCardanoPaymentKey :: SigningKey PaymentKey -> Either Text PrivateKey -fromCardanoPaymentKey sKey = - let dummyPrivKeySuffix = ByteString.replicate 32 0 +vkeyToDummyPrivKey' :: VerificationKey PaymentKey -> Either Text PrivateKey +vkeyToDummyPrivKey' = + mkDummyPrivateKey . PubKey . LedgerBytes . toBuiltin . serialiseToRawBytes + +mkDummyPrivateKey :: PubKey -> Either Text PrivateKey +mkDummyPrivateKey (PubKey (LedgerBytes pubkey)) = + let dummyPrivKey = ByteString.replicate 32 0 + dummyPrivKeySuffix = ByteString.replicate 32 0 dummyChainCode = ByteString.replicate 32 1 - vKey = getVerificationKey sKey - privkeyBS = serialiseToRawBytes sKey - pubkeyBS = serialiseToRawBytes vKey + pubkeyBS = fromBuiltin pubkey in mapLeft Text.pack $ Crypto.xprv $ - mconcat [privkeyBS, dummyPrivKeySuffix, pubkeyBS, dummyChainCode] + mconcat [dummyPrivKey, dummyPrivKeySuffix, pubkeyBS, dummyChainCode] serialiseScript :: Script -> PlutusScript PlutusScriptV1 serialiseScript = diff --git a/src/BotPlutusInterface/PreBalance.hs b/src/BotPlutusInterface/PreBalance.hs index 304eee60..a62e95a1 100644 --- a/src/BotPlutusInterface/PreBalance.hs +++ b/src/BotPlutusInterface/PreBalance.hs @@ -7,6 +7,7 @@ module BotPlutusInterface.PreBalance ( import BotPlutusInterface.CardanoCLI qualified as CardanoCLI import BotPlutusInterface.Effects (PABEffect, createDirectoryIfMissing, printLog) +import BotPlutusInterface.Files (DummyPrivKey, unDummyPrivateKey) import BotPlutusInterface.Files qualified as Files import BotPlutusInterface.Types (LogLevel (Debug), PABConfig) import Cardano.Api.Shelley (Lovelace (Lovelace), ProtocolParameters (protocolParamUTxOCostPerWord)) @@ -28,7 +29,7 @@ import Ledger qualified import Ledger.Ada qualified as Ada import Ledger.Address (Address (..)) import Ledger.Constraints.OffChain (UnbalancedTx (..), fromScriptOutput) -import Ledger.Crypto (PrivateKey, PubKeyHash) +import Ledger.Crypto (PubKeyHash) import Ledger.Interval ( Extended (Finite, NegInf, PosInf), Interval (Interval), @@ -86,7 +87,7 @@ preBalanceTxIO pabConf ownPkh unbalancedTx = where loop :: Map TxOutRef TxOut -> - Map PubKeyHash PrivateKey -> + Map PubKeyHash DummyPrivKey -> [PubKeyHash] -> [(TxOut, Integer)] -> Tx -> @@ -105,7 +106,7 @@ preBalanceTxIO pabConf ownPkh unbalancedTx = hoistEither $ preBalanceTx pabConf.pcProtocolParams minUtxos 0 utxoIndex ownPkh privKeys requiredSigs tx lift $ createDirectoryIfMissing @w False (Text.unpack pabConf.pcTxFileDir) - lift $ CardanoCLI.buildTx @w pabConf ownPkh (CardanoCLI.BuildRaw 0) txWithoutFees + lift $ CardanoCLI.buildTx @w pabConf privKeys ownPkh (CardanoCLI.BuildRaw 0) txWithoutFees fees <- newEitherT $ CardanoCLI.calculateMinFee @w pabConf txWithoutFees lift $ printLog @w Debug $ "Fees: " ++ show fees @@ -132,7 +133,7 @@ preBalanceTx :: Integer -> Map TxOutRef TxOut -> PubKeyHash -> - Map PubKeyHash PrivateKey -> + Map PubKeyHash DummyPrivKey -> [PubKeyHash] -> Tx -> Either Text Tx @@ -261,12 +262,12 @@ balanceNonAdaOuts ownPkh utxos tx = {- | Add the required signatorioes to the transaction. Be aware the the signature itself is invalid, and will be ignored. Only the pub key hashes are used, mapped to signing key files on disk. -} -addSignatories :: PubKeyHash -> Map PubKeyHash PrivateKey -> [PubKeyHash] -> Tx -> Either Text Tx +addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash] -> Tx -> Either Text Tx addSignatories ownPkh privKeys pkhs tx = foldM ( \tx' pkh -> case Map.lookup pkh privKeys of - Just privKey -> Right $ Tx.addSignature' privKey tx' + Just privKey -> Right $ Tx.addSignature' (unDummyPrivateKey privKey) tx' Nothing -> Left "Signing key not found." ) tx diff --git a/test/Spec/BotPlutusInterface/Contract.hs b/test/Spec/BotPlutusInterface/Contract.hs index 06d0c534..246614f7 100644 --- a/test/Spec/BotPlutusInterface/Contract.hs +++ b/test/Spec/BotPlutusInterface/Contract.hs @@ -56,8 +56,13 @@ import Spec.MockContract ( pkh3', pkhAddr1, runContractPure, + signingKey1, tip, + toSigningKeyFile, + toVerificationKeyFile, utxos, + verificationKey1, + verificationKey3, ) import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (Assertion, assertBool, assertFailure, testCase, (@?=)) @@ -74,6 +79,7 @@ tests = [ testCase "Send ada to address" sendAda , testCase "Send ada to address with staking key" sendAdaStaking , testCase "Support multiple signatories" multisigSupport + , testCase "Create a tx without signing" withoutSigning , testCase "Send native tokens" sendTokens , testCase "Send native tokens (without token name)" sendTokensWithoutName , testCase "Mint native tokens" mintTokens @@ -301,6 +307,47 @@ multisigSupport = do ) ] +withoutSigning :: Assertion +withoutSigning = do + let txOutRef = TxOutRef "e406b0cf676fc2b1a9edb0617f259ad025c20ea6f0333820aa7cef1bfe7302e5" 0 + txOut = TxOut pkhAddr1 (Ada.lovelaceValueOf 1250) Nothing + initState = + def + & utxos .~ [(txOutRef, txOut)] + & files + .~ Map.fromList + [ toSigningKeyFile "./signing-keys" signingKey1 + , toVerificationKeyFile "./signing-keys" verificationKey1 + , toVerificationKeyFile "./signing-keys" verificationKey3 + ] + inTxId = encodeByteString $ fromBuiltin $ TxId.getTxId $ Tx.txOutRefId txOutRef + + contract :: Contract Text (Endpoint "SendAda" ()) Text CardanoTx + contract = do + let constraints = + Constraints.mustPayToPubKey paymentPkh2 (Ada.lovelaceValueOf 1000) + <> Constraints.mustBeSignedBy paymentPkh3 + submitTx constraints + + -- Building and siging the tx should include both signing keys + assertContractWithTxId contract initState $ \state outTxId -> + assertCommandHistory + state + [ + ( 6 + , [text| + cardano-cli transaction build --alonzo-era + --tx-in ${inTxId}#0 + --tx-in-collateral ${inTxId}#0 + --tx-out ${addr2}+1000 + --required-signer ./signing-keys/signing-key-${pkh1'}.skey + --required-signer-hash ${pkh3'} + --change-address ${addr1} + --mainnet --protocol-params-file ./protocol.json --out-file ./txs/tx-${outTxId}.raw + |] + ) + ] + sendTokens :: Assertion sendTokens = do let txOutRef1 = TxOutRef "08b27dbdcff9ab3b432638536ec7eab36c8a2e457703fb1b559dd754032ef431" 0 diff --git a/test/Spec/BotPlutusInterface/PreBalance.hs b/test/Spec/BotPlutusInterface/PreBalance.hs index 6cc9bb58..9ff2663b 100644 --- a/test/Spec/BotPlutusInterface/PreBalance.hs +++ b/test/Spec/BotPlutusInterface/PreBalance.hs @@ -1,5 +1,6 @@ module Spec.BotPlutusInterface.PreBalance (tests) where +import BotPlutusInterface.Files (DummyPrivKey (FromSKey)) import BotPlutusInterface.PreBalance qualified as PreBalance import Cardano.Api.Shelley (Lovelace (Lovelace), ProtocolParameters (protocolParamUTxOCostPerWord)) import Data.Default (def) @@ -10,7 +11,7 @@ import Ledger.Ada qualified as Ada import Ledger.Address (Address, PaymentPubKeyHash (PaymentPubKeyHash)) import Ledger.Address qualified as Address import Ledger.CardanoWallet qualified as Wallet -import Ledger.Crypto (PrivateKey, PubKeyHash) +import Ledger.Crypto (PubKeyHash) import Ledger.Tx (Tx (..), TxIn (..), TxInType (..), TxOut (..), TxOutRef (..)) import Ledger.Value qualified as Value import Test.Tasty (TestTree, testGroup) @@ -30,8 +31,8 @@ tests = , testCase "Add utxos to cover change min utxo" addUtxosForChange ] -privateKey1 :: PrivateKey -privateKey1 = Address.unPaymentPrivateKey . Wallet.paymentPrivateKey $ Wallet.knownMockWallet 1 +privateKey1 :: DummyPrivKey +privateKey1 = FromSKey . Address.unPaymentPrivateKey . Wallet.paymentPrivateKey $ Wallet.knownMockWallet 1 pkh1, pkh2 :: PubKeyHash pkh1 = Address.unPaymentPubKeyHash . Wallet.paymentPubKeyHash $ Wallet.knownMockWallet 1 diff --git a/test/Spec/MockContract.hs b/test/Spec/MockContract.hs index a50dfd30..b934c404 100644 --- a/test/Spec/MockContract.hs +++ b/test/Spec/MockContract.hs @@ -4,12 +4,15 @@ {-# OPTIONS_GHC -Wno-orphans #-} module Spec.MockContract ( + -- Mock private and public keys etc. signingKey1, signingKey2, - runContractPure, + signingKey3, + verificationKey1, + verificationKey2, + verificationKey3, toSigningKeyFile, - runContractPure', - MockContractState (..), + toVerificationKeyFile, pubKey1, pubKey2, pubKey3, @@ -28,6 +31,10 @@ module Spec.MockContract ( pkhAddr1, pkhAddr2, pkhAddr3, + -- Test interpreter + runContractPure, + runContractPure', + MockContractState (..), commandHistory, instanceUpdateHistory, logHistory, @@ -52,6 +59,7 @@ import Cardano.Api ( AsType, FileError (FileError, FileIOError), HasTextEnvelope, + Key (VerificationKey, getVerificationKey), NetworkId (Mainnet), PaymentKey, SigningKey (PaymentSigningKey), @@ -59,6 +67,7 @@ import Cardano.Api ( TextEnvelopeDescr, TextEnvelopeError (TextEnvelopeAesonDecodeError), deserialiseFromTextEnvelope, + getVerificationKey, serialiseToTextEnvelope, ) import Cardano.Crypto.DSIGN (genKeyDSIGN) @@ -76,7 +85,7 @@ import Data.Aeson qualified as JSON import Data.Aeson.Extras (encodeByteString) import Data.ByteString qualified as ByteString import Data.Default (Default (def)) -import Data.Either.Combinators (fromRight, mapLeft) +import Data.Either.Combinators (mapLeft) import Data.Hex (hex) import Data.Kind (Type) import Data.List (isPrefixOf) @@ -115,10 +124,15 @@ signingKey1 = PaymentSigningKey $ genKeyDSIGN $ mkSeedFromBytes $ ByteString.rep signingKey2 = PaymentSigningKey $ genKeyDSIGN $ mkSeedFromBytes $ ByteString.replicate 32 1 signingKey3 = PaymentSigningKey $ genKeyDSIGN $ mkSeedFromBytes $ ByteString.replicate 32 2 +verificationKey1, verificationKey2, verificationKey3 :: VerificationKey PaymentKey +verificationKey1 = getVerificationKey signingKey1 +verificationKey2 = getVerificationKey signingKey2 +verificationKey3 = getVerificationKey signingKey3 + pubKey1, pubKey2, pubKey3 :: PubKey -pubKey1 = toPubKey signingKey1 -pubKey2 = toPubKey signingKey2 -pubKey3 = toPubKey signingKey3 +pubKey1 = skeyToPubKey signingKey1 +pubKey2 = skeyToPubKey signingKey2 +pubKey3 = skeyToPubKey signingKey3 pkh1, pkh2, pkh3 :: PubKeyHash pkh1 = Ledger.pubKeyHash pubKey1 @@ -145,15 +159,32 @@ addr1 = unsafeSerialiseAddress Mainnet (Ledger.pubKeyHashAddress paymentPkh1 Not addr2 = unsafeSerialiseAddress Mainnet (Ledger.pubKeyHashAddress paymentPkh2 Nothing) addr3 = unsafeSerialiseAddress Mainnet (Ledger.pubKeyHashAddress paymentPkh3 Nothing) -toPubKey :: SigningKey PaymentKey -> PubKey -toPubKey = Ledger.toPublicKey . fromRight (error "Impossible happened") . Files.fromCardanoPaymentKey +skeyToPubKey :: SigningKey PaymentKey -> PubKey +skeyToPubKey = + Ledger.toPublicKey + . Files.unDummyPrivateKey + . either (error . Text.unpack) id + . Files.skeyToDummyPrivKey + +vkeyToPubKey :: VerificationKey PaymentKey -> PubKey +vkeyToPubKey = + Ledger.toPublicKey + . Files.unDummyPrivateKey + . either (error . Text.unpack) id + . Files.vkeyToDummyPrivKey toSigningKeyFile :: FilePath -> SigningKey PaymentKey -> (FilePath, MockFile) toSigningKeyFile signingKeyFileDir sKey = - ( signingKeyFileDir ++ "/signing-key-" ++ show (Ledger.pubKeyHash (toPubKey sKey)) ++ ".skey" + ( signingKeyFileDir ++ "/signing-key-" ++ show (Ledger.pubKeyHash (skeyToPubKey sKey)) ++ ".skey" , TextEnvelopeFile $ serialiseToTextEnvelope Nothing sKey ) +toVerificationKeyFile :: FilePath -> VerificationKey PaymentKey -> (FilePath, MockFile) +toVerificationKeyFile signingKeyFileDir vKey = + ( signingKeyFileDir ++ "/signing-key-" ++ show (Ledger.pubKeyHash (vkeyToPubKey vKey)) ++ ".vkey" + , TextEnvelopeFile $ serialiseToTextEnvelope Nothing vKey + ) + data MockFile = TextEnvelopeFile TextEnvelope | JsonFile JSON.Value