22
33module 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 )
2829import BotPlutusInterface.Types (PABConfig )
2930import 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
5860import Data.Text (Text )
5961import Data.Text qualified as Text
6062import Ledger qualified
61- import Ledger.Crypto (PrivateKey , PubKeyHash (PubKeyHash ))
63+ import Ledger.Crypto (PrivateKey , PubKey ( PubKey ), PubKeyHash (PubKeyHash ))
6264import Ledger.Tx (Tx )
6365import Ledger.Tx qualified as Tx
6466import 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 )
7781import PlutusTx (ToData , toData )
7882import 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 ))
171175readPrivateKeys 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
215251serialiseScript :: Script -> PlutusScript PlutusScriptV1
216252serialiseScript =
0 commit comments