11{-# LANGUAGE DataKinds #-}
2+ {-# LANGUAGE DefaultSignatures #-}
23{-# LANGUAGE FlexibleInstances #-}
34{-# LANGUAGE RankNTypes #-}
45{-# LANGUAGE ScopedTypeVariables #-}
@@ -41,10 +42,14 @@ import GHC.Exts (IsList (..))
4142import Text.Read
4243
4344-- | CIP129 is a typeclass that captures the serialisation requirements of https://cips.cardano.org/cip/CIP-0129
44- class SerialiseAsRawBytes a => CIP129 a where
45- cip129Bech32PrefixFor :: a -> Text
45+ class (SerialiseAsRawBytes a , HasTypeProxy a ) => CIP129 a where
46+ cip129Bech32PrefixFor :: AsType a -> Text
47+
4648 cip129HeaderHexByte :: a -> ByteString
49+
4750 cip129Bech32PrefixesPermitted :: AsType a -> [Text ]
51+ default cip129Bech32PrefixesPermitted :: AsType a -> [Text ]
52+ cip129Bech32PrefixesPermitted = return . cip129Bech32PrefixFor
4853
4954instance CIP129 (Credential L. ColdCommitteeRole ) where
5055 cip129Bech32PrefixFor _ = " cc_cold"
@@ -111,19 +116,19 @@ instance SerialiseAsRawBytes (Credential L.DRepRole) where
111116 )
112117 . CBOR. decodeFull'
113118
114- serialiseToBech32CIP129 :: CIP129 a => a -> Text
119+ serialiseToBech32CIP129 :: forall a . CIP129 a => a -> Text
115120serialiseToBech32CIP129 a =
116121 Bech32. encodeLenient
117122 humanReadablePart
118123 (Bech32. dataPartFromBytes (cip129HeaderHexByte a <> serialiseToRawBytes a))
119124 where
120- prefix = cip129Bech32PrefixFor a
125+ prefix = cip129Bech32PrefixFor (proxyToAsType ( Proxy :: Proxy a ))
121126 humanReadablePart =
122127 case Bech32. humanReadablePartFromText prefix of
123128 Right p -> p
124129 Left err ->
125130 error $
126- " serialiseToBech32 : invalid prefix "
131+ " serialiseToBech32CIP129 : invalid prefix "
127132 ++ show prefix
128133 ++ " , "
129134 ++ show err
@@ -145,7 +150,7 @@ deserialiseFromBech32CIP129 asType bech32Str = do
145150 Bech32. dataPartToBytes dataPart
146151 ?! Bech32DataPartToBytesError (Bech32. dataPartToText dataPart)
147152
148- let (header, credential) = BS. splitAt 1 payload
153+ let (header, credential) = BS. uncons payload
149154
150155 value <- case deserialiseFromRawBytes asType credential of
151156 Right a -> Right a
@@ -156,7 +161,7 @@ deserialiseFromBech32CIP129 asType bech32Str = do
156161 guard (header == expectedHeader)
157162 ?! Bech32UnexpectedHeader (toBase16Text expectedHeader) (toBase16Text header)
158163
159- let expectedPrefix = cip129Bech32PrefixFor value
164+ let expectedPrefix = cip129Bech32PrefixFor asType
160165 guard (actualPrefix == expectedPrefix)
161166 ?! Bech32WrongPrefix actualPrefix expectedPrefix
162167
@@ -182,7 +187,7 @@ serialiseGovActionIdToBech32CIP129 (Gov.GovActionId txid index) =
182187 Right p -> p
183188 Left err ->
184189 error $
185- " serialiseToBech32 : invalid prefix "
190+ " serialiseGovActionIdToBech32CIP129 : invalid prefix "
186191 ++ show prefix
187192 ++ " , "
188193 ++ show err
0 commit comments