{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Cardano.Ledger.Address
( mkVKeyRwdAcnt,
mkRwdAcnt,
toAddr,
toCred,
serialiseAddr,
deserialiseAddr,
deserialiseAddrStakeRef,
Addr (..),
BootstrapAddress (..),
bootstrapAddressAttrsSize,
isBootstrapRedeemer,
getNetwork,
RewardAcnt (..),
serialiseRewardAcnt,
deserialiseRewardAcnt,
byron,
notBaseAddr,
isEnterpriseAddr,
stakeCredIsScript,
getAddr,
getKeyHash,
bootstrapKeyHash,
getPtr,
getRewardAcnt,
getScriptHash,
getVariableLengthWord64,
payCredIsScript,
putAddr,
putCredential,
putPtr,
putRewardAcnt,
putVariableLengthWord64,
word64ToWord7s,
word7sToWord64,
Word7 (..),
toWord7,
)
where
import Cardano.Binary
( Decoder,
DecoderError (..),
FromCBOR (..),
ToCBOR (..),
decodeFull,
serialize,
)
import qualified Cardano.Chain.Common as Byron
import qualified Cardano.Crypto.Hash.Class as Hash
import qualified Cardano.Crypto.Hashing as Byron
import Cardano.Ledger.BaseTypes
( CertIx (..),
Network (..),
TxIx (..),
networkToWord8,
word8ToNetwork,
)
import Cardano.Ledger.Credential
( Credential (..),
PaymentCredential,
Ptr (..),
StakeReference (..),
)
import Cardano.Ledger.Crypto (ADDRHASH)
import qualified Cardano.Ledger.Crypto as CC (Crypto)
import Cardano.Ledger.Hashes (ScriptHash (..))
import Cardano.Ledger.Keys
( KeyHash (..),
KeyPair (..),
KeyRole (..),
hashKey,
)
import Cardano.Ledger.Slot (SlotNo (..))
import Cardano.Prelude (panic)
import Control.DeepSeq (NFData)
import Data.Aeson (FromJSON (..), FromJSONKey (..), ToJSON (..), ToJSONKey (..), (.:), (.=))
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Encoding as Aeson
import qualified Data.Aeson.Key as Aeson (fromText)
import qualified Data.Aeson.Types as Aeson
import Data.Binary (Get, Put, Word8)
import qualified Data.Binary as B
import qualified Data.Binary.Get as B
import qualified Data.Binary.Put as B
import Data.Bits (setBit, shiftL, shiftR, testBit, (.&.), (.|.))
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base16 as B16
import qualified Data.ByteString.Lazy as BSL
import Data.Coders (cborError)
import Data.Foldable (foldl')
import Data.Maybe (fromMaybe)
import Data.String (fromString)
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
import Data.Word (Word64)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks (..))
import Quiet
mkVKeyRwdAcnt ::
CC.Crypto crypto =>
Network ->
KeyPair 'Staking crypto ->
RewardAcnt crypto
mkVKeyRwdAcnt :: Network -> KeyPair 'Staking crypto -> RewardAcnt crypto
mkVKeyRwdAcnt Network
network KeyPair 'Staking crypto
keys = Network -> Credential 'Staking crypto -> RewardAcnt crypto
forall crypto.
Network -> Credential 'Staking crypto -> RewardAcnt crypto
RewardAcnt Network
network (Credential 'Staking crypto -> RewardAcnt crypto)
-> Credential 'Staking crypto -> RewardAcnt crypto
forall a b. (a -> b) -> a -> b
$ KeyHash 'Staking crypto -> Credential 'Staking crypto
forall (kr :: KeyRole) crypto.
KeyHash kr crypto -> Credential kr crypto
KeyHashObj (VKey 'Staking crypto -> KeyHash 'Staking crypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
hashKey (VKey 'Staking crypto -> KeyHash 'Staking crypto)
-> VKey 'Staking crypto -> KeyHash 'Staking crypto
forall a b. (a -> b) -> a -> b
$ KeyPair 'Staking crypto -> VKey 'Staking crypto
forall (kd :: KeyRole) crypto. KeyPair kd crypto -> VKey kd crypto
vKey KeyPair 'Staking crypto
keys)
mkRwdAcnt ::
Network ->
Credential 'Staking crypto ->
RewardAcnt crypto
mkRwdAcnt :: Network -> Credential 'Staking crypto -> RewardAcnt crypto
mkRwdAcnt Network
network script :: Credential 'Staking crypto
script@(ScriptHashObj ScriptHash crypto
_) = Network -> Credential 'Staking crypto -> RewardAcnt crypto
forall crypto.
Network -> Credential 'Staking crypto -> RewardAcnt crypto
RewardAcnt Network
network Credential 'Staking crypto
script
mkRwdAcnt Network
network key :: Credential 'Staking crypto
key@(KeyHashObj KeyHash 'Staking crypto
_) = Network -> Credential 'Staking crypto -> RewardAcnt crypto
forall crypto.
Network -> Credential 'Staking crypto -> RewardAcnt crypto
RewardAcnt Network
network Credential 'Staking crypto
key
toAddr ::
CC.Crypto crypto =>
Network ->
(KeyPair 'Payment crypto, KeyPair 'Staking crypto) ->
Addr crypto
toAddr :: Network
-> (KeyPair 'Payment crypto, KeyPair 'Staking crypto)
-> Addr crypto
toAddr Network
n (KeyPair 'Payment crypto
payKey, KeyPair 'Staking crypto
stakeKey) = Network
-> PaymentCredential crypto -> StakeReference crypto -> Addr crypto
forall crypto.
Network
-> PaymentCredential crypto -> StakeReference crypto -> Addr crypto
Addr Network
n (KeyPair 'Payment crypto -> PaymentCredential crypto
forall crypto (kr :: KeyRole).
Crypto crypto =>
KeyPair kr crypto -> Credential kr crypto
toCred KeyPair 'Payment crypto
payKey) (StakeCredential crypto -> StakeReference crypto
forall crypto. StakeCredential crypto -> StakeReference crypto
StakeRefBase (StakeCredential crypto -> StakeReference crypto)
-> StakeCredential crypto -> StakeReference crypto
forall a b. (a -> b) -> a -> b
$ KeyPair 'Staking crypto -> StakeCredential crypto
forall crypto (kr :: KeyRole).
Crypto crypto =>
KeyPair kr crypto -> Credential kr crypto
toCred KeyPair 'Staking crypto
stakeKey)
toCred ::
CC.Crypto crypto =>
KeyPair kr crypto ->
Credential kr crypto
toCred :: KeyPair kr crypto -> Credential kr crypto
toCred KeyPair kr crypto
k = KeyHash kr crypto -> Credential kr crypto
forall (kr :: KeyRole) crypto.
KeyHash kr crypto -> Credential kr crypto
KeyHashObj (KeyHash kr crypto -> Credential kr crypto)
-> (VKey kr crypto -> KeyHash kr crypto)
-> VKey kr crypto
-> Credential kr crypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VKey kr crypto -> KeyHash kr crypto
forall crypto (kd :: KeyRole).
Crypto crypto =>
VKey kd crypto -> KeyHash kd crypto
hashKey (VKey kr crypto -> Credential kr crypto)
-> VKey kr crypto -> Credential kr crypto
forall a b. (a -> b) -> a -> b
$ KeyPair kr crypto -> VKey kr crypto
forall (kd :: KeyRole) crypto. KeyPair kd crypto -> VKey kd crypto
vKey KeyPair kr crypto
k
serialiseAddr :: Addr crypto -> ByteString
serialiseAddr :: Addr crypto -> ByteString
serialiseAddr = ByteString -> ByteString
BSL.toStrict (ByteString -> ByteString)
-> (Addr crypto -> ByteString) -> Addr crypto -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
B.runPut (Put -> ByteString)
-> (Addr crypto -> Put) -> Addr crypto -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr crypto -> Put
forall crypto. Addr crypto -> Put
putAddr
deserialiseAddr :: CC.Crypto crypto => ByteString -> Maybe (Addr crypto)
deserialiseAddr :: ByteString -> Maybe (Addr crypto)
deserialiseAddr ByteString
bs = case Get (Addr crypto)
-> ByteString
-> Either
(ByteString, ByteOffset, String)
(ByteString, ByteOffset, Addr crypto)
forall a.
Get a
-> ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
B.runGetOrFail Get (Addr crypto)
forall crypto. Crypto crypto => Get (Addr crypto)
getAddr (ByteString -> ByteString
BSL.fromStrict ByteString
bs) of
Left (ByteString
_remaining, ByteOffset
_offset, String
_message) -> Maybe (Addr crypto)
forall a. Maybe a
Nothing
Right (ByteString
remaining, ByteOffset
_offset, Addr crypto
result) ->
if ByteString -> Bool
BSL.null ByteString
remaining
then Addr crypto -> Maybe (Addr crypto)
forall a. a -> Maybe a
Just Addr crypto
result
else Maybe (Addr crypto)
forall a. Maybe a
Nothing
deserialiseAddrStakeRef :: CC.Crypto crypto => ByteString -> Maybe (StakeReference crypto)
deserialiseAddrStakeRef :: ByteString -> Maybe (StakeReference crypto)
deserialiseAddrStakeRef ByteString
bs =
case Get (Maybe (StakeReference crypto))
-> ByteString
-> Either
(ByteString, ByteOffset, String)
(ByteString, ByteOffset, Maybe (StakeReference crypto))
forall a.
Get a
-> ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
B.runGetOrFail Get (Maybe (StakeReference crypto))
forall crypto. Crypto crypto => Get (Maybe (StakeReference crypto))
getAddrStakeReference (ByteString -> ByteString
BSL.fromStrict ByteString
bs) of
Right (ByteString
remaining, ByteOffset
_offset, Maybe (StakeReference crypto)
result)
| Bool -> Bool
not (ByteString -> Bool
BSL.null ByteString
remaining) -> Maybe (StakeReference crypto)
result
Either
(ByteString, ByteOffset, String)
(ByteString, ByteOffset, Maybe (StakeReference crypto))
_ -> Maybe (StakeReference crypto)
forall a. Maybe a
Nothing
serialiseRewardAcnt :: RewardAcnt crypto -> ByteString
serialiseRewardAcnt :: RewardAcnt crypto -> ByteString
serialiseRewardAcnt = ByteString -> ByteString
BSL.toStrict (ByteString -> ByteString)
-> (RewardAcnt crypto -> ByteString)
-> RewardAcnt crypto
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
B.runPut (Put -> ByteString)
-> (RewardAcnt crypto -> Put) -> RewardAcnt crypto -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RewardAcnt crypto -> Put
forall crypto. RewardAcnt crypto -> Put
putRewardAcnt
deserialiseRewardAcnt :: CC.Crypto crypto => ByteString -> Maybe (RewardAcnt crypto)
deserialiseRewardAcnt :: ByteString -> Maybe (RewardAcnt crypto)
deserialiseRewardAcnt ByteString
bs = case Get (RewardAcnt crypto)
-> ByteString
-> Either
(ByteString, ByteOffset, String)
(ByteString, ByteOffset, RewardAcnt crypto)
forall a.
Get a
-> ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
B.runGetOrFail Get (RewardAcnt crypto)
forall crypto. Crypto crypto => Get (RewardAcnt crypto)
getRewardAcnt (ByteString -> ByteString
BSL.fromStrict ByteString
bs) of
Left (ByteString
_remaining, ByteOffset
_offset, String
_message) -> Maybe (RewardAcnt crypto)
forall a. Maybe a
Nothing
Right (ByteString
remaining, ByteOffset
_offset, RewardAcnt crypto
result) ->
if ByteString -> Bool
BSL.null ByteString
remaining
then RewardAcnt crypto -> Maybe (RewardAcnt crypto)
forall a. a -> Maybe a
Just RewardAcnt crypto
result
else Maybe (RewardAcnt crypto)
forall a. Maybe a
Nothing
data Addr crypto
= Addr Network (PaymentCredential crypto) (StakeReference crypto)
| AddrBootstrap (BootstrapAddress crypto)
deriving (Int -> Addr crypto -> ShowS
[Addr crypto] -> ShowS
Addr crypto -> String
(Int -> Addr crypto -> ShowS)
-> (Addr crypto -> String)
-> ([Addr crypto] -> ShowS)
-> Show (Addr crypto)
forall crypto. Int -> Addr crypto -> ShowS
forall crypto. [Addr crypto] -> ShowS
forall crypto. Addr crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Addr crypto] -> ShowS
$cshowList :: forall crypto. [Addr crypto] -> ShowS
show :: Addr crypto -> String
$cshow :: forall crypto. Addr crypto -> String
showsPrec :: Int -> Addr crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> Addr crypto -> ShowS
Show, Addr crypto -> Addr crypto -> Bool
(Addr crypto -> Addr crypto -> Bool)
-> (Addr crypto -> Addr crypto -> Bool) -> Eq (Addr crypto)
forall crypto. Addr crypto -> Addr crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Addr crypto -> Addr crypto -> Bool
$c/= :: forall crypto. Addr crypto -> Addr crypto -> Bool
== :: Addr crypto -> Addr crypto -> Bool
$c== :: forall crypto. Addr crypto -> Addr crypto -> Bool
Eq, (forall x. Addr crypto -> Rep (Addr crypto) x)
-> (forall x. Rep (Addr crypto) x -> Addr crypto)
-> Generic (Addr crypto)
forall x. Rep (Addr crypto) x -> Addr crypto
forall x. Addr crypto -> Rep (Addr crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (Addr crypto) x -> Addr crypto
forall crypto x. Addr crypto -> Rep (Addr crypto) x
$cto :: forall crypto x. Rep (Addr crypto) x -> Addr crypto
$cfrom :: forall crypto x. Addr crypto -> Rep (Addr crypto) x
Generic, Addr crypto -> ()
(Addr crypto -> ()) -> NFData (Addr crypto)
forall crypto. Addr crypto -> ()
forall a. (a -> ()) -> NFData a
rnf :: Addr crypto -> ()
$crnf :: forall crypto. Addr crypto -> ()
NFData, Eq (Addr crypto)
Eq (Addr crypto)
-> (Addr crypto -> Addr crypto -> Ordering)
-> (Addr crypto -> Addr crypto -> Bool)
-> (Addr crypto -> Addr crypto -> Bool)
-> (Addr crypto -> Addr crypto -> Bool)
-> (Addr crypto -> Addr crypto -> Bool)
-> (Addr crypto -> Addr crypto -> Addr crypto)
-> (Addr crypto -> Addr crypto -> Addr crypto)
-> Ord (Addr crypto)
Addr crypto -> Addr crypto -> Bool
Addr crypto -> Addr crypto -> Ordering
Addr crypto -> Addr crypto -> Addr crypto
forall crypto. Eq (Addr crypto)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall crypto. Addr crypto -> Addr crypto -> Bool
forall crypto. Addr crypto -> Addr crypto -> Ordering
forall crypto. Addr crypto -> Addr crypto -> Addr crypto
min :: Addr crypto -> Addr crypto -> Addr crypto
$cmin :: forall crypto. Addr crypto -> Addr crypto -> Addr crypto
max :: Addr crypto -> Addr crypto -> Addr crypto
$cmax :: forall crypto. Addr crypto -> Addr crypto -> Addr crypto
>= :: Addr crypto -> Addr crypto -> Bool
$c>= :: forall crypto. Addr crypto -> Addr crypto -> Bool
> :: Addr crypto -> Addr crypto -> Bool
$c> :: forall crypto. Addr crypto -> Addr crypto -> Bool
<= :: Addr crypto -> Addr crypto -> Bool
$c<= :: forall crypto. Addr crypto -> Addr crypto -> Bool
< :: Addr crypto -> Addr crypto -> Bool
$c< :: forall crypto. Addr crypto -> Addr crypto -> Bool
compare :: Addr crypto -> Addr crypto -> Ordering
$ccompare :: forall crypto. Addr crypto -> Addr crypto -> Ordering
$cp1Ord :: forall crypto. Eq (Addr crypto)
Ord)
getNetwork :: Addr crypto -> Network
getNetwork :: Addr crypto -> Network
getNetwork (Addr Network
n PaymentCredential crypto
_ StakeReference crypto
_) = Network
n
getNetwork (AddrBootstrap (BootstrapAddress Address
byronAddr)) =
case AddrAttributes -> NetworkMagic
Byron.aaNetworkMagic (AddrAttributes -> NetworkMagic)
-> (Address -> AddrAttributes) -> Address -> NetworkMagic
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attributes AddrAttributes -> AddrAttributes
forall h. Attributes h -> h
Byron.attrData (Attributes AddrAttributes -> AddrAttributes)
-> (Address -> Attributes AddrAttributes)
-> Address
-> AddrAttributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Attributes AddrAttributes
Byron.addrAttributes (Address -> NetworkMagic) -> Address -> NetworkMagic
forall a b. (a -> b) -> a -> b
$ Address
byronAddr of
NetworkMagic
Byron.NetworkMainOrStage -> Network
Mainnet
Byron.NetworkTestnet Word32
_ -> Network
Testnet
instance NoThunks (Addr crypto)
data RewardAcnt crypto = RewardAcnt
{ RewardAcnt crypto -> Network
getRwdNetwork :: !Network,
RewardAcnt crypto -> Credential 'Staking crypto
getRwdCred :: !(Credential 'Staking crypto)
}
deriving (Int -> RewardAcnt crypto -> ShowS
[RewardAcnt crypto] -> ShowS
RewardAcnt crypto -> String
(Int -> RewardAcnt crypto -> ShowS)
-> (RewardAcnt crypto -> String)
-> ([RewardAcnt crypto] -> ShowS)
-> Show (RewardAcnt crypto)
forall crypto. Int -> RewardAcnt crypto -> ShowS
forall crypto. [RewardAcnt crypto] -> ShowS
forall crypto. RewardAcnt crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RewardAcnt crypto] -> ShowS
$cshowList :: forall crypto. [RewardAcnt crypto] -> ShowS
show :: RewardAcnt crypto -> String
$cshow :: forall crypto. RewardAcnt crypto -> String
showsPrec :: Int -> RewardAcnt crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> RewardAcnt crypto -> ShowS
Show, RewardAcnt crypto -> RewardAcnt crypto -> Bool
(RewardAcnt crypto -> RewardAcnt crypto -> Bool)
-> (RewardAcnt crypto -> RewardAcnt crypto -> Bool)
-> Eq (RewardAcnt crypto)
forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RewardAcnt crypto -> RewardAcnt crypto -> Bool
$c/= :: forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
== :: RewardAcnt crypto -> RewardAcnt crypto -> Bool
$c== :: forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
Eq, (forall x. RewardAcnt crypto -> Rep (RewardAcnt crypto) x)
-> (forall x. Rep (RewardAcnt crypto) x -> RewardAcnt crypto)
-> Generic (RewardAcnt crypto)
forall x. Rep (RewardAcnt crypto) x -> RewardAcnt crypto
forall x. RewardAcnt crypto -> Rep (RewardAcnt crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (RewardAcnt crypto) x -> RewardAcnt crypto
forall crypto x. RewardAcnt crypto -> Rep (RewardAcnt crypto) x
$cto :: forall crypto x. Rep (RewardAcnt crypto) x -> RewardAcnt crypto
$cfrom :: forall crypto x. RewardAcnt crypto -> Rep (RewardAcnt crypto) x
Generic, Eq (RewardAcnt crypto)
Eq (RewardAcnt crypto)
-> (RewardAcnt crypto -> RewardAcnt crypto -> Ordering)
-> (RewardAcnt crypto -> RewardAcnt crypto -> Bool)
-> (RewardAcnt crypto -> RewardAcnt crypto -> Bool)
-> (RewardAcnt crypto -> RewardAcnt crypto -> Bool)
-> (RewardAcnt crypto -> RewardAcnt crypto -> Bool)
-> (RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto)
-> (RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto)
-> Ord (RewardAcnt crypto)
RewardAcnt crypto -> RewardAcnt crypto -> Bool
RewardAcnt crypto -> RewardAcnt crypto -> Ordering
RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto
forall crypto. Eq (RewardAcnt crypto)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Ordering
forall crypto.
RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto
min :: RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto
$cmin :: forall crypto.
RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto
max :: RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto
$cmax :: forall crypto.
RewardAcnt crypto -> RewardAcnt crypto -> RewardAcnt crypto
>= :: RewardAcnt crypto -> RewardAcnt crypto -> Bool
$c>= :: forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
> :: RewardAcnt crypto -> RewardAcnt crypto -> Bool
$c> :: forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
<= :: RewardAcnt crypto -> RewardAcnt crypto -> Bool
$c<= :: forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
< :: RewardAcnt crypto -> RewardAcnt crypto -> Bool
$c< :: forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Bool
compare :: RewardAcnt crypto -> RewardAcnt crypto -> Ordering
$ccompare :: forall crypto. RewardAcnt crypto -> RewardAcnt crypto -> Ordering
$cp1Ord :: forall crypto. Eq (RewardAcnt crypto)
Ord, RewardAcnt crypto -> ()
(RewardAcnt crypto -> ()) -> NFData (RewardAcnt crypto)
forall crypto. RewardAcnt crypto -> ()
forall a. (a -> ()) -> NFData a
rnf :: RewardAcnt crypto -> ()
$crnf :: forall crypto. RewardAcnt crypto -> ()
NFData, ToJSONKeyFunction [RewardAcnt crypto]
ToJSONKeyFunction (RewardAcnt crypto)
ToJSONKeyFunction (RewardAcnt crypto)
-> ToJSONKeyFunction [RewardAcnt crypto]
-> ToJSONKey (RewardAcnt crypto)
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
forall crypto.
Crypto crypto =>
ToJSONKeyFunction [RewardAcnt crypto]
forall crypto.
Crypto crypto =>
ToJSONKeyFunction (RewardAcnt crypto)
toJSONKeyList :: ToJSONKeyFunction [RewardAcnt crypto]
$ctoJSONKeyList :: forall crypto.
Crypto crypto =>
ToJSONKeyFunction [RewardAcnt crypto]
toJSONKey :: ToJSONKeyFunction (RewardAcnt crypto)
$ctoJSONKey :: forall crypto.
Crypto crypto =>
ToJSONKeyFunction (RewardAcnt crypto)
ToJSONKey, FromJSONKeyFunction [RewardAcnt crypto]
FromJSONKeyFunction (RewardAcnt crypto)
FromJSONKeyFunction (RewardAcnt crypto)
-> FromJSONKeyFunction [RewardAcnt crypto]
-> FromJSONKey (RewardAcnt crypto)
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
forall crypto.
Crypto crypto =>
FromJSONKeyFunction [RewardAcnt crypto]
forall crypto.
Crypto crypto =>
FromJSONKeyFunction (RewardAcnt crypto)
fromJSONKeyList :: FromJSONKeyFunction [RewardAcnt crypto]
$cfromJSONKeyList :: forall crypto.
Crypto crypto =>
FromJSONKeyFunction [RewardAcnt crypto]
fromJSONKey :: FromJSONKeyFunction (RewardAcnt crypto)
$cfromJSONKey :: forall crypto.
Crypto crypto =>
FromJSONKeyFunction (RewardAcnt crypto)
FromJSONKey)
instance CC.Crypto crypto => ToJSON (RewardAcnt crypto) where
toJSON :: RewardAcnt crypto -> Value
toJSON RewardAcnt crypto
ra =
[Pair] -> Value
Aeson.object
[ Key
"network" Key -> Network -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= RewardAcnt crypto -> Network
forall crypto. RewardAcnt crypto -> Network
getRwdNetwork RewardAcnt crypto
ra,
Key
"credential" Key -> Credential 'Staking crypto -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= RewardAcnt crypto -> Credential 'Staking crypto
forall crypto. RewardAcnt crypto -> Credential 'Staking crypto
getRwdCred RewardAcnt crypto
ra
]
instance CC.Crypto crypto => FromJSON (RewardAcnt crypto) where
parseJSON :: Value -> Parser (RewardAcnt crypto)
parseJSON =
String
-> (Object -> Parser (RewardAcnt crypto))
-> Value
-> Parser (RewardAcnt crypto)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"RewardAcnt" ((Object -> Parser (RewardAcnt crypto))
-> Value -> Parser (RewardAcnt crypto))
-> (Object -> Parser (RewardAcnt crypto))
-> Value
-> Parser (RewardAcnt crypto)
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
Network -> Credential 'Staking crypto -> RewardAcnt crypto
forall crypto.
Network -> Credential 'Staking crypto -> RewardAcnt crypto
RewardAcnt
(Network -> Credential 'Staking crypto -> RewardAcnt crypto)
-> Parser Network
-> Parser (Credential 'Staking crypto -> RewardAcnt crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser Network
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"network"
Parser (Credential 'Staking crypto -> RewardAcnt crypto)
-> Parser (Credential 'Staking crypto)
-> Parser (RewardAcnt crypto)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (Credential 'Staking crypto)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"credential"
instance NoThunks (RewardAcnt crypto)
instance ToJSONKey (Addr crypto) where
toJSONKey :: ToJSONKeyFunction (Addr crypto)
toJSONKey = (Addr crypto -> Key)
-> (Addr crypto -> Encoding' Key)
-> ToJSONKeyFunction (Addr crypto)
forall a. (a -> Key) -> (a -> Encoding' Key) -> ToJSONKeyFunction a
Aeson.ToJSONKeyText (Text -> Key
Aeson.fromText (Text -> Key) -> (Addr crypto -> Text) -> Addr crypto -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr crypto -> Text
forall crypto. Addr crypto -> Text
addrToText) (Text -> Encoding' Key
forall a. Text -> Encoding' a
Aeson.text (Text -> Encoding' Key)
-> (Addr crypto -> Text) -> Addr crypto -> Encoding' Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr crypto -> Text
forall crypto. Addr crypto -> Text
addrToText)
instance CC.Crypto crypto => FromJSONKey (Addr crypto) where
fromJSONKey :: FromJSONKeyFunction (Addr crypto)
fromJSONKey = (Text -> Parser (Addr crypto)) -> FromJSONKeyFunction (Addr crypto)
forall a. (Text -> Parser a) -> FromJSONKeyFunction a
Aeson.FromJSONKeyTextParser Text -> Parser (Addr crypto)
forall crypto. Crypto crypto => Text -> Parser (Addr crypto)
parseAddr
instance ToJSON (Addr crypto) where
toJSON :: Addr crypto -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (Addr crypto -> Text) -> Addr crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr crypto -> Text
forall crypto. Addr crypto -> Text
addrToText
instance CC.Crypto crypto => FromJSON (Addr crypto) where
parseJSON :: Value -> Parser (Addr crypto)
parseJSON = String
-> (Text -> Parser (Addr crypto)) -> Value -> Parser (Addr crypto)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText String
"address" Text -> Parser (Addr crypto)
forall crypto. Crypto crypto => Text -> Parser (Addr crypto)
parseAddr
addrToText :: Addr crypto -> Text
addrToText :: Addr crypto -> Text
addrToText = ByteString -> Text
Text.decodeLatin1 (ByteString -> Text)
-> (Addr crypto -> ByteString) -> Addr crypto -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B16.encode (ByteString -> ByteString)
-> (Addr crypto -> ByteString) -> Addr crypto -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr crypto -> ByteString
forall crypto. Addr crypto -> ByteString
serialiseAddr
parseAddr :: CC.Crypto crypto => Text -> Aeson.Parser (Addr crypto)
parseAddr :: Text -> Parser (Addr crypto)
parseAddr Text
t = do
ByteString
bytes <- (String -> Parser ByteString)
-> (ByteString -> Parser ByteString)
-> Either String ByteString
-> Parser ByteString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Parser ByteString
forall (m :: * -> *) a a. (MonadFail m, Show a) => a -> m a
badHex ByteString -> Parser ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Either String ByteString
B16.decode (Text -> ByteString
Text.encodeUtf8 Text
t))
Parser (Addr crypto)
-> (Addr crypto -> Parser (Addr crypto))
-> Maybe (Addr crypto)
-> Parser (Addr crypto)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Parser (Addr crypto)
forall a. Parser a
badFormat Addr crypto -> Parser (Addr crypto)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Maybe (Addr crypto)
forall crypto. Crypto crypto => ByteString -> Maybe (Addr crypto)
deserialiseAddr ByteString
bytes)
where
badHex :: a -> m a
badHex a
h = String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"Addresses are expected in hex encoding for now: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
h
badFormat :: Parser a
badFormat = String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Address is not in the right format"
byron :: Int
byron :: Int
byron = Int
7
notBaseAddr :: Int
notBaseAddr :: Int
notBaseAddr = Int
6
isEnterpriseAddr :: Int
isEnterpriseAddr :: Int
isEnterpriseAddr = Int
5
stakeCredIsScript :: Int
stakeCredIsScript :: Int
stakeCredIsScript = Int
5
payCredIsScript :: Int
payCredIsScript :: Int
payCredIsScript = Int
4
rewardCredIsScript :: Int
rewardCredIsScript :: Int
rewardCredIsScript = Int
4
putAddr :: Addr crypto -> Put
putAddr :: Addr crypto -> Put
putAddr (AddrBootstrap (BootstrapAddress Address
byronAddr)) = ByteString -> Put
B.putLazyByteString (Address -> ByteString
forall a. ToCBOR a => a -> ByteString
serialize Address
byronAddr)
putAddr (Addr Network
network PaymentCredential crypto
pc StakeReference crypto
sr) =
let setPayCredBit :: Word8 -> Word8
setPayCredBit = case PaymentCredential crypto
pc of
ScriptHashObj ScriptHash crypto
_ -> (Word8 -> Int -> Word8) -> Int -> Word8 -> Word8
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
setBit Int
payCredIsScript
KeyHashObj KeyHash 'Payment crypto
_ -> Word8 -> Word8
forall a. a -> a
id
netId :: Word8
netId = Network -> Word8
networkToWord8 Network
network
in case StakeReference crypto
sr of
StakeRefBase StakeCredential crypto
sc -> do
let setStakeCredBit :: Word8 -> Word8
setStakeCredBit = case StakeCredential crypto
sc of
ScriptHashObj ScriptHash crypto
_ -> (Word8 -> Int -> Word8) -> Int -> Word8 -> Word8
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
setBit Int
stakeCredIsScript
KeyHashObj KeyHash 'Staking crypto
_ -> Word8 -> Word8
forall a. a -> a
id
header :: Word8
header = Word8 -> Word8
setStakeCredBit (Word8 -> Word8) -> (Word8 -> Word8) -> Word8 -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Word8
setPayCredBit (Word8 -> Word8) -> Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ Word8
netId
Word8 -> Put
B.putWord8 Word8
header
PaymentCredential crypto -> Put
forall (kr :: KeyRole) crypto. Credential kr crypto -> Put
putCredential PaymentCredential crypto
pc
StakeCredential crypto -> Put
forall (kr :: KeyRole) crypto. Credential kr crypto -> Put
putCredential StakeCredential crypto
sc
StakeRefPtr Ptr
ptr -> do
let header :: Word8
header = Word8 -> Word8
setPayCredBit (Word8 -> Word8) -> Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ Word8
netId Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`setBit` Int
notBaseAddr
Word8 -> Put
B.putWord8 Word8
header
PaymentCredential crypto -> Put
forall (kr :: KeyRole) crypto. Credential kr crypto -> Put
putCredential PaymentCredential crypto
pc
Ptr -> Put
putPtr Ptr
ptr
StakeReference crypto
StakeRefNull -> do
let header :: Word8
header = Word8 -> Word8
setPayCredBit (Word8 -> Word8) -> Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ Word8
netId Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`setBit` Int
isEnterpriseAddr Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`setBit` Int
notBaseAddr
Word8 -> Put
B.putWord8 Word8
header
PaymentCredential crypto -> Put
forall (kr :: KeyRole) crypto. Credential kr crypto -> Put
putCredential PaymentCredential crypto
pc
getAddr :: CC.Crypto crypto => Get (Addr crypto)
getAddr :: Get (Addr crypto)
getAddr = do
Word8
header <- Get Word8 -> Get Word8
forall a. Get a -> Get a
B.lookAhead Get Word8
B.getWord8
if Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
header Int
byron
then Get (Addr crypto)
forall crypto. Get (Addr crypto)
getByron
else do
Word8
_ <- Get Word8
B.getWord8
let addrNetId :: Word8
addrNetId = Word8
header Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0F
case Word8 -> Maybe Network
word8ToNetwork Word8
addrNetId of
Just Network
n -> Network
-> PaymentCredential crypto -> StakeReference crypto -> Addr crypto
forall crypto.
Network
-> PaymentCredential crypto -> StakeReference crypto -> Addr crypto
Addr Network
n (PaymentCredential crypto -> StakeReference crypto -> Addr crypto)
-> Get (PaymentCredential crypto)
-> Get (StakeReference crypto -> Addr crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Get (PaymentCredential crypto)
forall crypto.
Crypto crypto =>
Word8 -> Get (PaymentCredential crypto)
getPayCred Word8
header Get (StakeReference crypto -> Addr crypto)
-> Get (StakeReference crypto) -> Get (Addr crypto)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Word8 -> Get (StakeReference crypto)
forall crypto.
Crypto crypto =>
Word8 -> Get (StakeReference crypto)
getStakeReference Word8
header
Maybe Network
Nothing ->
String -> Get (Addr crypto)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Addr crypto)) -> String -> Get (Addr crypto)
forall a b. (a -> b) -> a -> b
$
Context -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[String
"Address with unknown network Id. (", Word8 -> String
forall a. Show a => a -> String
show Word8
addrNetId, String
")"]
getAddrStakeReference :: forall crypto. CC.Crypto crypto => Get (Maybe (StakeReference crypto))
getAddrStakeReference :: Get (Maybe (StakeReference crypto))
getAddrStakeReference = do
Word8
header <- Get Word8
B.getWord8
if Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
header Int
byron
then Maybe (StakeReference crypto)
-> Get (Maybe (StakeReference crypto))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (StakeReference crypto)
forall a. Maybe a
Nothing
else [ADDRHASH crypto] -> Get ()
forall (proxy :: * -> *) h. HashAlgorithm h => proxy h -> Get ()
skipHash ([] @(ADDRHASH crypto)) Get ()
-> Get (Maybe (StakeReference crypto))
-> Get (Maybe (StakeReference crypto))
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> StakeReference crypto -> Maybe (StakeReference crypto)
forall a. a -> Maybe a
Just (StakeReference crypto -> Maybe (StakeReference crypto))
-> Get (StakeReference crypto)
-> Get (Maybe (StakeReference crypto))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Get (StakeReference crypto)
forall crypto.
Crypto crypto =>
Word8 -> Get (StakeReference crypto)
getStakeReference Word8
header
putRewardAcnt :: RewardAcnt crypto -> Put
putRewardAcnt :: RewardAcnt crypto -> Put
putRewardAcnt (RewardAcnt Network
network Credential 'Staking crypto
cred) = do
let setPayCredBit :: Word8 -> Word8
setPayCredBit = case Credential 'Staking crypto
cred of
ScriptHashObj ScriptHash crypto
_ -> (Word8 -> Int -> Word8) -> Int -> Word8 -> Word8
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
setBit Int
payCredIsScript
KeyHashObj KeyHash 'Staking crypto
_ -> Word8 -> Word8
forall a. a -> a
id
netId :: Word8
netId = Network -> Word8
networkToWord8 Network
network
rewardAcntPrefix :: Word8
rewardAcntPrefix = Word8
0xE0
header :: Word8
header = Word8 -> Word8
setPayCredBit (Word8
netId Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
rewardAcntPrefix)
Word8 -> Put
B.putWord8 Word8
header
Credential 'Staking crypto -> Put
forall (kr :: KeyRole) crypto. Credential kr crypto -> Put
putCredential Credential 'Staking crypto
cred
getRewardAcnt :: CC.Crypto crypto => Get (RewardAcnt crypto)
getRewardAcnt :: Get (RewardAcnt crypto)
getRewardAcnt = do
Word8
header <- Get Word8
B.getWord8
let rewardAcntPrefix :: Word8
rewardAcntPrefix = Word8
0xE0
isRewardAcnt :: Bool
isRewardAcnt = (Word8
header Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
rewardAcntPrefix) Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
rewardAcntPrefix
netId :: Word8
netId = Word8
header Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0F
case (Word8 -> Maybe Network
word8ToNetwork Word8
netId, Bool
isRewardAcnt) of
(Maybe Network
Nothing, Bool
_) ->
String -> Get (RewardAcnt crypto)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (RewardAcnt crypto))
-> String -> Get (RewardAcnt crypto)
forall a b. (a -> b) -> a -> b
$ Context -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"Reward account with unknown network Id. (", Word8 -> String
forall a. Show a => a -> String
show Word8
netId, String
")"]
(Maybe Network
_, Bool
False) ->
String -> Get (RewardAcnt crypto)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (RewardAcnt crypto))
-> String -> Get (RewardAcnt crypto)
forall a b. (a -> b) -> a -> b
$ Context -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"Expected reward account. Got account with header: ", Word8 -> String
forall a. Show a => a -> String
show Word8
header]
(Just Network
network, Bool
True) -> do
Credential 'Staking crypto
cred <- case Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
header Int
rewardCredIsScript of
Bool
True -> Get (Credential 'Staking crypto)
forall crypto (kr :: KeyRole).
Crypto crypto =>
Get (Credential kr crypto)
getScriptHash
Bool
False -> Get (Credential 'Staking crypto)
forall crypto (kr :: KeyRole).
Crypto crypto =>
Get (Credential kr crypto)
getKeyHash
RewardAcnt crypto -> Get (RewardAcnt crypto)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RewardAcnt crypto -> Get (RewardAcnt crypto))
-> RewardAcnt crypto -> Get (RewardAcnt crypto)
forall a b. (a -> b) -> a -> b
$ Network -> Credential 'Staking crypto -> RewardAcnt crypto
forall crypto.
Network -> Credential 'Staking crypto -> RewardAcnt crypto
RewardAcnt Network
network Credential 'Staking crypto
cred
skipHash :: forall proxy h. Hash.HashAlgorithm h => proxy h -> Get ()
skipHash :: proxy h -> Get ()
skipHash proxy h
p = Int -> Get ()
B.skip (Int -> Get ()) -> (Word -> Int) -> Word -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> Get ()) -> Word -> Get ()
forall a b. (a -> b) -> a -> b
$ proxy h -> Word
forall h (proxy :: * -> *). HashAlgorithm h => proxy h -> Word
Hash.sizeHash proxy h
p
getHash :: forall h a. Hash.HashAlgorithm h => Get (Hash.Hash h a)
getHash :: Get (Hash h a)
getHash = do
ByteString
bytes <- Int -> Get ByteString
B.getByteString (Int -> Get ByteString) -> (Word -> Int) -> Word -> Get ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> Get ByteString) -> Word -> Get ByteString
forall a b. (a -> b) -> a -> b
$ [h] -> Word
forall h (proxy :: * -> *). HashAlgorithm h => proxy h -> Word
Hash.sizeHash ([] @h)
case ByteString -> Maybe (Hash h a)
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Hash.hashFromBytes ByteString
bytes of
Maybe (Hash h a)
Nothing -> String -> Get (Hash h a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"getHash: implausible hash length mismatch"
Just !Hash h a
h -> Hash h a -> Get (Hash h a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Hash h a
h
putHash :: Hash.Hash h a -> Put
putHash :: Hash h a -> Put
putHash = ByteString -> Put
B.putByteString (ByteString -> Put) -> (Hash h a -> ByteString) -> Hash h a -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash h a -> ByteString
forall h a. Hash h a -> ByteString
Hash.hashToBytes
getPayCred :: CC.Crypto crypto => Word8 -> Get (PaymentCredential crypto)
getPayCred :: Word8 -> Get (PaymentCredential crypto)
getPayCred Word8
header = case Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
header Int
payCredIsScript of
Bool
True -> Get (PaymentCredential crypto)
forall crypto (kr :: KeyRole).
Crypto crypto =>
Get (Credential kr crypto)
getScriptHash
Bool
False -> Get (PaymentCredential crypto)
forall crypto (kr :: KeyRole).
Crypto crypto =>
Get (Credential kr crypto)
getKeyHash
getScriptHash :: CC.Crypto crypto => Get (Credential kr crypto)
getScriptHash :: Get (Credential kr crypto)
getScriptHash = ScriptHash crypto -> Credential kr crypto
forall (kr :: KeyRole) crypto.
ScriptHash crypto -> Credential kr crypto
ScriptHashObj (ScriptHash crypto -> Credential kr crypto)
-> (Hash (ADDRHASH crypto) EraIndependentScript
-> ScriptHash crypto)
-> Hash (ADDRHASH crypto) EraIndependentScript
-> Credential kr crypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash (ADDRHASH crypto) EraIndependentScript -> ScriptHash crypto
forall crypto.
Hash (ADDRHASH crypto) EraIndependentScript -> ScriptHash crypto
ScriptHash (Hash (ADDRHASH crypto) EraIndependentScript
-> Credential kr crypto)
-> Get (Hash (ADDRHASH crypto) EraIndependentScript)
-> Get (Credential kr crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Hash (ADDRHASH crypto) EraIndependentScript)
forall h a. HashAlgorithm h => Get (Hash h a)
getHash
getKeyHash :: CC.Crypto crypto => Get (Credential kr crypto)
getKeyHash :: Get (Credential kr crypto)
getKeyHash = KeyHash kr crypto -> Credential kr crypto
forall (kr :: KeyRole) crypto.
KeyHash kr crypto -> Credential kr crypto
KeyHashObj (KeyHash kr crypto -> Credential kr crypto)
-> (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash kr crypto)
-> Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> Credential kr crypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash kr crypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
KeyHash (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> Credential kr crypto)
-> Get (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)))
-> Get (Credential kr crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)))
forall h a. HashAlgorithm h => Get (Hash h a)
getHash
getStakeReference :: CC.Crypto crypto => Word8 -> Get (StakeReference crypto)
getStakeReference :: Word8 -> Get (StakeReference crypto)
getStakeReference Word8
header = case Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
header Int
notBaseAddr of
Bool
True -> case Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
header Int
isEnterpriseAddr of
Bool
True -> StakeReference crypto -> Get (StakeReference crypto)
forall (f :: * -> *) a. Applicative f => a -> f a
pure StakeReference crypto
forall crypto. StakeReference crypto
StakeRefNull
Bool
False -> Ptr -> StakeReference crypto
forall crypto. Ptr -> StakeReference crypto
StakeRefPtr (Ptr -> StakeReference crypto)
-> Get Ptr -> Get (StakeReference crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Ptr
getPtr
Bool
False -> case Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
header Int
stakeCredIsScript of
Bool
True -> StakeCredential crypto -> StakeReference crypto
forall crypto. StakeCredential crypto -> StakeReference crypto
StakeRefBase (StakeCredential crypto -> StakeReference crypto)
-> Get (StakeCredential crypto) -> Get (StakeReference crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (StakeCredential crypto)
forall crypto (kr :: KeyRole).
Crypto crypto =>
Get (Credential kr crypto)
getScriptHash
Bool
False -> StakeCredential crypto -> StakeReference crypto
forall crypto. StakeCredential crypto -> StakeReference crypto
StakeRefBase (StakeCredential crypto -> StakeReference crypto)
-> Get (StakeCredential crypto) -> Get (StakeReference crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (StakeCredential crypto)
forall crypto (kr :: KeyRole).
Crypto crypto =>
Get (Credential kr crypto)
getKeyHash
putCredential :: Credential kr crypto -> Put
putCredential :: Credential kr crypto -> Put
putCredential (ScriptHashObj (ScriptHash Hash (ADDRHASH crypto) EraIndependentScript
h)) = Hash (ADDRHASH crypto) EraIndependentScript -> Put
forall h a. Hash h a -> Put
putHash Hash (ADDRHASH crypto) EraIndependentScript
h
putCredential (KeyHashObj (KeyHash Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
h)) = Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)) -> Put
forall h a. Hash h a -> Put
putHash Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
h
getByron :: Get (Addr crypto)
getByron :: Get (Addr crypto)
getByron =
ByteString -> Either DecoderError Address
forall a. FromCBOR a => ByteString -> Either DecoderError a
decodeFull (ByteString -> Either DecoderError Address)
-> Get ByteString -> Get (Either DecoderError Address)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
B.getRemainingLazyByteString Get (Either DecoderError Address)
-> (Either DecoderError Address -> Get (Addr crypto))
-> Get (Addr crypto)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left DecoderError
e -> String -> Get (Addr crypto)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (DecoderError -> String
forall a. Show a => a -> String
show DecoderError
e)
Right Address
r -> Addr crypto -> Get (Addr crypto)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Addr crypto -> Get (Addr crypto))
-> Addr crypto -> Get (Addr crypto)
forall a b. (a -> b) -> a -> b
$ BootstrapAddress crypto -> Addr crypto
forall crypto. BootstrapAddress crypto -> Addr crypto
AddrBootstrap (BootstrapAddress crypto -> Addr crypto)
-> BootstrapAddress crypto -> Addr crypto
forall a b. (a -> b) -> a -> b
$ Address -> BootstrapAddress crypto
forall crypto. Address -> BootstrapAddress crypto
BootstrapAddress Address
r
bootstrapAddressAttrsSize :: BootstrapAddress crypto -> Int
(BootstrapAddress Address
addr) =
Int -> (HDAddressPayload -> Int) -> Maybe HDAddressPayload -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
Int
0
(ByteString -> Int
BS.length (ByteString -> Int)
-> (HDAddressPayload -> ByteString) -> HDAddressPayload -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HDAddressPayload -> ByteString
Byron.getHDAddressPayload)
(AddrAttributes -> Maybe HDAddressPayload
Byron.aaVKDerivationPath (Attributes AddrAttributes -> AddrAttributes
forall h. Attributes h -> h
Byron.attrData Attributes AddrAttributes
attrs))
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Attributes AddrAttributes -> Int
forall a. Attributes a -> Int
Byron.unknownAttributesLength Attributes AddrAttributes
attrs
where
attrs :: Attributes AddrAttributes
attrs = Address -> Attributes AddrAttributes
Byron.addrAttributes Address
addr
isBootstrapRedeemer :: BootstrapAddress crypto -> Bool
isBootstrapRedeemer :: BootstrapAddress crypto -> Bool
isBootstrapRedeemer (BootstrapAddress (Byron.Address AddressHash Address'
_ Attributes AddrAttributes
_ AddrType
Byron.ATRedeem)) = Bool
True
isBootstrapRedeemer BootstrapAddress crypto
_ = Bool
False
putPtr :: Ptr -> Put
putPtr :: Ptr -> Put
putPtr (Ptr SlotNo
slot (TxIx Word64
txIx) (CertIx Word64
certIx)) = do
SlotNo -> Put
putSlot SlotNo
slot
Word64 -> Put
putVariableLengthWord64 ((Word64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral @_ @Word64) Word64
txIx)
Word64 -> Put
putVariableLengthWord64 ((Word64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral @_ @Word64) Word64
certIx)
where
putSlot :: SlotNo -> Put
putSlot (SlotNo Word64
n) = Word64 -> Put
putVariableLengthWord64 Word64
n
getPtr :: Get Ptr
getPtr :: Get Ptr
getPtr =
SlotNo -> TxIx -> CertIx -> Ptr
Ptr (SlotNo -> TxIx -> CertIx -> Ptr)
-> Get SlotNo -> Get (TxIx -> CertIx -> Ptr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word64 -> SlotNo
SlotNo (Word64 -> SlotNo) -> Get Word64 -> Get SlotNo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getVariableLengthWord64)
Get (TxIx -> CertIx -> Ptr) -> Get TxIx -> Get (CertIx -> Ptr)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Word64 -> TxIx
TxIx (Word64 -> TxIx) -> (Word64 -> Word64) -> Word64 -> TxIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> TxIx) -> Get Word64 -> Get TxIx
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getVariableLengthWord64)
Get (CertIx -> Ptr) -> Get CertIx -> Get Ptr
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Word64 -> CertIx
CertIx (Word64 -> CertIx) -> (Word64 -> Word64) -> Word64 -> CertIx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> CertIx) -> Get Word64 -> Get CertIx
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getVariableLengthWord64)
newtype Word7 = Word7 Word8
deriving (Word7 -> Word7 -> Bool
(Word7 -> Word7 -> Bool) -> (Word7 -> Word7 -> Bool) -> Eq Word7
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word7 -> Word7 -> Bool
$c/= :: Word7 -> Word7 -> Bool
== :: Word7 -> Word7 -> Bool
$c== :: Word7 -> Word7 -> Bool
Eq, Int -> Word7 -> ShowS
[Word7] -> ShowS
Word7 -> String
(Int -> Word7 -> ShowS)
-> (Word7 -> String) -> ([Word7] -> ShowS) -> Show Word7
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word7] -> ShowS
$cshowList :: [Word7] -> ShowS
show :: Word7 -> String
$cshow :: Word7 -> String
showsPrec :: Int -> Word7 -> ShowS
$cshowsPrec :: Int -> Word7 -> ShowS
Show)
toWord7 :: Word8 -> Word7
toWord7 :: Word8 -> Word7
toWord7 Word8
x = Word8 -> Word7
Word7 (Word8
x Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x7F)
putWord7s :: [Word7] -> Put
putWord7s :: [Word7] -> Put
putWord7s [] = () -> Put
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
putWord7s [Word7 Word8
x] = Word8 -> Put
B.putWord8 Word8
x
putWord7s (Word7 Word8
x : [Word7]
xs) = Word8 -> Put
B.putWord8 (Word8
x Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
0x80) Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Word7] -> Put
putWord7s [Word7]
xs
getWord7s :: Get [Word7]
getWord7s :: Get [Word7]
getWord7s = do
Word8
next <- Get Word8
B.getWord8
if Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
next Int
7
then
(:) (Word8 -> Word7
toWord7 Word8
next) ([Word7] -> [Word7]) -> Get [Word7] -> Get [Word7]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Word7]
getWord7s
else
[Word7] -> Get [Word7]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Word8 -> Word7
Word7 Word8
next]
word64ToWord7s :: Word64 -> [Word7]
word64ToWord7s :: Word64 -> [Word7]
word64ToWord7s = [Word7] -> [Word7]
forall a. [a] -> [a]
reverse ([Word7] -> [Word7]) -> (Word64 -> [Word7]) -> Word64 -> [Word7]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> [Word7]
go
where
go :: Word64 -> [Word7]
go :: Word64 -> [Word7]
go Word64
n
| Word64
n Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
> Word64
0x7F = (Word8 -> Word7
toWord7 (Word8 -> Word7) -> (Word64 -> Word8) -> Word64 -> Word7
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral) Word64
n Word7 -> [Word7] -> [Word7]
forall a. a -> [a] -> [a]
: Word64 -> [Word7]
go (Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
shiftR Word64
n Int
7)
| Bool
otherwise = [Word8 -> Word7
Word7 (Word8 -> Word7) -> (Word64 -> Word8) -> Word64 -> Word7
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word7) -> Word64 -> Word7
forall a b. (a -> b) -> a -> b
$ Word64
n]
putVariableLengthWord64 :: Word64 -> Put
putVariableLengthWord64 :: Word64 -> Put
putVariableLengthWord64 = [Word7] -> Put
putWord7s ([Word7] -> Put) -> (Word64 -> [Word7]) -> Word64 -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> [Word7]
word64ToWord7s
word7sToWord64 :: [Word7] -> Word64
word7sToWord64 :: [Word7] -> Word64
word7sToWord64 = (Word64 -> Word7 -> Word64) -> Word64 -> [Word7] -> Word64
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Word64 -> Word7 -> Word64
forall a. (Bits a, Num a) => a -> Word7 -> a
f Word64
0
where
f :: a -> Word7 -> a
f a
n (Word7 Word8
r) = a -> Int -> a
forall a. Bits a => a -> Int -> a
shiftL a
n Int
7 a -> a -> a
forall a. Bits a => a -> a -> a
.|. Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
r
getVariableLengthWord64 :: Get Word64
getVariableLengthWord64 :: Get Word64
getVariableLengthWord64 = [Word7] -> Word64
word7sToWord64 ([Word7] -> Word64) -> Get [Word7] -> Get Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Word7]
getWord7s
decoderFromGet :: Text -> Get a -> Decoder s a
decoderFromGet :: Text -> Get a -> Decoder s a
decoderFromGet Text
name Get a
get = do
ByteString
bytes <- Decoder s ByteString
forall a s. FromCBOR a => Decoder s a
fromCBOR
case Get a
-> ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
forall a.
Get a
-> ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
B.runGetOrFail Get a
get ByteString
bytes of
Right (ByteString
_remaining, ByteOffset
_offset, a
value) -> a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
value
Left (ByteString
_remaining, ByteOffset
_offset, String
message) ->
DecoderError -> Decoder s a
forall e s a. Buildable e => e -> Decoder s a
cborError (Text -> Text -> DecoderError
DecoderErrorCustom Text
name (Text -> DecoderError) -> Text -> DecoderError
forall a b. (a -> b) -> a -> b
$ String -> Text
forall a. IsString a => String -> a
fromString String
message)
instance CC.Crypto crypto => ToCBOR (Addr crypto) where
toCBOR :: Addr crypto -> Encoding
toCBOR = ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (ByteString -> Encoding)
-> (Addr crypto -> ByteString) -> Addr crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
B.runPut (Put -> ByteString)
-> (Addr crypto -> Put) -> Addr crypto -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Addr crypto -> Put
forall crypto. Addr crypto -> Put
putAddr
instance CC.Crypto crypto => FromCBOR (Addr crypto) where
fromCBOR :: Decoder s (Addr crypto)
fromCBOR = Text -> Get (Addr crypto) -> Decoder s (Addr crypto)
forall a s. Text -> Get a -> Decoder s a
decoderFromGet Text
"Addr" Get (Addr crypto)
forall crypto. Crypto crypto => Get (Addr crypto)
getAddr
instance CC.Crypto crypto => ToCBOR (RewardAcnt crypto) where
toCBOR :: RewardAcnt crypto -> Encoding
toCBOR = ByteString -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR (ByteString -> Encoding)
-> (RewardAcnt crypto -> ByteString)
-> RewardAcnt crypto
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
B.runPut (Put -> ByteString)
-> (RewardAcnt crypto -> Put) -> RewardAcnt crypto -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RewardAcnt crypto -> Put
forall crypto. RewardAcnt crypto -> Put
putRewardAcnt
instance CC.Crypto crypto => FromCBOR (RewardAcnt crypto) where
fromCBOR :: Decoder s (RewardAcnt crypto)
fromCBOR = Text -> Get (RewardAcnt crypto) -> Decoder s (RewardAcnt crypto)
forall a s. Text -> Get a -> Decoder s a
decoderFromGet Text
"RewardAcnt" Get (RewardAcnt crypto)
forall crypto. Crypto crypto => Get (RewardAcnt crypto)
getRewardAcnt
newtype BootstrapAddress crypto = BootstrapAddress
{ BootstrapAddress crypto -> Address
unBootstrapAddress :: Byron.Address
}
deriving (BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
(BootstrapAddress crypto -> BootstrapAddress crypto -> Bool)
-> (BootstrapAddress crypto -> BootstrapAddress crypto -> Bool)
-> Eq (BootstrapAddress crypto)
forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
$c/= :: forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
== :: BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
$c== :: forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
Eq, (forall x.
BootstrapAddress crypto -> Rep (BootstrapAddress crypto) x)
-> (forall x.
Rep (BootstrapAddress crypto) x -> BootstrapAddress crypto)
-> Generic (BootstrapAddress crypto)
forall x.
Rep (BootstrapAddress crypto) x -> BootstrapAddress crypto
forall x.
BootstrapAddress crypto -> Rep (BootstrapAddress crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x.
Rep (BootstrapAddress crypto) x -> BootstrapAddress crypto
forall crypto x.
BootstrapAddress crypto -> Rep (BootstrapAddress crypto) x
$cto :: forall crypto x.
Rep (BootstrapAddress crypto) x -> BootstrapAddress crypto
$cfrom :: forall crypto x.
BootstrapAddress crypto -> Rep (BootstrapAddress crypto) x
Generic)
deriving newtype (BootstrapAddress crypto -> ()
(BootstrapAddress crypto -> ()) -> NFData (BootstrapAddress crypto)
forall crypto. BootstrapAddress crypto -> ()
forall a. (a -> ()) -> NFData a
rnf :: BootstrapAddress crypto -> ()
$crnf :: forall crypto. BootstrapAddress crypto -> ()
NFData, Eq (BootstrapAddress crypto)
Eq (BootstrapAddress crypto)
-> (BootstrapAddress crypto -> BootstrapAddress crypto -> Ordering)
-> (BootstrapAddress crypto -> BootstrapAddress crypto -> Bool)
-> (BootstrapAddress crypto -> BootstrapAddress crypto -> Bool)
-> (BootstrapAddress crypto -> BootstrapAddress crypto -> Bool)
-> (BootstrapAddress crypto -> BootstrapAddress crypto -> Bool)
-> (BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto)
-> (BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto)
-> Ord (BootstrapAddress crypto)
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
BootstrapAddress crypto -> BootstrapAddress crypto -> Ordering
BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto
forall crypto. Eq (BootstrapAddress crypto)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Ordering
forall crypto.
BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto
min :: BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto
$cmin :: forall crypto.
BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto
max :: BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto
$cmax :: forall crypto.
BootstrapAddress crypto
-> BootstrapAddress crypto -> BootstrapAddress crypto
>= :: BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
$c>= :: forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
> :: BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
$c> :: forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
<= :: BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
$c<= :: forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
< :: BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
$c< :: forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Bool
compare :: BootstrapAddress crypto -> BootstrapAddress crypto -> Ordering
$ccompare :: forall crypto.
BootstrapAddress crypto -> BootstrapAddress crypto -> Ordering
$cp1Ord :: forall crypto. Eq (BootstrapAddress crypto)
Ord)
deriving (Int -> BootstrapAddress crypto -> ShowS
[BootstrapAddress crypto] -> ShowS
BootstrapAddress crypto -> String
(Int -> BootstrapAddress crypto -> ShowS)
-> (BootstrapAddress crypto -> String)
-> ([BootstrapAddress crypto] -> ShowS)
-> Show (BootstrapAddress crypto)
forall crypto. Int -> BootstrapAddress crypto -> ShowS
forall crypto. [BootstrapAddress crypto] -> ShowS
forall crypto. BootstrapAddress crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BootstrapAddress crypto] -> ShowS
$cshowList :: forall crypto. [BootstrapAddress crypto] -> ShowS
show :: BootstrapAddress crypto -> String
$cshow :: forall crypto. BootstrapAddress crypto -> String
showsPrec :: Int -> BootstrapAddress crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> BootstrapAddress crypto -> ShowS
Show) via Quiet (BootstrapAddress crypto)
instance NoThunks (BootstrapAddress crypto)
bootstrapKeyHash ::
forall crypto.
CC.Crypto crypto =>
BootstrapAddress crypto ->
KeyHash 'Payment crypto
bootstrapKeyHash :: BootstrapAddress crypto -> KeyHash 'Payment crypto
bootstrapKeyHash (BootstrapAddress Address
byronAddress) =
let root :: AddressHash Address'
root = Address -> AddressHash Address'
Byron.addrRoot Address
byronAddress
bytes :: ByteString
bytes = AddressHash Address' -> ByteString
forall algo a. AbstractHash algo a -> ByteString
Byron.abstractHashToBytes AddressHash Address'
root
!hash :: Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
hash =
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> Maybe (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)))
-> Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
forall a. a -> Maybe a -> a
fromMaybe (Text -> Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
forall a. HasCallStack => Text -> a
panic Text
"bootstrapKeyHash: incorrect hash length") (Maybe (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)))
-> Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)))
-> Maybe (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)))
-> Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
forall a b. (a -> b) -> a -> b
$
ByteString
-> Maybe (Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto)))
forall h a. HashAlgorithm h => ByteString -> Maybe (Hash h a)
Hash.hashFromBytes ByteString
bytes
in Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash 'Payment crypto
forall (discriminator :: KeyRole) crypto.
Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
-> KeyHash discriminator crypto
KeyHash Hash (ADDRHASH crypto) (VerKeyDSIGN (DSIGN crypto))
hash