Skip to content

Commit efd5358

Browse files
author
gege251
committed
Allow the use of verificiation keys to build tx with required signers
1 parent 427d71a commit efd5358

File tree

4 files changed

+108
-48
lines changed

4 files changed

+108
-48
lines changed

src/BotPlutusInterface/CardanoCLI.hs

Lines changed: 38 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -16,16 +16,17 @@ module BotPlutusInterface.CardanoCLI (
1616
queryTip,
1717
) where
1818

19-
import BotPlutusInterface.Effects (PABEffect, ShellArgs (..), callCommand, uploadDir)
19+
import BotPlutusInterface.Effects (PABEffect, ShellArgs (..), callCommand, printLog, uploadDir)
2020
import BotPlutusInterface.Files (
21+
DummyPrivKey (FromSKey, FromVKey),
2122
datumJsonFilePath,
2223
policyScriptFilePath,
2324
redeemerJsonFilePath,
2425
signingKeyFilePath,
2526
txFilePath,
2627
validatorScriptFilePath,
2728
)
28-
import BotPlutusInterface.Types (PABConfig, Tip)
29+
import BotPlutusInterface.Types (LogLevel (Warn), PABConfig, Tip)
2930
import BotPlutusInterface.UtxoParser qualified as UtxoParser
3031
import Cardano.Api.Shelley (NetworkId (Mainnet, Testnet), NetworkMagic (..), serialiseAddress)
3132
import Codec.Serialise qualified as Codec
@@ -53,7 +54,7 @@ import Ledger (Slot (Slot), SlotRange)
5354
import Ledger qualified
5455
import Ledger.Ada qualified as Ada
5556
import Ledger.Address (Address (..))
56-
import Ledger.Crypto (PubKey, PubKeyHash)
57+
import Ledger.Crypto (PubKey, PubKeyHash (getPubKeyHash))
5758
import Ledger.Interval (
5859
Extended (Finite),
5960
Interval (Interval),
@@ -197,17 +198,24 @@ buildTx ::
197198
forall (w :: Type) (effs :: [Type -> Type]).
198199
Member (PABEffect w) effs =>
199200
PABConfig ->
201+
Map PubKeyHash DummyPrivKey ->
200202
PubKeyHash ->
201203
BuildMode ->
202204
Tx ->
203205
Eff effs ()
204-
buildTx pabConf ownPkh buildMode tx =
206+
buildTx pabConf privKeys ownPkh buildMode tx =
205207
callCommand @w $ ShellArgs "cardano-cli" opts (const ())
206208
where
207209
ownAddr = Ledger.pubKeyHashAddress (Ledger.PaymentPubKeyHash ownPkh) Nothing
210+
skeys = Map.filter (\case FromSKey _ -> True; FromVKey _ -> False) privKeys
208211
requiredSigners =
209212
concatMap
210-
(\pubKey -> ["--required-signer", signingKeyFilePath pabConf (Ledger.pubKeyHash pubKey)])
213+
( \pubKey ->
214+
let pkh = Ledger.pubKeyHash pubKey
215+
in if Map.member pkh skeys
216+
then ["--required-signer", signingKeyFilePath pabConf pkh]
217+
else ["--required-signer-hash", encodeByteString $ fromBuiltin $ getPubKeyHash pkh]
218+
)
211219
(Map.keys (Ledger.txSignatures tx))
212220
opts =
213221
mconcat
@@ -236,27 +244,39 @@ signTx ::
236244
forall (w :: Type) (effs :: [Type -> Type]).
237245
Member (PABEffect w) effs =>
238246
PABConfig ->
247+
Map PubKeyHash DummyPrivKey ->
239248
Tx ->
240249
[PubKey] ->
241-
Eff effs ()
242-
signTx pabConf tx pubKeys =
243-
callCommand @w $
244-
ShellArgs
245-
"cardano-cli"
246-
( mconcat
247-
[ ["transaction", "sign"]
248-
, ["--tx-body-file", txFilePath pabConf "raw" tx]
249-
, signingKeyFiles
250-
, ["--out-file", txFilePath pabConf "signed" tx]
251-
]
252-
)
253-
(const ())
250+
Eff effs (Either Text ())
251+
signTx pabConf privKeys tx pubKeys =
252+
let skeys = Map.filter (\case FromSKey _ -> True; FromVKey _ -> False) privKeys
253+
in if all ((`Map.member` skeys) . Ledger.pubKeyHash) pubKeys
254+
then callCommand @w $ ShellArgs "cardano-cli" opts (const (Right ()))
255+
else do
256+
let err =
257+
Text.unlines
258+
[ "Not all required signatures have signing key files. Please sign and submit the tx manually:"
259+
, "Tx file: " <> txFilePath pabConf "raw" tx
260+
, "Signatories (pkh): "
261+
<> Text.unwords
262+
(map (encodeByteString . fromBuiltin . getPubKeyHash . Ledger.pubKeyHash) pubKeys)
263+
]
264+
printLog @w Warn (Text.unpack err)
265+
pure $ Left err
254266
where
255267
signingKeyFiles =
256268
concatMap
257269
(\pubKey -> ["--signing-key-file", signingKeyFilePath pabConf (Ledger.pubKeyHash pubKey)])
258270
pubKeys
259271

272+
opts =
273+
mconcat
274+
[ ["transaction", "sign"]
275+
, ["--tx-body-file", txFilePath pabConf "raw" tx]
276+
, signingKeyFiles
277+
, ["--out-file", txFilePath pabConf "signed" tx]
278+
]
279+
260280
-- Signs and writes a tx (uses the tx body written to disk as input)
261281
submitTx ::
262282
forall (w :: Type) (effs :: [Type -> Type]).

src/BotPlutusInterface/Contract.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ import Control.Monad.Freer.Extras.Modify (raiseEnd)
2424
import Control.Monad.Freer.Writer (Writer (Tell))
2525
import Data.Aeson (ToJSON, Value)
2626
import Data.Default (Default (def))
27+
import Data.Either (isRight)
2728
import Data.Kind (Type)
2829
import Data.Map qualified as Map
2930
import Data.Row (Row)
@@ -200,14 +201,15 @@ writeBalancedTx contractEnv (Right tx) = do
200201
Right _ -> do
201202
let ownPkh = contractEnv.cePABConfig.pcOwnPubKeyHash
202203
let requiredSigners = Map.keys $ tx ^. Tx.signatures
204+
privKeys <- either (error . Text.unpack) id <$> Files.readPrivateKeys @w contractEnv.cePABConfig
203205

204206
CardanoCLI.uploadFiles @w contractEnv.cePABConfig
205207

206-
CardanoCLI.buildTx @w contractEnv.cePABConfig ownPkh CardanoCLI.BuildAuto tx
207-
CardanoCLI.signTx @w contractEnv.cePABConfig tx requiredSigners
208+
CardanoCLI.buildTx @w contractEnv.cePABConfig privKeys ownPkh CardanoCLI.BuildAuto tx
209+
res <- CardanoCLI.signTx @w contractEnv.cePABConfig privKeys tx requiredSigners
208210

209211
result <-
210-
if contractEnv.cePABConfig.pcDryRun
212+
if contractEnv.cePABConfig.pcDryRun || isRight res
211213
then pure Nothing
212214
else CardanoCLI.submitTx @w contractEnv.cePABConfig tx
213215

src/BotPlutusInterface/Files.hs

Lines changed: 57 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -2,18 +2,19 @@
22

33
module BotPlutusInterface.Files (
44
policyScriptFilePath,
5+
DummyPrivKey (FromSKey, FromVKey),
56
validatorScriptFilePath,
67
readPrivateKeys,
78
signingKeyFilePath,
89
txFilePath,
9-
readPrivateKey,
1010
writeAll,
1111
writePolicyScriptFile,
1212
redeemerJsonFilePath,
13+
mkDummyPrivateKey,
1314
writeRedeemerJsonFile,
1415
writeValidatorScriptFile,
1516
datumJsonFilePath,
16-
fromCardanoPaymentKey,
17+
skeyToDummyPrivKey,
1718
writeDatumJsonFile,
1819
) where
1920

@@ -27,8 +28,9 @@ import BotPlutusInterface.Effects (
2728
)
2829
import BotPlutusInterface.Types (PABConfig)
2930
import Cardano.Api (
30-
AsType (AsPaymentKey, AsSigningKey),
31+
AsType (AsPaymentKey, AsSigningKey, AsVerificationKey),
3132
FileError,
33+
Key (VerificationKey),
3234
PaymentKey,
3335
SigningKey,
3436
getVerificationKey,
@@ -58,7 +60,7 @@ import Data.Set qualified as Set
5860
import Data.Text (Text)
5961
import Data.Text qualified as Text
6062
import Ledger qualified
61-
import Ledger.Crypto (PrivateKey, PubKeyHash (PubKeyHash))
63+
import Ledger.Crypto (PrivateKey, PubKey (PubKey), PubKeyHash (PubKeyHash))
6264
import Ledger.Tx (Tx)
6365
import Ledger.Tx qualified as Tx
6466
import Ledger.TxId qualified as TxId
@@ -67,12 +69,14 @@ import Plutus.V1.Ledger.Api (
6769
CurrencySymbol,
6870
Datum (getDatum),
6971
DatumHash (..),
72+
LedgerBytes (LedgerBytes),
7073
MintingPolicy,
7174
Redeemer (getRedeemer),
7275
RedeemerHash (..),
7376
Script,
7477
Validator,
7578
ValidatorHash (..),
79+
toBuiltin,
7680
)
7781
import PlutusTx (ToData, toData)
7882
import PlutusTx.Builtins (fromBuiltin)
@@ -167,50 +171,82 @@ readPrivateKeys ::
167171
forall (w :: Type) (effs :: [Type -> Type]).
168172
Member (PABEffect w) effs =>
169173
PABConfig ->
170-
Eff effs (Either Text (Map PubKeyHash PrivateKey))
174+
Eff effs (Either Text (Map PubKeyHash DummyPrivKey))
171175
readPrivateKeys pabConf = do
172176
files <- listDirectory @w $ Text.unpack pabConf.pcSigningKeyFileDir
173177
let sKeyFiles =
174178
map (\filename -> Text.unpack pabConf.pcSigningKeyFileDir ++ "/" ++ filename) $
175179
filter ("skey" `isExtensionOf`) files
176-
privKeys <- mapM (readPrivateKey @w) sKeyFiles
177-
pure $ toPrivKeyMap <$> sequence privKeys
180+
let vKeyFiles =
181+
map (\filename -> Text.unpack pabConf.pcSigningKeyFileDir ++ "/" ++ filename) $
182+
filter ("vkey" `isExtensionOf`) files
183+
privKeys <- mapM (readSigningKey @w) sKeyFiles
184+
privKeys' <- mapM (readVerificationKey @w) vKeyFiles
185+
pure $ toPrivKeyMap <$> sequence (privKeys <> privKeys')
178186
where
179-
toPrivKeyMap :: [PrivateKey] -> Map PubKeyHash PrivateKey
187+
toPrivKeyMap :: [DummyPrivKey] -> Map PubKeyHash DummyPrivKey
180188
toPrivKeyMap =
181189
foldl
182190
( \pKeyMap pKey ->
183-
let pkh = Ledger.pubKeyHash $ Ledger.toPublicKey pKey
191+
let pkh = Ledger.pubKeyHash $ Ledger.toPublicKey $ unDummyPrivateKey pKey
184192
in Map.insert pkh pKey pKeyMap
185193
)
186194
Map.empty
187195

188-
readPrivateKey ::
196+
data DummyPrivKey
197+
= FromSKey PrivateKey
198+
| FromVKey PrivateKey
199+
200+
unDummyPrivateKey :: DummyPrivKey -> PrivateKey
201+
unDummyPrivateKey (FromSKey key) = key
202+
unDummyPrivateKey (FromVKey key) = key
203+
204+
readSigningKey ::
189205
forall (w :: Type) (effs :: [Type -> Type]).
190206
Member (PABEffect w) effs =>
191207
FilePath ->
192-
Eff effs (Either Text PrivateKey)
193-
readPrivateKey filePath = do
208+
Eff effs (Either Text DummyPrivKey)
209+
readSigningKey filePath = do
194210
pKey <- mapLeft (Text.pack . show) <$> readFileTextEnvelope @w (AsSigningKey AsPaymentKey) filePath
195-
pure $ fromCardanoPaymentKey =<< pKey
211+
pure $ skeyToDummyPrivKey =<< pKey
212+
213+
readVerificationKey ::
214+
forall (w :: Type) (effs :: [Type -> Type]).
215+
Member (PABEffect w) effs =>
216+
FilePath ->
217+
Eff effs (Either Text DummyPrivKey)
218+
readVerificationKey filePath = do
219+
pKey <- mapLeft (Text.pack . show) <$> readFileTextEnvelope @w (AsVerificationKey AsPaymentKey) filePath
220+
pure $ vkeyToDummyPrivKey =<< pKey
221+
222+
vkeyToDummyPrivKey :: VerificationKey PaymentKey -> Either Text DummyPrivKey
223+
vkeyToDummyPrivKey =
224+
fmap FromVKey . vkeyToDummyPrivKey'
225+
226+
skeyToDummyPrivKey :: SigningKey PaymentKey -> Either Text DummyPrivKey
227+
skeyToDummyPrivKey =
228+
fmap FromSKey . vkeyToDummyPrivKey' . getVerificationKey
196229

197230
{- | Warning! This implementation is not correct!
198231
This private key is derived from a normal signing key which uses a 32 byte private key compared
199232
to the extended key which is 64 bytes. Also, the extended key includes a chain index value
200233
201-
This keys sole purpose is to be able to derive a public key from it, which is then used for
234+
This key's sole purpose is to be able to derive a public key from it, which is then used for
202235
mapping to a signing key file for the CLI
203236
-}
204-
fromCardanoPaymentKey :: SigningKey PaymentKey -> Either Text PrivateKey
205-
fromCardanoPaymentKey sKey =
206-
let dummyPrivKeySuffix = ByteString.replicate 32 0
237+
vkeyToDummyPrivKey' :: VerificationKey PaymentKey -> Either Text PrivateKey
238+
vkeyToDummyPrivKey' =
239+
mkDummyPrivateKey . PubKey . LedgerBytes . toBuiltin . serialiseToRawBytes
240+
241+
mkDummyPrivateKey :: PubKey -> Either Text PrivateKey
242+
mkDummyPrivateKey (PubKey (LedgerBytes pubkey)) =
243+
let dummyPrivKey = ByteString.replicate 32 0
244+
dummyPrivKeySuffix = ByteString.replicate 32 0
207245
dummyChainCode = ByteString.replicate 32 1
208-
vKey = getVerificationKey sKey
209-
privkeyBS = serialiseToRawBytes sKey
210-
pubkeyBS = serialiseToRawBytes vKey
246+
pubkeyBS = fromBuiltin pubkey
211247
in mapLeft Text.pack $
212248
Crypto.xprv $
213-
mconcat [privkeyBS, dummyPrivKeySuffix, pubkeyBS, dummyChainCode]
249+
mconcat [dummyPrivKey, dummyPrivKeySuffix, pubkeyBS, dummyChainCode]
214250

215251
serialiseScript :: Script -> PlutusScript PlutusScriptV1
216252
serialiseScript =

src/BotPlutusInterface/PreBalance.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module BotPlutusInterface.PreBalance (
77

88
import BotPlutusInterface.CardanoCLI qualified as CardanoCLI
99
import BotPlutusInterface.Effects (PABEffect, createDirectoryIfMissing, printLog)
10+
import BotPlutusInterface.Files (DummyPrivKey (FromSKey, FromVKey))
1011
import BotPlutusInterface.Files qualified as Files
1112
import BotPlutusInterface.Types (LogLevel (Debug), PABConfig)
1213
import Cardano.Api.Shelley (Lovelace (Lovelace), ProtocolParameters (protocolParamUTxOCostPerWord))
@@ -29,7 +30,7 @@ import Ledger qualified
2930
import Ledger.Ada qualified as Ada
3031
import Ledger.Address (Address (..))
3132
import Ledger.Constraints.OffChain (UnbalancedTx (..), fromScriptOutput)
32-
import Ledger.Crypto (PrivateKey, PubKeyHash)
33+
import Ledger.Crypto (PubKeyHash)
3334
import Ledger.Interval (
3435
Extended (Finite, NegInf, PosInf),
3536
Interval (Interval),
@@ -86,7 +87,7 @@ preBalanceTxIO pabConf ownPkh unbalancedTx =
8687
where
8788
loop ::
8889
Map TxOutRef TxOut ->
89-
Map PubKeyHash PrivateKey ->
90+
Map PubKeyHash DummyPrivKey ->
9091
[PubKeyHash] ->
9192
[(TxOut, Integer)] ->
9293
Tx ->
@@ -105,7 +106,7 @@ preBalanceTxIO pabConf ownPkh unbalancedTx =
105106
hoistEither $ preBalanceTx pabConf.pcProtocolParams minUtxos 0 utxoIndex ownPkh privKeys requiredSigs tx
106107

107108
lift $ createDirectoryIfMissing @w False (Text.unpack pabConf.pcTxFileDir)
108-
lift $ CardanoCLI.buildTx @w pabConf ownPkh (CardanoCLI.BuildRaw 0) txWithoutFees
109+
lift $ CardanoCLI.buildTx @w pabConf privKeys ownPkh (CardanoCLI.BuildRaw 0) txWithoutFees
109110
fees <- newEitherT $ CardanoCLI.calculateMinFee @w pabConf txWithoutFees
110111

111112
lift $ printLog @w Debug $ "Fees: " ++ show fees
@@ -132,7 +133,7 @@ preBalanceTx ::
132133
Integer ->
133134
Map TxOutRef TxOut ->
134135
PubKeyHash ->
135-
Map PubKeyHash PrivateKey ->
136+
Map PubKeyHash DummyPrivKey ->
136137
[PubKeyHash] ->
137138
Tx ->
138139
Either Text Tx
@@ -261,12 +262,13 @@ balanceNonAdaOuts ownPkh utxos tx =
261262
{- | Add the required signatorioes to the transaction. Be aware the the signature itself is invalid,
262263
and will be ignored. Only the pub key hashes are used, mapped to signing key files on disk.
263264
-}
264-
addSignatories :: PubKeyHash -> Map PubKeyHash PrivateKey -> [PubKeyHash] -> Tx -> Either Text Tx
265+
addSignatories :: PubKeyHash -> Map PubKeyHash DummyPrivKey -> [PubKeyHash] -> Tx -> Either Text Tx
265266
addSignatories ownPkh privKeys pkhs tx =
266267
foldM
267268
( \tx' pkh ->
268269
case Map.lookup pkh privKeys of
269-
Just privKey -> Right $ Tx.addSignature' privKey tx'
270+
Just (FromSKey privKey) -> Right $ Tx.addSignature' privKey tx'
271+
Just (FromVKey privKey) -> Right $ Tx.addSignature' privKey tx'
270272
Nothing -> Left "Signing key not found."
271273
)
272274
tx

0 commit comments

Comments
 (0)