33{-# LANGUAGE DerivingStrategies #-}
44{-# LANGUAGE FlexibleContexts #-}
55{-# LANGUAGE GADTs #-}
6+ {-# LANGUAGE InstanceSigs #-}
67{-# LANGUAGE LambdaCase #-}
78{-# LANGUAGE NamedFieldPuns #-}
89{-# LANGUAGE ScopedTypeVariables #-}
@@ -56,6 +57,10 @@ module Cardano.Api.Certificate
5657 , Ledger. MIRPot (.. )
5758 , selectStakeCredentialWitness
5859
60+ -- * Anchor data
61+ , AnchorDataFromCertificateError (.. )
62+ , getAnchorDataFromCertificate
63+
5964 -- * Internal conversion functions
6065 , toShelleyCertificate
6166 , fromShelleyCertificate
@@ -77,10 +82,12 @@ import Cardano.Api.Eon.ConwayEraOnwards
7782import Cardano.Api.Eon.ShelleyBasedEra
7883import Cardano.Api.Eon.ShelleyToBabbageEra
7984import Cardano.Api.Eras
85+ import Cardano.Api.Error (Error (.. ))
8086import Cardano.Api.Governance.Actions.VotingProcedure
8187import Cardano.Api.HasTypeProxy
8288import Cardano.Api.Keys.Praos
8389import Cardano.Api.Keys.Shelley
90+ import Cardano.Api.Pretty (Doc )
8491import Cardano.Api.ReexposeLedger (EraCrypto , StandardCrypto )
8592import qualified Cardano.Api.ReexposeLedger as Ledger
8693import Cardano.Api.Script
@@ -90,9 +97,11 @@ import Cardano.Api.StakePoolMetadata
9097import Cardano.Api.Utils (noInlineMaybeToStrictMaybe )
9198import Cardano.Api.Value
9299
100+ import Cardano.Ledger.BaseTypes (strictMaybe )
93101import qualified Cardano.Ledger.Coin as L
94102import qualified Cardano.Ledger.Keys as Ledger
95103
104+ import Control.Monad.Except (MonadError (.. ))
96105import Data.ByteString (ByteString )
97106import qualified Data.ByteString as BS
98107import Data.IP (IPv4 , IPv6 )
@@ -101,7 +110,7 @@ import Data.Text (Text)
101110import qualified Data.Text as Text
102111import qualified Data.Text.Encoding as Text
103112import Data.Typeable
104- import GHC.Exts (IsList (.. ))
113+ import GHC.Exts (IsList (.. ), fromString )
105114import Network.Socket (PortNumber )
106115
107116-- ----------------------------------------------------------------------------
@@ -724,3 +733,62 @@ fromShelleyPoolParams
724733 fromShelleyDnsName =
725734 Text. encodeUtf8
726735 . Ledger. dnsToText
736+
737+ data AnchorDataFromCertificateError
738+ = InvalidPoolMetadataHashError Ledger. Url ByteString
739+ deriving (Eq , Show )
740+
741+ instance Error AnchorDataFromCertificateError where
742+ prettyError :: AnchorDataFromCertificateError -> Doc ann
743+ prettyError (InvalidPoolMetadataHashError url hash) =
744+ " Invalid pool metadata hash for URL " <> fromString (show url) <> " : " <> fromString (show hash)
745+
746+ -- | Get anchor data hash from a certificate. A return value of `Nothing`
747+ -- means that the certificate does not contain anchor data.
748+ getAnchorDataFromCertificate
749+ :: Certificate era
750+ -> Either AnchorDataFromCertificateError (Maybe (Ledger. Anchor StandardCrypto ))
751+ getAnchorDataFromCertificate c =
752+ case c of
753+ ShelleyRelatedCertificate stbe scert ->
754+ shelleyToBabbageEraConstraints stbe $
755+ case scert of
756+ Ledger. RegTxCert _ -> return Nothing
757+ Ledger. UnRegTxCert _ -> return Nothing
758+ Ledger. DelegStakeTxCert _ _ -> return Nothing
759+ Ledger. RegPoolTxCert poolParams -> strictMaybe (return Nothing ) anchorDataFromPoolMetadata $ Ledger. ppMetadata poolParams
760+ Ledger. RetirePoolTxCert _ _ -> return Nothing
761+ Ledger. GenesisDelegTxCert {} -> return Nothing
762+ Ledger. MirTxCert _ -> return Nothing
763+ ConwayCertificate ceo ccert ->
764+ conwayEraOnwardsConstraints ceo $
765+ case ccert of
766+ Ledger. RegTxCert _ -> return Nothing
767+ Ledger. UnRegTxCert _ -> return Nothing
768+ Ledger. RegDepositTxCert _ _ -> return Nothing
769+ Ledger. UnRegDepositTxCert _ _ -> return Nothing
770+ Ledger. RegDepositDelegTxCert {} -> return Nothing
771+ Ledger. DelegTxCert {} -> return Nothing
772+ Ledger. RegPoolTxCert poolParams -> strictMaybe (return Nothing ) anchorDataFromPoolMetadata $ Ledger. ppMetadata poolParams
773+ Ledger. RetirePoolTxCert _ _ -> return Nothing
774+ Ledger. RegDRepTxCert _ _ mAnchor -> return $ Ledger. strictMaybeToMaybe mAnchor
775+ Ledger. UnRegDRepTxCert _ _ -> return Nothing
776+ Ledger. UpdateDRepTxCert _ mAnchor -> return $ Ledger. strictMaybeToMaybe mAnchor
777+ Ledger. AuthCommitteeHotKeyTxCert _ _ -> return Nothing
778+ Ledger. ResignCommitteeColdTxCert _ mAnchor -> return $ Ledger. strictMaybeToMaybe mAnchor
779+ where
780+ anchorDataFromPoolMetadata
781+ :: MonadError AnchorDataFromCertificateError m
782+ => Ledger. PoolMetadata
783+ -> m (Maybe (Ledger. Anchor StandardCrypto ))
784+ anchorDataFromPoolMetadata (Ledger. PoolMetadata {Ledger. pmUrl = url, Ledger. pmHash = hashBytes}) = do
785+ hash <-
786+ maybe (throwError $ InvalidPoolMetadataHashError url hashBytes) return $
787+ Ledger. hashFromBytes hashBytes
788+ return $
789+ Just
790+ ( Ledger. Anchor
791+ { Ledger. anchorUrl = url
792+ , Ledger. anchorDataHash = Ledger. unsafeMakeSafeHash hash
793+ }
794+ )
0 commit comments