diff --git a/cardano-api/cardano-api.cabal b/cardano-api/cardano-api.cabal index e713e244a6..8d2aa807e8 100644 --- a/cardano-api/cardano-api.cabal +++ b/cardano-api/cardano-api.cabal @@ -54,6 +54,7 @@ library internal Cardano.Api.Convenience.Construction Cardano.Api.Convenience.Query Cardano.Api.DeserialiseAnyOf + Cardano.Api.DRepMetadata Cardano.Api.EraCast Cardano.Api.Eras Cardano.Api.Error diff --git a/cardano-api/internal/Cardano/Api/Certificate.hs b/cardano-api/internal/Cardano/Api/Certificate.hs index ca50d0ac75..fc29adbcf6 100644 --- a/cardano-api/internal/Cardano/Api/Certificate.hs +++ b/cardano-api/internal/Cardano/Api/Certificate.hs @@ -25,6 +25,9 @@ module Cardano.Api.Certificate ( makeCommitteeDelegationCertificate, makeCommitteeHotKeyUnregistrationCertificate, + -- * Registering DReps + DRepMetadataReference(..), + -- * Special certificates makeMIRCertificate, makeGenesisKeyDelegationCertificate, @@ -41,9 +44,8 @@ module Cardano.Api.Certificate ( ) where import Cardano.Api.Address -import Cardano.Api.Hash +import Cardano.Api.DRepMetadata import Cardano.Api.HasTypeProxy -import Cardano.Api.Keys.Byron import Cardano.Api.Keys.Praos import Cardano.Api.Keys.Shelley import Cardano.Api.SerialiseCBOR @@ -191,6 +193,13 @@ data StakePoolMetadataReference = } deriving (Eq, Show) +data DRepMetadataReference = + DRepMetadataReference { + drepMetadataURL :: Text, + drepMetadataHash :: Hash DRepMetadata + } + deriving (Eq, Show) + -- ---------------------------------------------------------------------------- -- Constructor functions diff --git a/cardano-api/internal/Cardano/Api/DRepMetadata.hs b/cardano-api/internal/Cardano/Api/DRepMetadata.hs new file mode 100644 index 0000000000..201bfa11d0 --- /dev/null +++ b/cardano-api/internal/Cardano/Api/DRepMetadata.hs @@ -0,0 +1,167 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE TypeFamilies #-} + +-- | DRep off-chain metadata +-- +module Cardano.Api.DRepMetadata ( + -- * DRep off-chain metadata + DRepMetadata(..), + validateAndHashDRepMetadata, + DRepMetadataValidationError(..), + + -- * Data family instances + AsType(..), + Hash(..), + ) where + +import Cardano.Api.Eras +import Cardano.Api.Error +import Cardano.Api.Hash +import Cardano.Api.HasTypeProxy +import Cardano.Api.Keys.Byron +import Cardano.Api.Keys.Praos +import Cardano.Api.Script +import Cardano.Api.SerialiseJSON +import Cardano.Api.SerialiseRaw + +import qualified Cardano.Crypto.Hash.Class as Crypto +import Cardano.Ledger.Crypto (StandardCrypto) +import qualified Cardano.Ledger.Keys as Shelley + +import Data.Aeson ((.:)) +import qualified Data.Aeson as Aeson +import qualified Data.Aeson.Types as Aeson +import Data.Bifunctor (first) +import Data.ByteString (ByteString) +import qualified Data.ByteString as BS +import Data.Either.Combinators (maybeToRight) +import Data.Text (Text) +import qualified Data.Text as Text + +-- ---------------------------------------------------------------------------- +-- DRep metadata +-- + +-- | A representation of the required fields for off-chain drep metadata. +-- +data DRepMetadata = + DRepMetadata + { drepName :: !Text + -- ^ A name of up to 50 characters. + , drepDescription :: !Text + -- ^ A description of up to 255 characters. + , drepTicker :: !Text + -- ^ A ticker of 3-5 characters, for a compact display of dreps in + -- a wallet. + , drepHomepage :: !Text + -- ^ A URL to a homepage with additional information about the drep. + -- n.b. the spec does not specify a character limit for this field. + } deriving (Eq, Show) + +newtype instance Hash DRepMetadata = DRepMetadataHash (Shelley.Hash StandardCrypto ByteString) + deriving (Eq, Show) + +instance HasTypeProxy DRepMetadata where + data AsType DRepMetadata = AsDRepMetadata + proxyToAsType _ = AsDRepMetadata + +instance SerialiseAsRawBytes (Hash DRepMetadata) where + serialiseToRawBytes (DRepMetadataHash h) = Crypto.hashToBytes h + + deserialiseFromRawBytes (AsHash AsDRepMetadata) bs = + maybeToRight (SerialiseAsRawBytesError "Unable to deserialise Hash DRepMetadata") $ + DRepMetadataHash <$> Crypto.hashFromBytes bs + +--TODO: instance ToJSON DRepMetadata where + +instance FromJSON DRepMetadata where + parseJSON = + Aeson.withObject "DRepMetadata" $ \obj -> + DRepMetadata + <$> parseName obj + <*> parseDescription obj + <*> parseTicker obj + <*> obj .: "homepage" + + where + -- Parse and validate the drep metadata name from a JSON object. + -- The name must be 50 characters or fewer. + parseName :: Aeson.Object -> Aeson.Parser Text + parseName obj = do + name <- obj .: "name" + if Text.length name <= 50 + then pure name + else + fail $ mconcat + [ "\"name\" must have at most 50 characters, but it has " + , show (Text.length name) + , " characters." + ] + + -- Parse and validate the drep metadata description + -- The description must be 255 characters or fewer. + parseDescription :: Aeson.Object -> Aeson.Parser Text + parseDescription obj = do + description <- obj .: "description" + if Text.length description <= 255 + then pure description + else + fail $ mconcat + [ "\"description\" must have at most 255 characters, but it has " + , show (Text.length description) + , " characters." + ] + + -- | Parse and validate the drep ticker description + -- The ticker must be 3 to 5 characters long. + parseTicker :: Aeson.Object -> Aeson.Parser Text + parseTicker obj = do + ticker <- obj .: "ticker" + let tickerLen = Text.length ticker + if tickerLen >= 3 && tickerLen <= 5 + then pure ticker + else + fail $ mconcat + [ "\"ticker\" must have at least 3 and at most 5 " + , "characters, but it has " + , show (Text.length ticker) + , " characters." + ] + +-- | A drep metadata validation error. +data DRepMetadataValidationError + = DRepMetadataJsonDecodeError !String + | DRepMetadataInvalidLengthError + -- ^ The length of the JSON-encoded drep metadata exceeds the + -- maximum. + !Int + -- ^ Maximum byte length. + !Int + -- ^ Actual byte length. + deriving Show + +instance Error DRepMetadataValidationError where + displayError = \case + DRepMetadataJsonDecodeError errStr -> errStr + DRepMetadataInvalidLengthError maxLen actualLen -> + mconcat + [ "DRep metadata must consist of at most " + , show maxLen + , " bytes, but it consists of " + , show actualLen + , " bytes." + ] + +-- | Decode and validate the provided JSON-encoded bytes as 'DRepMetadata'. +-- Return the decoded metadata and the hash of the original bytes. +validateAndHashDRepMetadata + :: ByteString + -> Either DRepMetadataValidationError (DRepMetadata, Hash DRepMetadata) +validateAndHashDRepMetadata bs + | BS.length bs <= 512 = do + md <- first DRepMetadataJsonDecodeError + (Aeson.eitherDecodeStrict' bs) + let mdh = DRepMetadataHash (Crypto.hashWith id bs) + return (md, mdh) + | otherwise = Left $ DRepMetadataInvalidLengthError 512 (BS.length bs) diff --git a/cardano-api/internal/Cardano/Api/Keys/Shelley.hs b/cardano-api/internal/Cardano/Api/Keys/Shelley.hs index 9fe3544ba1..dbb4799cd6 100644 --- a/cardano-api/internal/Cardano/Api/Keys/Shelley.hs +++ b/cardano-api/internal/Cardano/Api/Keys/Shelley.hs @@ -19,6 +19,7 @@ module Cardano.Api.Keys.Shelley ( -- * Key types CommitteeColdKey, CommitteeHotKey, + DRepKey, PaymentKey, PaymentExtendedKey, StakeKey, @@ -1462,3 +1463,121 @@ instance HasTextEnvelope (SigningKey StakePoolKey) where proxy :: Proxy (Shelley.DSIGN StandardCrypto) proxy = Proxy +-- +-- DRep keys +-- + +data DRepKey + +instance HasTypeProxy DRepKey where + data AsType DRepKey = AsDRepKey + proxyToAsType _ = AsDRepKey + +instance Key DRepKey where + + newtype VerificationKey DRepKey = + DRepVerificationKey (Shelley.VKey {- TODO cip-1694: replace with Shelley.DRep -} Shelley.StakePool StandardCrypto) + deriving stock (Eq) + deriving (Show, IsString) via UsingRawBytesHex (VerificationKey DRepKey) + deriving newtype (ToCBOR, FromCBOR) + deriving anyclass SerialiseAsCBOR + + newtype SigningKey DRepKey = + DRepSigningKey (Shelley.SignKeyDSIGN StandardCrypto) + deriving (Show, IsString) via UsingRawBytesHex (SigningKey DRepKey) + deriving newtype (ToCBOR, FromCBOR) + deriving anyclass SerialiseAsCBOR + + deterministicSigningKey :: AsType DRepKey -> Crypto.Seed -> SigningKey DRepKey + deterministicSigningKey AsDRepKey seed = + DRepSigningKey (Crypto.genKeyDSIGN seed) + + deterministicSigningKeySeedSize :: AsType DRepKey -> Word + deterministicSigningKeySeedSize AsDRepKey = + Crypto.seedSizeDSIGN proxy + where + proxy :: Proxy (Shelley.DSIGN StandardCrypto) + proxy = Proxy + + getVerificationKey :: SigningKey DRepKey -> VerificationKey DRepKey + getVerificationKey (DRepSigningKey sk) = + DRepVerificationKey (Shelley.VKey (Crypto.deriveVerKeyDSIGN sk)) + + verificationKeyHash :: VerificationKey DRepKey -> Hash DRepKey + verificationKeyHash (DRepVerificationKey vkey) = + DRepKeyHash (Shelley.hashKey vkey) + +instance SerialiseAsRawBytes (VerificationKey DRepKey) where + serialiseToRawBytes (DRepVerificationKey (Shelley.VKey vk)) = + Crypto.rawSerialiseVerKeyDSIGN vk + + deserialiseFromRawBytes (AsVerificationKey AsDRepKey) bs = + maybeToRight (SerialiseAsRawBytesError "Unable to deserialise VerificationKey DRepKey") $ + DRepVerificationKey . Shelley.VKey <$> + Crypto.rawDeserialiseVerKeyDSIGN bs + +instance SerialiseAsRawBytes (SigningKey DRepKey) where + serialiseToRawBytes (DRepSigningKey sk) = + Crypto.rawSerialiseSignKeyDSIGN sk + + deserialiseFromRawBytes (AsSigningKey AsDRepKey) bs = + maybe + (Left (SerialiseAsRawBytesError "Unable to deserialise SigningKey DRepKey")) + (Right . DRepSigningKey) + (Crypto.rawDeserialiseSignKeyDSIGN bs) + +instance SerialiseAsBech32 (VerificationKey DRepKey) where + bech32PrefixFor _ = "drep_vk" + bech32PrefixesPermitted _ = ["drep_vk"] + +instance SerialiseAsBech32 (SigningKey DRepKey) where + bech32PrefixFor _ = "drep_sk" + bech32PrefixesPermitted _ = ["drep_sk"] + +newtype instance Hash DRepKey = + DRepKeyHash { unDRepKeyHash :: Shelley.KeyHash {- TODO cip-1694: replace with Shelley.DRep -} Shelley.StakePool StandardCrypto } + deriving stock (Eq, Ord) + deriving (Show, IsString) via UsingRawBytesHex (Hash DRepKey) + deriving (ToCBOR, FromCBOR) via UsingRawBytes (Hash DRepKey) + deriving anyclass SerialiseAsCBOR + +instance SerialiseAsRawBytes (Hash DRepKey) where + serialiseToRawBytes (DRepKeyHash (Shelley.KeyHash vkh)) = + Crypto.hashToBytes vkh + + deserialiseFromRawBytes (AsHash AsDRepKey) bs = + maybeToRight + (SerialiseAsRawBytesError "Unable to deserialise Hash DRepKey") + (DRepKeyHash . Shelley.KeyHash <$> Crypto.hashFromBytes bs) + +instance SerialiseAsBech32 (Hash DRepKey) where + bech32PrefixFor _ = "drep" + bech32PrefixesPermitted _ = ["drep"] + +instance ToJSON (Hash DRepKey) where + toJSON = toJSON . serialiseToBech32 + +instance ToJSONKey (Hash DRepKey) where + toJSONKey = toJSONKeyText serialiseToBech32 + +instance FromJSON (Hash DRepKey) where + parseJSON = withText "DRepId" $ \str -> + case deserialiseFromBech32 (AsHash AsDRepKey) str of + Left err -> + fail $ "Error deserialising Hash DRepKey: " <> Text.unpack str <> + " Error: " <> displayError err + Right h -> pure h + +instance HasTextEnvelope (VerificationKey DRepKey) where + textEnvelopeType _ = "DRepVerificationKey_" + <> fromString (Crypto.algorithmNameDSIGN proxy) + where + proxy :: Proxy (Shelley.DSIGN StandardCrypto) + proxy = Proxy + +instance HasTextEnvelope (SigningKey DRepKey) where + textEnvelopeType _ = "DRepSigningKey_" + <> fromString (Crypto.algorithmNameDSIGN proxy) + where + proxy :: Proxy (Shelley.DSIGN StandardCrypto) + proxy = Proxy diff --git a/cardano-api/src/Cardano/Api.hs b/cardano-api/src/Cardano/Api.hs index 52b06ca8b7..e933d41537 100644 --- a/cardano-api/src/Cardano/Api.hs +++ b/cardano-api/src/Cardano/Api.hs @@ -852,10 +852,16 @@ module Cardano.Api ( -- * Governance + -- ** DReps + DRepKey, + DRepMetadata, + DRepMetadataReference, + DRepMetadataValidationError, + validateAndHashDRepMetadata, + -- ** Governance Committee makeCommitteeDelegationCertificate, makeCommitteeHotKeyUnregistrationCertificate, - ) where import Cardano.Api.Address @@ -865,6 +871,7 @@ import Cardano.Api.Convenience.Constraints import Cardano.Api.Convenience.Construction import Cardano.Api.Convenience.Query import Cardano.Api.DeserialiseAnyOf +import Cardano.Api.DRepMetadata import Cardano.Api.EraCast import Cardano.Api.Eras import Cardano.Api.Error diff --git a/cardano-api/src/Cardano/Api/Shelley.hs b/cardano-api/src/Cardano/Api/Shelley.hs index bb4095111b..41a5a526b4 100644 --- a/cardano-api/src/Cardano/Api/Shelley.hs +++ b/cardano-api/src/Cardano/Api/Shelley.hs @@ -182,6 +182,10 @@ module Cardano.Api.Shelley ), EpochNo(..), + -- * DRep + DRepMetadata(DRepMetadata), + DRepMetadataReference(DRepMetadataReference), + -- ** Stake pool operator's keys StakePoolKey, PoolId, @@ -258,12 +262,12 @@ import Cardano.Api import Cardano.Api.Address import Cardano.Api.Block import Cardano.Api.Certificate +import Cardano.Api.DRepMetadata import Cardano.Api.Eras import Cardano.Api.Genesis import Cardano.Api.Governance.Poll import Cardano.Api.InMode import Cardano.Api.IPC -import Cardano.Api.Keys.Byron import Cardano.Api.Keys.Praos import Cardano.Api.Keys.Shelley import Cardano.Api.LedgerState