From 1c14a3cfb65d64c21865ecaf9c5601ba4e2ead9b Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Mon, 9 Dec 2024 13:27:12 +0100 Subject: [PATCH 1/9] correct swagger --- specifications/api/swagger.yaml | 11 +---------- 1 file changed, 1 insertion(+), 10 deletions(-) diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index bd3634535f0..d7803a6c5f0 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -406,13 +406,6 @@ x-drepKeyHash: &drepKeyHash description: DRep's key hash. pattern: "^(drep)1[0-9a-z]*$" -x-drepScriptHash: &drepScriptHash - type: string - format: bech32 - example: drep_script1wqaz0q0zhtxlgn0ewssevn2mrtm30fgh2g7hr7z9rj5856457mm - description: DRep's script hash. - pattern: "^(drep_script)1[0-9a-z]*$" - x-walletAccountXPubkey: &walletAccountXPubkey description: An extended account public key (public key + chain code) type: string @@ -2978,9 +2971,7 @@ components: - no_confidence title: casting a default vote - <<: *drepKeyHash - title: vote to a drep represented by key hash - - <<: *drepScriptHash - title: vote to a drep represented by script hash + title: vote to a drep represented by key/script hash ApiWalletDelegationNext: &ApiWalletDelegationNext type: object From 667512caf9e116bfa6eb792908907cb856c8d130 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Tue, 10 Dec 2024 16:28:10 +0100 Subject: [PATCH 2/9] Primitive.Types.DRep adjusted --- .../Cardano/Wallet/Primitive/Types/DRep.hs | 107 +++++++++--------- 1 file changed, 52 insertions(+), 55 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs index 3c03047e485..92b072e7c33 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BinaryLiterals #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} @@ -9,10 +10,8 @@ module Cardano.Wallet.Primitive.Types.DRep , DRepKeyHash (..) , DRepScriptHash (..) , DRep (..) - , encodeDRepKeyHashBech32 - , decodeDRepKeyHashBech32 - , encodeDRepScriptHashBech32 - , decodeDRepScriptHashBech32 + , encodeDRepIDBech32 + , decodeDRepIDBech32 ) where @@ -21,6 +20,9 @@ import Prelude import Control.DeepSeq ( NFData ) +import Data.Bifunctor + ( first + ) import Data.ByteString ( ByteString ) @@ -32,6 +34,9 @@ import Data.Text.Class , TextDecodingError (TextDecodingError) , ToText (..) ) +import Data.Word + ( Word8 + ) import Fmt ( Buildable (..) ) @@ -41,12 +46,15 @@ import GHC.Generics import qualified Codec.Binary.Bech32 as Bech32 import qualified Codec.Binary.Bech32.TH as Bech32 +import qualified Data.ByteString as BS +-- | This is raw key hash credential newtype DRepKeyHash = DRepKeyHash { getDRepKeyHash :: ByteString } deriving (Generic, Eq, Ord, Show) instance NFData DRepKeyHash +-- | This is raw script hash credential newtype DRepScriptHash = DRepScriptHash { getDRepScriptHash :: ByteString } deriving (Generic, Eq, Ord, Show) @@ -57,58 +65,57 @@ data DRepID = deriving (Eq, Generic, Show, Ord) deriving anyclass NFData --- | Encode 'DRepKeyHash' as Bech32 with "drep" hrp. -encodeDRepKeyHashBech32 :: DRepKeyHash -> Text -encodeDRepKeyHashBech32 = +-- | Encode 'DRepID' as Bech32 with "drep" hrp. +encodeDRepIDBech32 :: DRepID -> Text +encodeDRepIDBech32 drepid = Bech32.encodeLenient hrp . Bech32.dataPartFromBytes - . getDRepKeyHash + $ appendCip0129BytePrefix where hrp = [Bech32.humanReadablePart|drep|] - --- | Decode a Bech32 encoded 'DRepKeyHash'. -decodeDRepKeyHashBech32 :: Text -> Either TextDecodingError DRepKeyHash -decodeDRepKeyHashBech32 t = + appendCip0129BytePrefix = case drepid of + DRepFromKeyHash (DRepKeyHash payload) -> + -- according to CIP-0129 (https://github.com/cardano-foundation/CIPs/tree/master/CIP-0129) + -- drep 0010.... + -- keyhash ....0010 + let fstByte = 0b00100010 :: Word8 + in BS.cons fstByte payload + DRepFromScriptHash (DRepScriptHash payload) -> + -- according to CIP-0129 (https://github.com/cardano-foundation/CIPs/tree/master/CIP-0129) + -- drep 0010.... + -- scripthash ....0011 + let fstByte = 0b00100011 :: Word8 + in BS.cons fstByte payload + +-- | Decode a Bech32 encoded 'DRepID'. +decodeDRepIDBech32 :: Text -> Either TextDecodingError DRepID +decodeDRepIDBech32 t = case fmap Bech32.dataPartToBytes <$> Bech32.decodeLenient t of Left _ -> Left textDecodingError Right (hrp', Just bytes) - | hrp' == hrp -> Right $ DRepKeyHash bytes + | hrp' == hrp -> + let (fstByte, payload) = first BS.head $ BS.splitAt 1 bytes + in case fstByte of + 0b00100010 -> + Right $ DRepFromKeyHash (DRepKeyHash payload) + 0b00100011 -> + Right $ DRepFromScriptHash (DRepScriptHash payload) + _ -> + Left textFirstByteError Right _ -> Left textDecodingError where textDecodingError = TextDecodingError $ unwords [ "Invalid DRep key hash: expecting a Bech32 encoded value" , "with human readable part of 'drep'." ] - hrp = [Bech32.humanReadablePart|drep|] - --- | Encode 'DRepScriptHash' as Bech32 with "drep_script" hrp. -encodeDRepScriptHashBech32 :: DRepScriptHash -> Text -encodeDRepScriptHashBech32 = - Bech32.encodeLenient hrp - . Bech32.dataPartFromBytes - . getDRepScriptHash - where - hrp = [Bech32.humanReadablePart|drep_script|] - --- | Decode a Bech32 encoded 'DRepScriptHash'. -decodeDRepScriptHashBech32 :: Text -> Either TextDecodingError DRepScriptHash -decodeDRepScriptHashBech32 t = - case fmap Bech32.dataPartToBytes <$> Bech32.decodeLenient t of - Left _ -> Left textDecodingError - Right (hrp', Just bytes) - | hrp' == hrp -> Right $ DRepScriptHash bytes - Right _ -> Left textDecodingError - where - textDecodingError = TextDecodingError $ unwords - [ "Invalid DRep Script hash: expecting a Bech32 encoded value" - , "with human readable part of 'drep_script'." + textFirstByteError = TextDecodingError $ unwords + [ "Invalid DRep metadata: expecting a byte '00100010' value for key hash or" + , "a byte '0b00100011' value for script hash." ] - hrp = [Bech32.humanReadablePart|drep_script|] + hrp = [Bech32.humanReadablePart|drep|] instance Buildable DRepID where - build = \case - DRepFromKeyHash keyhash -> build $ encodeDRepKeyHashBech32 keyhash - DRepFromScriptHash scripthash -> build $ encodeDRepScriptHashBech32 scripthash + build = build . encodeDRepIDBech32 -- | A decentralized representation ('DRep') will -- vote on behalf of the stake delegated to it. @@ -122,26 +129,16 @@ data DRep instance ToText DRep where toText Abstain = "abstain" toText NoConfidence = "no_confidence" - toText (FromDRepID (DRepFromKeyHash keyhash)) = - encodeDRepKeyHashBech32 keyhash - toText (FromDRepID (DRepFromScriptHash scripthash)) = - encodeDRepScriptHashBech32 scripthash + toText (FromDRepID drepid) = encodeDRepIDBech32 drepid instance FromText DRep where fromText txt = case txt of "abstain" -> Right Abstain "no_confidence" -> Right NoConfidence - _ -> case decodeDRepKeyHashBech32 txt of - Right keyhash -> - Right $ FromDRepID $ DRepFromKeyHash keyhash - Left _ -> case decodeDRepScriptHashBech32 txt of - Right scripthash -> - Right $ FromDRepID $ DRepFromScriptHash scripthash - Left _ -> Left $ TextDecodingError $ unwords - [ "I couldn't parse the given decentralized representative (DRep)." - , "I am expecting either 'abstain', 'no_confidence'" - , "or bech32 encoded drep having prefixes: 'drep'" - , "or 'drep_script'."] + _ -> case decodeDRepIDBech32 txt of + Right drepid -> + Right $ FromDRepID drepid + Left err -> Left err instance Buildable DRep where build = \case From 3d7e85b08f0962ddb5ba2ef070afa5e48005c081 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Tue, 10 Dec 2024 16:46:25 +0100 Subject: [PATCH 3/9] use second and clean description --- .../lib/Cardano/Wallet/Primitive/Types/DRep.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs index 92b072e7c33..b9134ccced6 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -22,6 +22,7 @@ import Control.DeepSeq ) import Data.Bifunctor ( first + , second ) import Data.ByteString ( ByteString @@ -48,13 +49,13 @@ import qualified Codec.Binary.Bech32 as Bech32 import qualified Codec.Binary.Bech32.TH as Bech32 import qualified Data.ByteString as BS --- | This is raw key hash credential +-- | Raw key hash credential newtype DRepKeyHash = DRepKeyHash { getDRepKeyHash :: ByteString } deriving (Generic, Eq, Ord, Show) instance NFData DRepKeyHash --- | This is raw script hash credential +-- | Raw script hash credential newtype DRepScriptHash = DRepScriptHash { getDRepScriptHash :: ByteString } deriving (Generic, Eq, Ord, Show) @@ -135,10 +136,7 @@ instance FromText DRep where fromText txt = case txt of "abstain" -> Right Abstain "no_confidence" -> Right NoConfidence - _ -> case decodeDRepIDBech32 txt of - Right drepid -> - Right $ FromDRepID drepid - Left err -> Left err + _ -> second FromDRepID (decodeDRepIDBech32 txt) instance Buildable DRep where build = \case From 2b667d9cb2c2dede181af83c6f6b30520586cfb6 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Tue, 10 Dec 2024 17:22:40 +0100 Subject: [PATCH 4/9] Api.Types.Certificate adjustment --- .../Cardano/Wallet/Api/Types/Certificate.hs | 29 ++++++------------- 1 file changed, 9 insertions(+), 20 deletions(-) diff --git a/lib/api/src/Cardano/Wallet/Api/Types/Certificate.hs b/lib/api/src/Cardano/Wallet/Api/Types/Certificate.hs index 67cbe2bf0e9..52671e88926 100644 --- a/lib/api/src/Cardano/Wallet/Api/Types/Certificate.hs +++ b/lib/api/src/Cardano/Wallet/Api/Types/Certificate.hs @@ -69,11 +69,8 @@ import Cardano.Wallet.Primitive.Types ) import Cardano.Wallet.Primitive.Types.DRep ( DRep (..) - , DRepID (..) - , decodeDRepKeyHashBech32 - , decodeDRepScriptHashBech32 - , encodeDRepKeyHashBech32 - , encodeDRepScriptHashBech32 + , decodeDRepIDBech32 + , encodeDRepIDBech32 ) import Cardano.Wallet.Util ( ShowFmt (..) @@ -343,25 +340,17 @@ mkApiAnyCertificate acct' acctPath' = \case instance ToJSON (ApiT DRep) where toJSON (ApiT Abstain) = "abstain" toJSON (ApiT NoConfidence) = "no_confidence" - toJSON (ApiT (FromDRepID drep)) = case drep of - DRepFromKeyHash keyhash -> - String $ encodeDRepKeyHashBech32 keyhash - DRepFromScriptHash scripthash -> - String $ encodeDRepScriptHashBech32 scripthash + toJSON (ApiT (FromDRepID drepid)) = + String $ encodeDRepIDBech32 drepid instance FromJSON (ApiT DRep) where parseJSON t = - parseAbstain t <|> parseNoConfidence t <|> parseKeyHash t <|> parseScriptHash t + parseAbstain t <|> parseNoConfidence t <|> parseDrepID t where - parseKeyHash = withText "DRepKeyHash" $ \txt -> - case decodeDRepKeyHashBech32 txt of + parseDrepID = withText "DRepID" $ \txt -> + case decodeDRepIDBech32 txt of Left (TextDecodingError err) -> fail err - Right keyhash -> - pure $ ApiT $ FromDRepID $ DRepFromKeyHash keyhash - parseScriptHash = withText "DRepScriptHash" $ \txt -> - case decodeDRepScriptHashBech32 txt of - Left (TextDecodingError err) -> fail err - Right scripthash -> - pure $ ApiT $ FromDRepID $ DRepFromScriptHash scripthash + Right drepid -> + pure $ ApiT $ FromDRepID drepid parseAbstain = withText "Abstain" $ \txt -> if txt == "abstain" then pure $ ApiT Abstain From 875e7722e5a72d4866713e6be2ed4be745b7fc65 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Wed, 11 Dec 2024 10:21:29 +0100 Subject: [PATCH 5/9] handle testing - part 1 --- .../Cardano/Wallet/Primitive/Types/DRep.hs | 26 ++++++++++++------- .../test/unit/Cardano/Wallet/Api/Malformed.hs | 7 +++-- .../test/unit/Cardano/Wallet/Api/TypesSpec.hs | 8 ++++-- 3 files changed, 27 insertions(+), 14 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs index b9134ccced6..15634e13d79 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -12,6 +12,8 @@ module Cardano.Wallet.Primitive.Types.DRep , DRep (..) , encodeDRepIDBech32 , decodeDRepIDBech32 + , fstByteDRepKeyHash + , fstByteDRepScriptHash ) where @@ -53,12 +55,24 @@ import qualified Data.ByteString as BS newtype DRepKeyHash = DRepKeyHash { getDRepKeyHash :: ByteString } deriving (Generic, Eq, Ord, Show) +-- | In accordance to CIP-0129 (https://github.com/cardano-foundation/CIPs/tree/master/CIP-0129) +-- drep 0010.... +-- keyhash ....0010 +fstByteDRepKeyHash :: Word8 +fstByteDRepKeyHash = 0b00100010 + instance NFData DRepKeyHash -- | Raw script hash credential newtype DRepScriptHash = DRepScriptHash { getDRepScriptHash :: ByteString } deriving (Generic, Eq, Ord, Show) +-- | In accordance to CIP-0129 (https://github.com/cardano-foundation/CIPs/tree/master/CIP-0129) +-- drep 0010.... +-- scripthash ....0011 +fstByteDRepScriptHash :: Word8 +fstByteDRepScriptHash = 0b00100011 + instance NFData DRepScriptHash data DRepID = @@ -76,17 +90,9 @@ encodeDRepIDBech32 drepid = hrp = [Bech32.humanReadablePart|drep|] appendCip0129BytePrefix = case drepid of DRepFromKeyHash (DRepKeyHash payload) -> - -- according to CIP-0129 (https://github.com/cardano-foundation/CIPs/tree/master/CIP-0129) - -- drep 0010.... - -- keyhash ....0010 - let fstByte = 0b00100010 :: Word8 - in BS.cons fstByte payload + BS.cons fstByteDRepKeyHash payload DRepFromScriptHash (DRepScriptHash payload) -> - -- according to CIP-0129 (https://github.com/cardano-foundation/CIPs/tree/master/CIP-0129) - -- drep 0010.... - -- scripthash ....0011 - let fstByte = 0b00100011 :: Word8 - in BS.cons fstByte payload + BS.cons fstByteDRepScriptHash payload -- | Decode a Bech32 encoded 'DRepID'. decodeDRepIDBech32 :: Text -> Either TextDecodingError DRepID diff --git a/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs b/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs index fdb05cf1977..2268cb7eb65 100644 --- a/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs +++ b/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs @@ -215,8 +215,8 @@ instance Wellformed (PathParam ApiDRepSpecifier) where wellformed = PathParam <$> [ "abstain" , "no_confidence" - , "drep15k6929drl7xt0spvudgcxndryn4kmlzpk4meed0xhqe25nle07s" - , "drep_script1hwj9yuvzxc623w5lmwvp44md7qkdywz2fcd583qmyu62jvjnz69" + , "drep1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcvy952y" --28-byte payload with key hash byte prefix ('22' in hex prefixed) + , "drep1y0je8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcvk492r" --28-byte payload with script hash byte prefix ('23' in hex prefixed) ] instance Malformed (PathParam ApiDRepSpecifier) where @@ -226,6 +226,9 @@ instance Malformed (PathParam ApiDRepSpecifier) where , (T.replicate 65 "1", msg) , ("something", msg) , ("no-confidence", msg) + , ("drep15k6929drl7xt0spvudgcxndryn4kmlzpk4meed0xhqe25nle07s",msg) --28-byte payload without byte prefix correct hrp prefix + , ("drep1xhje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axc9fjca3",msg) --28-byte payload with wrong byte prefix but correct hrp prefix + , ("drepp1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcp60l06",msg) --28-byte payload with key hash byte prefix but wrong hrp prefix ] where msg = "I couldn't parse the given decentralized representative (DRep). I am expecting either 'abstain', 'no_confidence' or bech32 encoded drep having prefixes: 'drep' or 'drep_script'." diff --git a/lib/unit/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/unit/test/unit/Cardano/Wallet/Api/TypesSpec.hs index 7eba242c605..e03abc0dfca 100644 --- a/lib/unit/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/unit/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -395,6 +395,8 @@ import Cardano.Wallet.Primitive.Types.DRep , DRepID (..) , DRepKeyHash (..) , DRepScriptHash (..) + , fstByteDRepKeyHash + , fstByteDRepScriptHash ) import Cardano.Wallet.Primitive.Types.Hash ( Hash (..) @@ -2089,8 +2091,10 @@ instance Arbitrary ApiEncryptMetadataMethod where instance Arbitrary DRepID where arbitrary = do InfiniteList bytes _ <- arbitrary - oneof [ pure $ DRepFromKeyHash $ DRepKeyHash $ BS.pack $ take 28 bytes - , pure $ DRepFromScriptHash $ DRepScriptHash $ BS.pack $ take 28 bytes + oneof [ pure $ DRepFromKeyHash $ DRepKeyHash $ + BS.cons fstByteDRepKeyHash $ BS.pack $ take 28 bytes + , pure $ DRepFromScriptHash $ DRepScriptHash $ + BS.cons fstByteDRepScriptHash $ BS.pack $ take 28 bytes ] instance Arbitrary DRep where From ee6d135c09adcbee454eed7eb6c8cb5fc635dbc1 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Wed, 11 Dec 2024 10:48:25 +0100 Subject: [PATCH 6/9] handle testing - part 2 --- .../test/unit/Cardano/Wallet/Api/Malformed.hs | 19 ++++++++++--------- 1 file changed, 10 insertions(+), 9 deletions(-) diff --git a/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs b/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs index 2268cb7eb65..3f5ba82d2c9 100644 --- a/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs +++ b/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs @@ -221,17 +221,18 @@ instance Wellformed (PathParam ApiDRepSpecifier) where instance Malformed (PathParam ApiDRepSpecifier) where malformed = first PathParam <$> - [ (T.replicate 64 "ś", msg) - , (T.replicate 63 "1", msg) - , (T.replicate 65 "1", msg) - , ("something", msg) - , ("no-confidence", msg) - , ("drep15k6929drl7xt0spvudgcxndryn4kmlzpk4meed0xhqe25nle07s",msg) --28-byte payload without byte prefix correct hrp prefix - , ("drep1xhje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axc9fjca3",msg) --28-byte payload with wrong byte prefix but correct hrp prefix - , ("drepp1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcp60l06",msg) --28-byte payload with key hash byte prefix but wrong hrp prefix + [ (T.replicate 64 "ś", msg1) + , (T.replicate 63 "1", msg1) + , (T.replicate 65 "1", msg1) + , ("something", msg1) + , ("no-confidence", msg1) + , ("drep15k6929drl7xt0spvudgcxndryn4kmlzpk4meed0xhqe25nle07s",msg2) --28-byte payload without byte prefix correct hrp prefix + , ("drep1xhje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axc9fjca3",msg2) --28-byte payload with wrong byte prefix but correct hrp prefix + , ("drepp1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcp60l06",msg1) --28-byte payload with key hash byte prefix but wrong hrp prefix ] where - msg = "I couldn't parse the given decentralized representative (DRep). I am expecting either 'abstain', 'no_confidence' or bech32 encoded drep having prefixes: 'drep' or 'drep_script'." + msg1 = "Invalid DRep key hash: expecting a Bech32 encoded value with human readable part of 'drep'." + msg2 = "Invalid DRep metadata: expecting a byte '00100010' value for key hash or a byte '0b00100011' value for script hash." instance Wellformed (PathParam (ApiAddress ('Testnet 0))) where wellformed = [PathParam From 0863a7fc8353156d4b98261242cae702958c91e6 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Wed, 11 Dec 2024 11:08:34 +0100 Subject: [PATCH 7/9] regenerate ApiTDRep golden --- lib/unit/test/data/Cardano/Wallet/Api/ApiTDRep.json | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/lib/unit/test/data/Cardano/Wallet/Api/ApiTDRep.json b/lib/unit/test/data/Cardano/Wallet/Api/ApiTDRep.json index 6514ebc74ba..4f8914a32bd 100644 --- a/lib/unit/test/data/Cardano/Wallet/Api/ApiTDRep.json +++ b/lib/unit/test/data/Cardano/Wallet/Api/ApiTDRep.json @@ -2,14 +2,14 @@ "samples": [ "abstain", "abstain", - "drep1c9umxe06vc0vzv9fu866axles2lpaqhsh36suqc7h0hzv8e2hcs", - "no_confidence", - "abstain", "abstain", - "drep_script13y9jcl4mu3sxr6t2dckyceuz6mwtaahqyr8dld8yqhqmwjv0l9e", + "drep1yv3cj5rqf0xtv7t77v30dyvm25umvhku76td23z4yf7xllsl0cw64x", "abstain", + "drep1yv3mrqjjtrekq8hjskdlv7dfmwq3s93urkff6d6v344w9hjj9kxc0k", "no_confidence", + "abstain", + "drep1yg3q2x8ph8ujl6eqm85ej9a4f69qw8dujcnvf9w2kry3jsa0nmwjfz", "abstain" ], - "seed": -2053978213 + "seed": -323609406 } \ No newline at end of file From be83ff0d44083923b0902e982c85471506c1d1a9 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Wed, 11 Dec 2024 12:33:33 +0100 Subject: [PATCH 8/9] Update drep keys description to point to CIP-0129 Note that we spent time trying to have a unique DRep keys schema representing both keys and scripts hashes but for reasons unknown to the mere mortals, bump.sh kept rejecting our changes hence why we resorted to keeping the 2 types but with identical underlying representations. --- specifications/api/swagger.yaml | 16 ++++++++++++++-- 1 file changed, 14 insertions(+), 2 deletions(-) diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index d7803a6c5f0..93bfd17cf3e 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -403,7 +403,17 @@ x-drepKeyHash: &drepKeyHash type: string format: bech32 example: drep1wqaz0q0zhtxlgn0ewssevn2mrtm30fgh2g7hr7z9rj5856457mm - description: DRep's key hash. + description: DRep's key hash according to CIP-0129. + pattern: "^(drep)1[0-9a-z]*$" + +x-drepScriptHash: &drepScriptHash + type: string + format: bech32 + example: drep1wqaz0q0zhtxlgn0ewssevn2mrtm30fgh2g7hr7z9rj5856457mm + description: | + DRep's script hash according to CIP-0129. Note this is identical + to drepKeyHash but for unknown reasons we need to different + schema fragments here. pattern: "^(drep)1[0-9a-z]*$" x-walletAccountXPubkey: &walletAccountXPubkey @@ -2971,7 +2981,9 @@ components: - no_confidence title: casting a default vote - <<: *drepKeyHash - title: vote to a drep represented by key/script hash + title: vote to a drep represented by key hash + - <<: *drepScriptHash + title: vote to a drep represented by script hash ApiWalletDelegationNext: &ApiWalletDelegationNext type: object From 8b5d36d7022ef4ad334d2a3211c4a9a0390e6127 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Fri, 13 Dec 2024 14:49:20 +0100 Subject: [PATCH 9/9] applying review remarks --- .../lib/Cardano/Wallet/Primitive/Types/DRep.hs | 2 +- .../test/unit/Cardano/Wallet/Api/Malformed.hs | 16 +++++++++++----- specifications/api/swagger.yaml | 7 +++---- 3 files changed, 15 insertions(+), 10 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs index 15634e13d79..ca2118bd5c3 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -80,7 +80,7 @@ data DRepID = deriving (Eq, Generic, Show, Ord) deriving anyclass NFData --- | Encode 'DRepID' as Bech32 with "drep" hrp. +-- | Encode 'DRepID' as Bech32 with "drep" human readable prefix. encodeDRepIDBech32 :: DRepID -> Text encodeDRepIDBech32 drepid = Bech32.encodeLenient hrp diff --git a/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs b/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs index 3f5ba82d2c9..a059a4d12c6 100644 --- a/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs +++ b/lib/unit/test/unit/Cardano/Wallet/Api/Malformed.hs @@ -215,9 +215,12 @@ instance Wellformed (PathParam ApiDRepSpecifier) where wellformed = PathParam <$> [ "abstain" , "no_confidence" - , "drep1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcvy952y" --28-byte payload with key hash byte prefix ('22' in hex prefixed) - , "drep1y0je8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcvk492r" --28-byte payload with script hash byte prefix ('23' in hex prefixed) + , payloadKeyHashWith22HexByte + , payloadScriptHashWith23HexByte ] + where + payloadKeyHashWith22HexByte = "drep1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcvy952y" + payloadScriptHashWith23HexByte = "drep1y0je8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcvk492r" instance Malformed (PathParam ApiDRepSpecifier) where malformed = first PathParam <$> @@ -226,13 +229,16 @@ instance Malformed (PathParam ApiDRepSpecifier) where , (T.replicate 65 "1", msg1) , ("something", msg1) , ("no-confidence", msg1) - , ("drep15k6929drl7xt0spvudgcxndryn4kmlzpk4meed0xhqe25nle07s",msg2) --28-byte payload without byte prefix correct hrp prefix - , ("drep1xhje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axc9fjca3",msg2) --28-byte payload with wrong byte prefix but correct hrp prefix - , ("drepp1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcp60l06",msg1) --28-byte payload with key hash byte prefix but wrong hrp prefix + , (payloadWithoutCorrectBytePrefixCorrectHrp, msg2) + , (payloadWithWrongBytePrefixCorrectHrp, msg2) + , (payloadWithCorrectBytePrefixWrondHrp, msg1) ] where msg1 = "Invalid DRep key hash: expecting a Bech32 encoded value with human readable part of 'drep'." msg2 = "Invalid DRep metadata: expecting a byte '00100010' value for key hash or a byte '0b00100011' value for script hash." + payloadWithoutCorrectBytePrefixCorrectHrp = "drep15k6929drl7xt0spvudgcxndryn4kmlzpk4meed0xhqe25nle07s" + payloadWithWrongBytePrefixCorrectHrp = "drep1xhje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axc9fjca3" + payloadWithCorrectBytePrefixWrondHrp = "drepp1ytje8qacj9dyua6esh86rdjqpdactf8wph05gdd72u46axcp60l06" instance Wellformed (PathParam (ApiAddress ('Testnet 0))) where wellformed = [PathParam diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index 93bfd17cf3e..aeb27a75725 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -411,10 +411,9 @@ x-drepScriptHash: &drepScriptHash format: bech32 example: drep1wqaz0q0zhtxlgn0ewssevn2mrtm30fgh2g7hr7z9rj5856457mm description: | - DRep's script hash according to CIP-0129. Note this is identical - to drepKeyHash but for unknown reasons we need to different - schema fragments here. - pattern: "^(drep)1[0-9a-z]*$" + DRep's script hash according to CIP-0129 uses also 'drep' bech32 prefix. + This one is deprecated and should not be used. + pattern: "^(drep_script)1[0-9a-z]*$" x-walletAccountXPubkey: &walletAccountXPubkey description: An extended account public key (public key + chain code)