Skip to content

Commit

Permalink
Do not throw exception when looking for policy public key
Browse files Browse the repository at this point in the history
Delegate that task to callers
  • Loading branch information
abailly committed Dec 18, 2024
1 parent eab1d67 commit 3af10dd
Show file tree
Hide file tree
Showing 3 changed files with 34 additions and 28 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -44,9 +44,6 @@ import Control.Category
import Control.Monad.IO.Class
( MonadIO (liftIO)
)
import Control.Monad.Trans.Except
( runExceptT
)
import Data.Either.Extra
( eitherToMaybe
)
Expand All @@ -62,7 +59,7 @@ convertApiAssetMintBurn
-> Handler (ApiAssetMintBurn, ApiAssetMintBurn)
convertApiAssetMintBurn ctx (mint, burn) = do
xpubM <- fmap (fmap fst . eitherToMaybe)
<$> liftIO . runExceptT $ readPolicyPublicKey ctx
<$> liftIO $ readPolicyPublicKey ctx
let convert tokenWithScripts = ApiAssetMintBurn
{ tokens = toApiTokens tokenWithScripts
, walletPolicyKeyHash =
Expand Down
26 changes: 16 additions & 10 deletions lib/api/src/Cardano/Wallet/Api/Http/Shelley/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2632,10 +2632,7 @@ constructTransaction api knownPools poolStatus apiWalletId body = do
transactionCtx0 { txDelegationAction = Just action }

policyXPubM <-
if isJust mintBurnDatum || isJust mintBurnReferenceScriptTemplate then
liftHandler $ Just . fst <$> W.readPolicyPublicKey wrk
else
pure Nothing
fmap fst . eitherToMaybe <$> liftIO (W.readPolicyPublicKey wrk)

transactionCtx2 <-
if isJust mintBurnDatum then do
Expand Down Expand Up @@ -3434,8 +3431,18 @@ decodeTransaction
let ApiDecodeTransactionPostData (ApiT sealed) decryptMetadata = postData
era <- liftIO $ NW.currentNodeEra netLayer
withWorkerCtx ctx wid liftE liftE $ \wrk -> do
(k, _) <- liftHandler $ W.readPolicyPublicKey wrk
let keyhash = KeyHash Policy (xpubToBytes k)
policyKeyM <-
fmap fst . eitherToMaybe <$> liftIO (W.readPolicyPublicKey wrk)
let txWitnessCount =
mkApiWitnessCount
. witnessCount
$ maybe
AnyWitnessCountCtx
( ShelleyWalletCtx
. KeyHash Policy
. xpubToBytes
)
policyKeyM
TxExtended{..} = decodeTx tl era sealed
Tx { txId
, fee
Expand Down Expand Up @@ -3492,8 +3499,7 @@ decodeTransaction
, metadata = ApiTxMetadata metadata'
, scriptValidity = ApiT <$> scriptValidity
, validityInterval = ApiValidityIntervalExplicit <$> validity
, witnessCount = mkApiWitnessCount $ witnessCount
$ ShelleyWalletCtx keyhash
, witnessCount = txWitnessCount
}
where
tl = ctx ^. W.transactionLayer @(KeyOf s) @'CredFromKeyK
Expand Down Expand Up @@ -4425,7 +4431,7 @@ getPolicyKey
-> Handler ApiPolicyKey
getPolicyKey ctx (ApiT wid) hashed = do
withWorkerCtx @_ @s ctx wid liftE liftE $ \wrk -> do
(k, _) <- liftHandler $ W.readPolicyPublicKey wrk
(k, _) <- liftHandler $ ExceptT $ W.readPolicyPublicKey wrk
pure $ uncurry ApiPolicyKey (computeKeyPayload hashed k)

postPolicyKey
Expand Down Expand Up @@ -4468,7 +4474,7 @@ postPolicyId ctx (ApiT wid) payload = do
liftHandler $ throwE ErrGetPolicyIdWrongMintingBurningTemplate

withWorkerCtx @_ @s ctx wid liftE liftE $ \wrk -> do
(xpub, _) <- liftHandler $ W.readPolicyPublicKey wrk
(xpub, _) <- liftHandler $ ExceptT $ W.readPolicyPublicKey wrk
pure $ ApiPolicyId $ ApiT $
toTokenPolicyId (keyFlavorFromState @s)
scriptTempl (Map.singleton (Cosigner 0) xpub)
Expand Down
31 changes: 17 additions & 14 deletions lib/wallet/src/Cardano/Wallet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1670,20 +1670,23 @@ readPolicyPublicKey
:: forall s
. WalletFlavor s
=> WalletLayer IO s
-> ExceptT ErrReadPolicyPublicKey IO (XPub, NonEmpty DerivationIndex)
readPolicyPublicKey ctx = db & \DBLayer{..} -> do
cp <- lift $ atomically readCheckpoint
case walletFlavor @s of
ShelleyWallet -> do
let s = getState cp
case Seq.policyXPub s of
Nothing -> throwE ErrReadPolicyPublicKeyAbsent
Just xpub -> pure
( getRawKey (keyFlavorFromState @s) xpub
, policyDerivationPath
)
_ ->
throwE ErrReadPolicyPublicKeyNotAShelleyWallet
-> IO (Either ErrReadPolicyPublicKey (XPub, NonEmpty DerivationIndex))
readPolicyPublicKey ctx =
db & \DBLayer{..} -> do
cp <- atomically readCheckpoint
case walletFlavor @s of
ShelleyWallet -> do
let s = getState cp
case Seq.policyXPub s of
Nothing -> pure $ Left ErrReadPolicyPublicKeyAbsent
Just xpub ->
pure
$ Right
( getRawKey (keyFlavorFromState @s) xpub
, policyDerivationPath
)
_ ->
pure $ Left ErrReadPolicyPublicKeyNotAShelleyWallet
where
db = ctx ^. dbLayer

Expand Down

0 comments on commit 3af10dd

Please sign in to comment.