1
1
{-# LANGUAGE DataKinds #-}
2
2
{-# LANGUAGE DefaultSignatures #-}
3
3
{-# LANGUAGE FlexibleInstances #-}
4
+ {-# LANGUAGE LambdaCase #-}
4
5
{-# LANGUAGE RankNTypes #-}
5
6
{-# LANGUAGE ScopedTypeVariables #-}
6
7
{-# LANGUAGE TypeFamilies #-}
@@ -12,12 +13,13 @@ module Cardano.Api.Internal.CIP.Cip129
12
13
, serialiseToBech32Cip129
13
14
, serialiseGovActionIdToBech32CIP129
14
15
, deserialiseGovActionIdFromBech32CIP129
16
+ , AsType (AsColdCommitteeCredential , AsDrepCredential , AsHotCommitteeCredential )
15
17
)
16
18
where
17
19
18
20
import Cardano.Api.Internal.Governance.Actions.ProposalProcedure
19
21
import Cardano.Api.Internal.HasTypeProxy
20
- import Cardano.Api.Internal.Orphans.All (AsType (.. ))
22
+ import Cardano.Api.Internal.Orphans (AsType (.. ))
21
23
import Cardano.Api.Internal.SerialiseBech32
22
24
import Cardano.Api.Internal.SerialiseRaw
23
25
import Cardano.Api.Internal.TxIn
@@ -38,17 +40,22 @@ import Data.Text (Text)
38
40
import Data.Text.Encoding qualified as Text
39
41
import GHC.Exts (IsList (.. ))
40
42
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
42
44
-- which pertain to governance credentials and governance action ids.
43
45
class (SerialiseAsRawBytes a , HasTypeProxy a ) => Cip129 a where
46
+ -- | The human readable part of the Bech32 encoding for the credential.
44
47
cip129Bech32PrefixFor :: AsType a -> Bech32. HumanReadablePart
45
48
49
+ -- | The header byte that identifies the credential type according to Cip-129.
46
50
cip129HeaderHexByte :: a -> ByteString
47
51
52
+ -- | Permitted bech32 prefixes according to Cip-129.
48
53
cip129Bech32PrefixesPermitted :: AsType a -> [Text ]
49
54
default cip129Bech32PrefixesPermitted :: AsType a -> [Text ]
50
55
cip129Bech32PrefixesPermitted = return . Bech32. humanReadablePartToText . cip129Bech32PrefixFor
51
56
57
+ -- | The human readable part of the Bech32 encoding for the credential. This will
58
+ -- error if the prefix is not valid.
52
59
unsafeHumanReadablePartFromText :: Text -> Bech32. HumanReadablePart
53
60
unsafeHumanReadablePartFromText =
54
61
either (error . (" Error while parsing Bech32: " <> ) . show ) id
@@ -57,26 +64,27 @@ unsafeHumanReadablePartFromText =
57
64
instance Cip129 (Credential L. ColdCommitteeRole ) where
58
65
cip129Bech32PrefixFor _ = unsafeHumanReadablePartFromText " cc_cold"
59
66
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
64
72
65
73
instance Cip129 (Credential L. HotCommitteeRole ) where
66
74
cip129Bech32PrefixFor _ = unsafeHumanReadablePartFromText " cc_hot"
67
75
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
72
80
73
81
instance Cip129 (Credential L. DRepRole ) where
74
82
cip129Bech32PrefixFor _ = unsafeHumanReadablePartFromText " drep"
75
83
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
80
88
81
89
-- | Serialize a accoding to the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
82
90
-- which currently pertain to governance credentials. Governance action ids are dealt separately with
0 commit comments