6
6
{-# LANGUAGE TypeFamilies #-}
7
7
{-# OPTIONS_GHC -Wno-orphans #-}
8
8
9
- module Cardano.Api.Internal.CIP.CIP129
10
- ( CIP129 (.. )
9
+ module Cardano.Api.Internal.CIP.Cip129
10
+ ( Cip129 (.. )
11
11
, deserialiseFromBech32CIP129
12
- , serialiseToBech32CIP129
12
+ , serialiseToBech32Cip129
13
13
, serialiseGovActionIdToBech32CIP129
14
14
, deserialiseGovActionIdFromBech32CIP129
15
15
)
@@ -38,9 +38,9 @@ import Data.Text (Text)
38
38
import Data.Text.Encoding qualified as Text
39
39
import GHC.Exts (IsList (.. ))
40
40
41
- -- | CIP129 is a typeclass that captures the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
41
+ -- | Cip129 is a typeclass that captures the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
42
42
-- which pertain to governance credentials and governance action ids.
43
- class (SerialiseAsRawBytes a , HasTypeProxy a ) => CIP129 a where
43
+ class (SerialiseAsRawBytes a , HasTypeProxy a ) => Cip129 a where
44
44
cip129Bech32PrefixFor :: AsType a -> Text
45
45
46
46
cip129HeaderHexByte :: a -> ByteString
@@ -49,32 +49,35 @@ class (SerialiseAsRawBytes a, HasTypeProxy a) => CIP129 a where
49
49
default cip129Bech32PrefixesPermitted :: AsType a -> [Text ]
50
50
cip129Bech32PrefixesPermitted = return . cip129Bech32PrefixFor
51
51
52
- instance CIP129 (Credential L. ColdCommitteeRole ) where
52
+ instance Cip129 (Credential L. ColdCommitteeRole ) where
53
53
cip129Bech32PrefixFor _ = " cc_cold"
54
54
cip129Bech32PrefixesPermitted AsColdCommitteeCredential = [" cc_cold" ]
55
55
cip129HeaderHexByte c =
56
56
case c of
57
57
L. KeyHashObj {} -> BS. singleton 0x12 -- 0001 0010
58
58
L. ScriptHashObj {} -> BS. singleton 0x13 -- 0001 0011
59
59
60
- instance CIP129 (Credential L. HotCommitteeRole ) where
60
+ instance Cip129 (Credential L. HotCommitteeRole ) where
61
61
cip129Bech32PrefixFor _ = " cc_hot"
62
62
cip129Bech32PrefixesPermitted AsHotCommitteeCredential = [" cc_hot" ]
63
63
cip129HeaderHexByte c =
64
64
case c of
65
65
L. KeyHashObj {} -> BS. singleton 0x02 -- 0000 0010
66
66
L. ScriptHashObj {} -> BS. singleton 0x03 -- 0000 0011
67
67
68
- instance CIP129 (Credential L. DRepRole ) where
68
+ instance Cip129 (Credential L. DRepRole ) where
69
69
cip129Bech32PrefixFor _ = " drep"
70
70
cip129Bech32PrefixesPermitted AsDrepCredential = [" drep" ]
71
71
cip129HeaderHexByte c =
72
72
case c of
73
73
L. KeyHashObj {} -> BS. singleton 0x22 -- 0010 0010
74
74
L. ScriptHashObj {} -> BS. singleton 0x23 -- 0010 0011
75
75
76
- serialiseToBech32CIP129 :: forall a . CIP129 a => a -> Text
77
- serialiseToBech32CIP129 a =
76
+ -- | Serialize a accoding to the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
77
+ -- which currently pertain to governance credentials. Governance action ids are dealt separately with
78
+ -- via 'serialiseGovActionIdToBech32CIP129'.
79
+ serialiseToBech32Cip129 :: forall a . Cip129 a => a -> Text
80
+ serialiseToBech32Cip129 a =
78
81
Bech32. encodeLenient
79
82
humanReadablePart
80
83
(Bech32. dataPartFromBytes (cip129HeaderHexByte a <> serialiseToRawBytes a))
@@ -85,13 +88,13 @@ serialiseToBech32CIP129 a =
85
88
Right p -> p
86
89
Left err ->
87
90
error $
88
- " serialiseToBech32CIP129 : invalid prefix "
91
+ " serialiseToBech32Cip129 : invalid prefix "
89
92
++ show prefix
90
93
++ " , "
91
94
++ show err
92
95
93
96
deserialiseFromBech32CIP129
94
- :: CIP129 a
97
+ :: Cip129 a
95
98
=> AsType a -> Text -> Either Bech32DecodeError a
96
99
deserialiseFromBech32CIP129 asType bech32Str = do
97
100
(prefix, dataPart) <-
@@ -130,7 +133,7 @@ deserialiseFromBech32CIP129 asType bech32Str = do
130
133
toBase16Text = Text. decodeUtf8 . Base16. encode
131
134
132
135
-- | Governance Action ID
133
- -- According to CIP129 there is no header byte for GovActionId.
136
+ -- According to Cip129 there is no header byte for GovActionId.
134
137
-- Instead they append the txid and index to form the payload.
135
138
serialiseGovActionIdToBech32CIP129 :: Gov. GovActionId -> Text
136
139
serialiseGovActionIdToBech32CIP129 (Gov. GovActionId txid index) =
0 commit comments