11{-# LANGUAGE DataKinds #-}
22{-# LANGUAGE DefaultSignatures #-}
33{-# LANGUAGE FlexibleInstances #-}
4+ {-# LANGUAGE LambdaCase #-}
45{-# LANGUAGE RankNTypes #-}
56{-# LANGUAGE ScopedTypeVariables #-}
67{-# LANGUAGE TypeFamilies #-}
@@ -12,12 +13,13 @@ module Cardano.Api.Internal.CIP.Cip129
1213 , serialiseToBech32Cip129
1314 , serialiseGovActionIdToBech32CIP129
1415 , deserialiseGovActionIdFromBech32CIP129
16+ , AsType (AsColdCommitteeCredential , AsDrepCredential , AsHotCommitteeCredential )
1517 )
1618where
1719
1820import Cardano.Api.Internal.Governance.Actions.ProposalProcedure
1921import Cardano.Api.Internal.HasTypeProxy
20- import Cardano.Api.Internal.Orphans.All (AsType (.. ))
22+ import Cardano.Api.Internal.Orphans (AsType (.. ))
2123import Cardano.Api.Internal.SerialiseBech32
2224import Cardano.Api.Internal.SerialiseRaw
2325import Cardano.Api.Internal.TxIn
@@ -38,17 +40,22 @@ import Data.Text (Text)
3840import Data.Text.Encoding qualified as Text
3941import GHC.Exts (IsList (.. ))
4042
41- -- | Cip129 is a typeclass that captures the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
43+ -- | Cip-129 is a typeclass that captures the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
4244-- which pertain to governance credentials and governance action ids.
4345class (SerialiseAsRawBytes a , HasTypeProxy a ) => Cip129 a where
46+ -- | The human readable part of the Bech32 encoding for the credential.
4447 cip129Bech32PrefixFor :: AsType a -> Bech32. HumanReadablePart
4548
49+ -- | The header byte that identifies the credential type according to Cip-129.
4650 cip129HeaderHexByte :: a -> ByteString
4751
52+ -- | Permitted bech32 prefixes according to Cip-129.
4853 cip129Bech32PrefixesPermitted :: AsType a -> [Text ]
4954 default cip129Bech32PrefixesPermitted :: AsType a -> [Text ]
5055 cip129Bech32PrefixesPermitted = return . Bech32. humanReadablePartToText . cip129Bech32PrefixFor
5156
57+ -- | The human readable part of the Bech32 encoding for the credential. This will
58+ -- error if the prefix is not valid.
5259unsafeHumanReadablePartFromText :: Text -> Bech32. HumanReadablePart
5360unsafeHumanReadablePartFromText =
5461 either (error . (" Error while parsing Bech32: " <> ) . show ) id
@@ -57,26 +64,27 @@ unsafeHumanReadablePartFromText =
5764instance Cip129 (Credential L. ColdCommitteeRole ) where
5865 cip129Bech32PrefixFor _ = unsafeHumanReadablePartFromText " cc_cold"
5966 cip129Bech32PrefixesPermitted AsColdCommitteeCredential = [" cc_cold" ]
60- cip129HeaderHexByte c =
61- case c of
62- L. KeyHashObj {} -> BS. singleton 0x12 -- 0001 0010
63- L. ScriptHashObj {} -> BS. singleton 0x13 -- 0001 0011
67+
68+ cip129HeaderHexByte =
69+ BS. singleton . \ case
70+ L. KeyHashObj {} -> 0x12 -- 0001 0010
71+ L. ScriptHashObj {} -> 0x13 -- 0001 0011
6472
6573instance Cip129 (Credential L. HotCommitteeRole ) where
6674 cip129Bech32PrefixFor _ = unsafeHumanReadablePartFromText " cc_hot"
6775 cip129Bech32PrefixesPermitted AsHotCommitteeCredential = [" cc_hot" ]
68- cip129HeaderHexByte c =
69- case c of
70- L. KeyHashObj {} -> BS. singleton 0x02 -- 0000 0010
71- L. ScriptHashObj {} -> BS. singleton 0x03 -- 0000 0011
76+ cip129HeaderHexByte =
77+ BS. singleton . \ case
78+ L. KeyHashObj {} -> 0x02 -- 0000 0010
79+ L. ScriptHashObj {} -> 0x03 -- 0000 0011
7280
7381instance Cip129 (Credential L. DRepRole ) where
7482 cip129Bech32PrefixFor _ = unsafeHumanReadablePartFromText " drep"
7583 cip129Bech32PrefixesPermitted AsDrepCredential = [" drep" ]
76- cip129HeaderHexByte c =
77- case c of
78- L. KeyHashObj {} -> BS. singleton 0x22 -- 0010 0010
79- L. ScriptHashObj {} -> BS. singleton 0x23 -- 0010 0011
84+ cip129HeaderHexByte =
85+ BS. singleton . \ case
86+ L. KeyHashObj {} -> 0x22 -- 0010 0010
87+ L. ScriptHashObj {} -> 0x23 -- 0010 0011
8088
8189-- | Serialize a accoding to the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
8290-- which currently pertain to governance credentials. Governance action ids are dealt separately with
0 commit comments