{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
module Cardano.Api.Address (
Address(..),
ByronAddr,
makeByronAddress,
ShelleyAddr,
makeShelleyAddress,
PaymentCredential(..),
StakeAddressReference(..),
StakeAddressPointer(..),
AddressAny(..),
lexPlausibleAddressString,
parseAddressAny,
AddressInEra(..),
AddressTypeInEra(..),
byronAddressInEra,
shelleyAddressInEra,
anyAddressInShelleyBasedEra,
anyAddressInEra,
toAddressAny,
makeByronAddressInEra,
makeShelleyAddressInEra,
StakeAddress(..),
StakeCredential(..),
makeStakeAddress,
StakeKey,
StakeExtendedKey,
shelleyPayAddrToPlutusPubKHash,
toShelleyAddr,
toShelleyStakeAddr,
toShelleyStakeCredential,
fromShelleyAddr,
fromShelleyAddrIsSbe,
fromShelleyAddrToAny,
fromShelleyPaymentCredential,
fromShelleyStakeAddr,
fromShelleyStakeCredential,
fromShelleyStakeReference,
SerialiseAddress(..),
AsType(AsByronAddr, AsShelleyAddr, AsByronAddress, AsShelleyAddress,
AsAddress, AsAddressAny, AsAddressInEra, AsStakeAddress),
isKeyAddress
) where
import Prelude
import Control.Applicative ((<|>))
import Data.Aeson (FromJSON (..), ToJSON (..), withText, (.=))
import qualified Data.Aeson as Aeson
import qualified Data.ByteString.Base58 as Base58
import Data.Char (isAsciiLower, isAsciiUpper, isDigit)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Text.Parsec as Parsec
import qualified Text.Parsec.String as Parsec
import qualified Cardano.Chain.Common as Byron
import qualified Cardano.Ledger.Address as Shelley
import qualified Cardano.Ledger.Alonzo.TxInfo as Alonzo
import qualified Cardano.Ledger.BaseTypes as Shelley
import qualified Cardano.Ledger.Credential as Shelley
import Cardano.Ledger.Crypto (StandardCrypto)
import qualified Plutus.V1.Ledger.Api as Plutus
import Cardano.Api.EraCast
import Cardano.Api.Eras
import Cardano.Api.Hash
import Cardano.Api.HasTypeProxy
import Cardano.Api.Key
import Cardano.Api.KeysByron
import Cardano.Api.KeysShelley
import Cardano.Api.NetworkId
import Cardano.Api.Script
import Cardano.Api.SerialiseBech32
import Cardano.Api.SerialiseRaw
import Cardano.Api.Utils
class HasTypeProxy addr => SerialiseAddress addr where
serialiseAddress :: addr -> Text
deserialiseAddress :: AsType addr -> Text -> Maybe addr
data ByronAddr
data ShelleyAddr
instance HasTypeProxy ByronAddr where
data AsType ByronAddr = AsByronAddr
proxyToAsType :: Proxy ByronAddr -> AsType ByronAddr
proxyToAsType Proxy ByronAddr
_ = AsType ByronAddr
AsByronAddr
instance HasTypeProxy ShelleyAddr where
data AsType ShelleyAddr = AsShelleyAddr
proxyToAsType :: Proxy ShelleyAddr -> AsType ShelleyAddr
proxyToAsType Proxy ShelleyAddr
_ = AsType ShelleyAddr
AsShelleyAddr
data Address addrtype where
ByronAddress
:: Byron.Address
-> Address ByronAddr
ShelleyAddress
:: Shelley.Network
-> Shelley.PaymentCredential StandardCrypto
-> Shelley.StakeReference StandardCrypto
-> Address ShelleyAddr
deriving instance Eq (Address addrtype)
deriving instance Ord (Address addrtype)
deriving instance Show (Address addrtype)
instance HasTypeProxy addrtype => HasTypeProxy (Address addrtype) where
data AsType (Address addrtype) = AsAddress (AsType addrtype)
proxyToAsType :: Proxy (Address addrtype) -> AsType (Address addrtype)
proxyToAsType Proxy (Address addrtype)
_ = AsType addrtype -> AsType (Address addrtype)
forall addrtype. AsType addrtype -> AsType (Address addrtype)
AsAddress (Proxy addrtype -> AsType addrtype
forall t. HasTypeProxy t => Proxy t -> AsType t
proxyToAsType (Proxy addrtype
forall k (t :: k). Proxy t
Proxy :: Proxy addrtype))
pattern AsByronAddress :: AsType (Address ByronAddr)
pattern $bAsByronAddress :: AsType (Address ByronAddr)
$mAsByronAddress :: forall r.
AsType (Address ByronAddr) -> (Void# -> r) -> (Void# -> r) -> r
AsByronAddress = AsAddress AsByronAddr
{-# COMPLETE AsByronAddress #-}
pattern AsShelleyAddress :: AsType (Address ShelleyAddr)
pattern $bAsShelleyAddress :: AsType (Address ShelleyAddr)
$mAsShelleyAddress :: forall r.
AsType (Address ShelleyAddr) -> (Void# -> r) -> (Void# -> r) -> r
AsShelleyAddress = AsAddress AsShelleyAddr
{-# COMPLETE AsShelleyAddress #-}
instance SerialiseAsRawBytes (Address ByronAddr) where
serialiseToRawBytes :: Address ByronAddr -> ByteString
serialiseToRawBytes (ByronAddress Address
addr) =
Addr Any -> ByteString
forall crypto. Addr crypto -> ByteString
Shelley.serialiseAddr
(Addr Any -> ByteString)
-> (Address -> Addr Any) -> Address -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BootstrapAddress Any -> Addr Any
forall crypto. BootstrapAddress crypto -> Addr crypto
Shelley.AddrBootstrap
(BootstrapAddress Any -> Addr Any)
-> (Address -> BootstrapAddress Any) -> Address -> Addr Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> BootstrapAddress Any
forall crypto. Address -> BootstrapAddress crypto
Shelley.BootstrapAddress
(Address -> ByteString) -> Address -> ByteString
forall a b. (a -> b) -> a -> b
$ Address
addr
deserialiseFromRawBytes :: AsType (Address ByronAddr)
-> ByteString -> Maybe (Address ByronAddr)
deserialiseFromRawBytes (AsAddress AsByronAddr) ByteString
bs =
case ByteString -> Maybe (Addr StandardCrypto)
forall crypto. Crypto crypto => ByteString -> Maybe (Addr crypto)
Shelley.deserialiseAddr ByteString
bs :: Maybe (Shelley.Addr StandardCrypto) of
Maybe (Addr StandardCrypto)
Nothing -> Maybe (Address ByronAddr)
forall a. Maybe a
Nothing
Just Shelley.Addr{} -> Maybe (Address ByronAddr)
forall a. Maybe a
Nothing
Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress Address
addr)) ->
Address ByronAddr -> Maybe (Address ByronAddr)
forall a. a -> Maybe a
Just (Address -> Address ByronAddr
ByronAddress Address
addr)
instance SerialiseAsRawBytes (Address ShelleyAddr) where
serialiseToRawBytes :: Address ShelleyAddr -> ByteString
serialiseToRawBytes (ShelleyAddress Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) =
Addr StandardCrypto -> ByteString
forall crypto. Addr crypto -> ByteString
Shelley.serialiseAddr (Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Addr StandardCrypto
forall crypto.
Network
-> PaymentCredential crypto -> StakeReference crypto -> Addr crypto
Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr)
deserialiseFromRawBytes :: AsType (Address ShelleyAddr)
-> ByteString -> Maybe (Address ShelleyAddr)
deserialiseFromRawBytes (AsAddress AsShelleyAddr) ByteString
bs =
case ByteString -> Maybe (Addr StandardCrypto)
forall crypto. Crypto crypto => ByteString -> Maybe (Addr crypto)
Shelley.deserialiseAddr ByteString
bs of
Maybe (Addr StandardCrypto)
Nothing -> Maybe (Address ShelleyAddr)
forall a. Maybe a
Nothing
Just Shelley.AddrBootstrap{} -> Maybe (Address ShelleyAddr)
forall a. Maybe a
Nothing
Just (Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) -> Address ShelleyAddr -> Maybe (Address ShelleyAddr)
forall a. a -> Maybe a
Just (Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Address ShelleyAddr
ShelleyAddress Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr)
instance SerialiseAsBech32 (Address ShelleyAddr) where
bech32PrefixFor :: Address ShelleyAddr -> Text
bech32PrefixFor (ShelleyAddress Network
Shelley.Mainnet PaymentCredential StandardCrypto
_ StakeReference StandardCrypto
_) = Text
"addr"
bech32PrefixFor (ShelleyAddress Network
Shelley.Testnet PaymentCredential StandardCrypto
_ StakeReference StandardCrypto
_) = Text
"addr_test"
bech32PrefixesPermitted :: AsType (Address ShelleyAddr) -> [Text]
bech32PrefixesPermitted (AsAddress AsShelleyAddr) = [Text
"addr", Text
"addr_test"]
instance SerialiseAddress (Address ByronAddr) where
serialiseAddress :: Address ByronAddr -> Text
serialiseAddress addr :: Address ByronAddr
addr@ByronAddress{} =
ByteString -> Text
Text.decodeLatin1
(ByteString -> Text)
-> (Address ByronAddr -> ByteString) -> Address ByronAddr -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Alphabet -> ByteString -> ByteString
Base58.encodeBase58 Alphabet
Base58.bitcoinAlphabet
(ByteString -> ByteString)
-> (Address ByronAddr -> ByteString)
-> Address ByronAddr
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address ByronAddr -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes
(Address ByronAddr -> Text) -> Address ByronAddr -> Text
forall a b. (a -> b) -> a -> b
$ Address ByronAddr
addr
deserialiseAddress :: AsType (Address ByronAddr) -> Text -> Maybe (Address ByronAddr)
deserialiseAddress (AsAddress AsByronAddr) Text
txt = do
ByteString
bs <- Alphabet -> ByteString -> Maybe ByteString
Base58.decodeBase58 Alphabet
Base58.bitcoinAlphabet (Text -> ByteString
Text.encodeUtf8 Text
txt)
AsType (Address ByronAddr)
-> ByteString -> Maybe (Address ByronAddr)
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Maybe a
deserialiseFromRawBytes (AsType ByronAddr -> AsType (Address ByronAddr)
forall addrtype. AsType addrtype -> AsType (Address addrtype)
AsAddress AsType ByronAddr
AsByronAddr) ByteString
bs
instance SerialiseAddress (Address ShelleyAddr) where
serialiseAddress :: Address ShelleyAddr -> Text
serialiseAddress addr :: Address ShelleyAddr
addr@ShelleyAddress{} =
Address ShelleyAddr -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 Address ShelleyAddr
addr
deserialiseAddress :: AsType (Address ShelleyAddr) -> Text -> Maybe (Address ShelleyAddr)
deserialiseAddress (AsAddress AsShelleyAddr) Text
t =
(Bech32DecodeError -> Maybe (Address ShelleyAddr))
-> (Address ShelleyAddr -> Maybe (Address ShelleyAddr))
-> Either Bech32DecodeError (Address ShelleyAddr)
-> Maybe (Address ShelleyAddr)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (Address ShelleyAddr)
-> Bech32DecodeError -> Maybe (Address ShelleyAddr)
forall a b. a -> b -> a
const Maybe (Address ShelleyAddr)
forall a. Maybe a
Nothing) Address ShelleyAddr -> Maybe (Address ShelleyAddr)
forall a. a -> Maybe a
Just (Either Bech32DecodeError (Address ShelleyAddr)
-> Maybe (Address ShelleyAddr))
-> Either Bech32DecodeError (Address ShelleyAddr)
-> Maybe (Address ShelleyAddr)
forall a b. (a -> b) -> a -> b
$
AsType (Address ShelleyAddr)
-> Text -> Either Bech32DecodeError (Address ShelleyAddr)
forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 (AsType ShelleyAddr -> AsType (Address ShelleyAddr)
forall addrtype. AsType addrtype -> AsType (Address addrtype)
AsAddress AsType ShelleyAddr
AsShelleyAddr) Text
t
makeByronAddress :: NetworkId
-> VerificationKey ByronKey
-> Address ByronAddr
makeByronAddress :: NetworkId -> VerificationKey ByronKey -> Address ByronAddr
makeByronAddress NetworkId
nw (ByronVerificationKey vk) =
Address -> Address ByronAddr
ByronAddress (Address -> Address ByronAddr) -> Address -> Address ByronAddr
forall a b. (a -> b) -> a -> b
$
NetworkMagic -> VerificationKey -> Address
Byron.makeVerKeyAddress
(NetworkId -> NetworkMagic
toByronNetworkMagic NetworkId
nw)
VerificationKey
vk
makeShelleyAddress :: NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
makeShelleyAddress :: NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
makeShelleyAddress NetworkId
nw PaymentCredential
pc StakeAddressReference
scr =
Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Address ShelleyAddr
ShelleyAddress
(NetworkId -> Network
toShelleyNetwork NetworkId
nw)
(PaymentCredential -> PaymentCredential StandardCrypto
toShelleyPaymentCredential PaymentCredential
pc)
(StakeAddressReference -> StakeReference StandardCrypto
toShelleyStakeReference StakeAddressReference
scr)
data AddressAny = AddressByron !(Address ByronAddr)
| AddressShelley !(Address ShelleyAddr)
deriving (AddressAny -> AddressAny -> Bool
(AddressAny -> AddressAny -> Bool)
-> (AddressAny -> AddressAny -> Bool) -> Eq AddressAny
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressAny -> AddressAny -> Bool
$c/= :: AddressAny -> AddressAny -> Bool
== :: AddressAny -> AddressAny -> Bool
$c== :: AddressAny -> AddressAny -> Bool
Eq, Eq AddressAny
Eq AddressAny
-> (AddressAny -> AddressAny -> Ordering)
-> (AddressAny -> AddressAny -> Bool)
-> (AddressAny -> AddressAny -> Bool)
-> (AddressAny -> AddressAny -> Bool)
-> (AddressAny -> AddressAny -> Bool)
-> (AddressAny -> AddressAny -> AddressAny)
-> (AddressAny -> AddressAny -> AddressAny)
-> Ord AddressAny
AddressAny -> AddressAny -> Bool
AddressAny -> AddressAny -> Ordering
AddressAny -> AddressAny -> AddressAny
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
min :: AddressAny -> AddressAny -> AddressAny
$cmin :: AddressAny -> AddressAny -> AddressAny
max :: AddressAny -> AddressAny -> AddressAny
$cmax :: AddressAny -> AddressAny -> AddressAny
>= :: AddressAny -> AddressAny -> Bool
$c>= :: AddressAny -> AddressAny -> Bool
> :: AddressAny -> AddressAny -> Bool
$c> :: AddressAny -> AddressAny -> Bool
<= :: AddressAny -> AddressAny -> Bool
$c<= :: AddressAny -> AddressAny -> Bool
< :: AddressAny -> AddressAny -> Bool
$c< :: AddressAny -> AddressAny -> Bool
compare :: AddressAny -> AddressAny -> Ordering
$ccompare :: AddressAny -> AddressAny -> Ordering
$cp1Ord :: Eq AddressAny
Ord, Int -> AddressAny -> ShowS
[AddressAny] -> ShowS
AddressAny -> String
(Int -> AddressAny -> ShowS)
-> (AddressAny -> String)
-> ([AddressAny] -> ShowS)
-> Show AddressAny
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressAny] -> ShowS
$cshowList :: [AddressAny] -> ShowS
show :: AddressAny -> String
$cshow :: AddressAny -> String
showsPrec :: Int -> AddressAny -> ShowS
$cshowsPrec :: Int -> AddressAny -> ShowS
Show)
instance HasTypeProxy AddressAny where
data AsType AddressAny = AsAddressAny
proxyToAsType :: Proxy AddressAny -> AsType AddressAny
proxyToAsType Proxy AddressAny
_ = AsType AddressAny
AsAddressAny
instance SerialiseAsRawBytes AddressAny where
serialiseToRawBytes :: AddressAny -> ByteString
serialiseToRawBytes (AddressByron Address ByronAddr
addr) = Address ByronAddr -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes Address ByronAddr
addr
serialiseToRawBytes (AddressShelley Address ShelleyAddr
addr) = Address ShelleyAddr -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes Address ShelleyAddr
addr
deserialiseFromRawBytes :: AsType AddressAny -> ByteString -> Maybe AddressAny
deserialiseFromRawBytes AsType AddressAny
AsAddressAny ByteString
bs =
case ByteString -> Maybe (Addr StandardCrypto)
forall crypto. Crypto crypto => ByteString -> Maybe (Addr crypto)
Shelley.deserialiseAddr ByteString
bs of
Maybe (Addr StandardCrypto)
Nothing -> Maybe AddressAny
forall a. Maybe a
Nothing
Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress Address
addr)) ->
AddressAny -> Maybe AddressAny
forall a. a -> Maybe a
Just (Address ByronAddr -> AddressAny
AddressByron (Address -> Address ByronAddr
ByronAddress Address
addr))
Just (Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) ->
AddressAny -> Maybe AddressAny
forall a. a -> Maybe a
Just (Address ShelleyAddr -> AddressAny
AddressShelley (Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Address ShelleyAddr
ShelleyAddress Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr))
instance SerialiseAddress AddressAny where
serialiseAddress :: AddressAny -> Text
serialiseAddress (AddressByron Address ByronAddr
addr) = Address ByronAddr -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress Address ByronAddr
addr
serialiseAddress (AddressShelley Address ShelleyAddr
addr) = Address ShelleyAddr -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress Address ShelleyAddr
addr
deserialiseAddress :: AsType AddressAny -> Text -> Maybe AddressAny
deserialiseAddress AsType AddressAny
AsAddressAny Text
t =
(Address ByronAddr -> AddressAny
AddressByron (Address ByronAddr -> AddressAny)
-> Maybe (Address ByronAddr) -> Maybe AddressAny
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsType (Address ByronAddr) -> Text -> Maybe (Address ByronAddr)
forall addr.
SerialiseAddress addr =>
AsType addr -> Text -> Maybe addr
deserialiseAddress (AsType ByronAddr -> AsType (Address ByronAddr)
forall addrtype. AsType addrtype -> AsType (Address addrtype)
AsAddress AsType ByronAddr
AsByronAddr) Text
t)
Maybe AddressAny -> Maybe AddressAny -> Maybe AddressAny
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Address ShelleyAddr -> AddressAny
AddressShelley (Address ShelleyAddr -> AddressAny)
-> Maybe (Address ShelleyAddr) -> Maybe AddressAny
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsType (Address ShelleyAddr) -> Text -> Maybe (Address ShelleyAddr)
forall addr.
SerialiseAddress addr =>
AsType addr -> Text -> Maybe addr
deserialiseAddress (AsType ShelleyAddr -> AsType (Address ShelleyAddr)
forall addrtype. AsType addrtype -> AsType (Address addrtype)
AsAddress AsType ShelleyAddr
AsShelleyAddr) Text
t)
fromShelleyAddrToAny :: Shelley.Addr StandardCrypto -> AddressAny
fromShelleyAddrToAny :: Addr StandardCrypto -> AddressAny
fromShelleyAddrToAny (Shelley.AddrBootstrap (Shelley.BootstrapAddress Address
addr)) =
Address ByronAddr -> AddressAny
AddressByron (Address ByronAddr -> AddressAny)
-> Address ByronAddr -> AddressAny
forall a b. (a -> b) -> a -> b
$ Address -> Address ByronAddr
ByronAddress Address
addr
fromShelleyAddrToAny (Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) =
Address ShelleyAddr -> AddressAny
AddressShelley (Address ShelleyAddr -> AddressAny)
-> Address ShelleyAddr -> AddressAny
forall a b. (a -> b) -> a -> b
$ Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Address ShelleyAddr
ShelleyAddress Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr
data AddressInEra era where
AddressInEra :: AddressTypeInEra addrtype era
-> Address addrtype
-> AddressInEra era
instance IsCardanoEra era => ToJSON (AddressInEra era) where
toJSON :: AddressInEra era -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value)
-> (AddressInEra era -> Text) -> AddressInEra era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AddressInEra era -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress
instance IsShelleyBasedEra era => FromJSON (AddressInEra era) where
parseJSON :: Value -> Parser (AddressInEra era)
parseJSON = String
-> (Text -> Parser (AddressInEra era))
-> Value
-> Parser (AddressInEra era)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"AddressInEra" ((Text -> Parser (AddressInEra era))
-> Value -> Parser (AddressInEra era))
-> (Text -> Parser (AddressInEra era))
-> Value
-> Parser (AddressInEra era)
forall a b. (a -> b) -> a -> b
$ \Text
txt -> do
AddressAny
addressAny <- Parser AddressAny -> Text -> Parser AddressAny
forall a. Parser a -> Text -> Parser a
runParsecParser Parser AddressAny
parseAddressAny Text
txt
AddressInEra era -> Parser (AddressInEra era)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AddressInEra era -> Parser (AddressInEra era))
-> AddressInEra era -> Parser (AddressInEra era)
forall a b. (a -> b) -> a -> b
$ AddressAny -> AddressInEra era
forall era. IsShelleyBasedEra era => AddressAny -> AddressInEra era
anyAddressInShelleyBasedEra AddressAny
addressAny
instance EraCast AddressInEra where
eraCast :: CardanoEra toEra
-> AddressInEra fromEra -> Either EraCastError (AddressInEra toEra)
eraCast CardanoEra toEra
toEra' (AddressInEra AddressTypeInEra addrtype fromEra
addressTypeInEra Address addrtype
address) = AddressTypeInEra addrtype toEra
-> Address addrtype -> AddressInEra toEra
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra
(AddressTypeInEra addrtype toEra
-> Address addrtype -> AddressInEra toEra)
-> Either EraCastError (AddressTypeInEra addrtype toEra)
-> Either EraCastError (Address addrtype -> AddressInEra toEra)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CardanoEra toEra
-> AddressTypeInEra addrtype fromEra
-> Either EraCastError (AddressTypeInEra addrtype toEra)
forall (f :: * -> *) fromEra toEra.
(EraCast f, IsCardanoEra fromEra, IsCardanoEra toEra) =>
CardanoEra toEra -> f fromEra -> Either EraCastError (f toEra)
eraCast CardanoEra toEra
toEra' AddressTypeInEra addrtype fromEra
addressTypeInEra
Either EraCastError (Address addrtype -> AddressInEra toEra)
-> Either EraCastError (Address addrtype)
-> Either EraCastError (AddressInEra toEra)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Address addrtype -> Either EraCastError (Address addrtype)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Address addrtype
address
parseAddressAny :: Parsec.Parser AddressAny
parseAddressAny :: Parser AddressAny
parseAddressAny = do
Text
str <- Parser Text
lexPlausibleAddressString
case AsType AddressAny -> Text -> Maybe AddressAny
forall addr.
SerialiseAddress addr =>
AsType addr -> Text -> Maybe addr
deserialiseAddress AsType AddressAny
AsAddressAny Text
str of
Maybe AddressAny
Nothing -> String -> Parser AddressAny
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser AddressAny) -> String -> Parser AddressAny
forall a b. (a -> b) -> a -> b
$ String
"invalid address: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
Text.unpack Text
str
Just AddressAny
addr -> AddressAny -> Parser AddressAny
forall (f :: * -> *) a. Applicative f => a -> f a
pure AddressAny
addr
lexPlausibleAddressString :: Parsec.Parser Text
lexPlausibleAddressString :: Parser Text
lexPlausibleAddressString =
String -> Text
Text.pack (String -> Text)
-> ParsecT String () Identity String -> Parser Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String () Identity Char
-> ParsecT String () Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
Parsec.many1 ((Char -> Bool) -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
Parsec.satisfy Char -> Bool
isPlausibleAddressChar)
where
isPlausibleAddressChar :: Char -> Bool
isPlausibleAddressChar Char
c =
Char -> Bool
isAsciiLower Char
c
Bool -> Bool -> Bool
|| Char -> Bool
isAsciiUpper Char
c
Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
c
Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'
instance Eq (AddressInEra era) where
== :: AddressInEra era -> AddressInEra era -> Bool
(==) (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
addr1)
(AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
addr2) = Address addrtype
addr1 Address addrtype -> Address addrtype -> Bool
forall a. Eq a => a -> a -> Bool
== Address addrtype
Address addrtype
addr2
(==) (AddressInEra ShelleyAddressInEra{} Address addrtype
addr1)
(AddressInEra ShelleyAddressInEra{} Address addrtype
addr2) = Address addrtype
addr1 Address addrtype -> Address addrtype -> Bool
forall a. Eq a => a -> a -> Bool
== Address addrtype
Address addrtype
addr2
(==) (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
_)
(AddressInEra ShelleyAddressInEra{} Address addrtype
_) = Bool
False
(==) (AddressInEra ShelleyAddressInEra{} Address addrtype
_)
(AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
_) = Bool
False
deriving instance Show (AddressInEra era)
data AddressTypeInEra addrtype era where
ByronAddressInAnyEra :: AddressTypeInEra ByronAddr era
ShelleyAddressInEra :: ShelleyBasedEra era
-> AddressTypeInEra ShelleyAddr era
deriving instance Show (AddressTypeInEra addrtype era)
instance HasTypeProxy era => HasTypeProxy (AddressInEra era) where
data AsType (AddressInEra era) = AsAddressInEra (AsType era)
proxyToAsType :: Proxy (AddressInEra era) -> AsType (AddressInEra era)
proxyToAsType Proxy (AddressInEra era)
_ = AsType era -> AsType (AddressInEra era)
forall era. AsType era -> AsType (AddressInEra era)
AsAddressInEra (Proxy era -> AsType era
forall t. HasTypeProxy t => Proxy t -> AsType t
proxyToAsType (Proxy era
forall k (t :: k). Proxy t
Proxy :: Proxy era))
instance IsCardanoEra era => SerialiseAsRawBytes (AddressInEra era) where
serialiseToRawBytes :: AddressInEra era -> ByteString
serialiseToRawBytes (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
addr) =
Address addrtype -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes Address addrtype
addr
serialiseToRawBytes (AddressInEra ShelleyAddressInEra{} Address addrtype
addr) =
Address addrtype -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes Address addrtype
addr
deserialiseFromRawBytes :: AsType (AddressInEra era) -> ByteString -> Maybe (AddressInEra era)
deserialiseFromRawBytes AsType (AddressInEra era)
_ ByteString
bs =
CardanoEra era -> AddressAny -> Maybe (AddressInEra era)
forall era.
CardanoEra era -> AddressAny -> Maybe (AddressInEra era)
anyAddressInEra CardanoEra era
forall era. IsCardanoEra era => CardanoEra era
cardanoEra (AddressAny -> Maybe (AddressInEra era))
-> Maybe AddressAny -> Maybe (AddressInEra era)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< AsType AddressAny -> ByteString -> Maybe AddressAny
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Maybe a
deserialiseFromRawBytes AsType AddressAny
AsAddressAny ByteString
bs
instance IsCardanoEra era => SerialiseAddress (AddressInEra era) where
serialiseAddress :: AddressInEra era -> Text
serialiseAddress (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
addr) =
Address addrtype -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress Address addrtype
addr
serialiseAddress (AddressInEra ShelleyAddressInEra{} Address addrtype
addr) =
Address addrtype -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress Address addrtype
addr
deserialiseAddress :: AsType (AddressInEra era) -> Text -> Maybe (AddressInEra era)
deserialiseAddress AsType (AddressInEra era)
_ Text
t =
CardanoEra era -> AddressAny -> Maybe (AddressInEra era)
forall era.
CardanoEra era -> AddressAny -> Maybe (AddressInEra era)
anyAddressInEra CardanoEra era
forall era. IsCardanoEra era => CardanoEra era
cardanoEra (AddressAny -> Maybe (AddressInEra era))
-> Maybe AddressAny -> Maybe (AddressInEra era)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< AsType AddressAny -> Text -> Maybe AddressAny
forall addr.
SerialiseAddress addr =>
AsType addr -> Text -> Maybe addr
deserialiseAddress AsType AddressAny
AsAddressAny Text
t
instance EraCast (AddressTypeInEra addrtype) where
eraCast :: CardanoEra toEra
-> AddressTypeInEra addrtype fromEra
-> Either EraCastError (AddressTypeInEra addrtype toEra)
eraCast CardanoEra toEra
toEra' AddressTypeInEra addrtype fromEra
v = case AddressTypeInEra addrtype fromEra
v of
AddressTypeInEra addrtype fromEra
ByronAddressInAnyEra -> AddressTypeInEra ByronAddr toEra
-> Either EraCastError (AddressTypeInEra ByronAddr toEra)
forall (f :: * -> *) a. Applicative f => a -> f a
pure AddressTypeInEra ByronAddr toEra
forall era. AddressTypeInEra ByronAddr era
ByronAddressInAnyEra
ShelleyAddressInEra ShelleyBasedEra fromEra
previousEra ->
case CardanoEra toEra -> CardanoEraStyle toEra
forall era. CardanoEra era -> CardanoEraStyle era
cardanoEraStyle CardanoEra toEra
toEra' of
CardanoEraStyle toEra
LegacyByronEra -> EraCastError
-> Either EraCastError (AddressTypeInEra addrtype toEra)
forall a b. a -> Either a b
Left (EraCastError
-> Either EraCastError (AddressTypeInEra addrtype toEra))
-> EraCastError
-> Either EraCastError (AddressTypeInEra addrtype toEra)
forall a b. (a -> b) -> a -> b
$ AddressTypeInEra addrtype fromEra
-> CardanoEra fromEra -> CardanoEra toEra -> EraCastError
forall fromEra toEra value.
(IsCardanoEra fromEra, IsCardanoEra toEra, Show value) =>
value -> CardanoEra fromEra -> CardanoEra toEra -> EraCastError
EraCastError AddressTypeInEra addrtype fromEra
v (ShelleyBasedEra fromEra -> CardanoEra fromEra
forall era. ShelleyBasedEra era -> CardanoEra era
shelleyBasedToCardanoEra ShelleyBasedEra fromEra
previousEra) CardanoEra toEra
toEra'
ShelleyBasedEra ShelleyBasedEra toEra
newSbe -> AddressTypeInEra ShelleyAddr toEra
-> Either EraCastError (AddressTypeInEra ShelleyAddr toEra)
forall a b. b -> Either a b
Right (AddressTypeInEra ShelleyAddr toEra
-> Either EraCastError (AddressTypeInEra ShelleyAddr toEra))
-> AddressTypeInEra ShelleyAddr toEra
-> Either EraCastError (AddressTypeInEra ShelleyAddr toEra)
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra toEra -> AddressTypeInEra ShelleyAddr toEra
forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
ShelleyAddressInEra ShelleyBasedEra toEra
newSbe
byronAddressInEra :: Address ByronAddr -> AddressInEra era
byronAddressInEra :: Address ByronAddr -> AddressInEra era
byronAddressInEra = AddressTypeInEra ByronAddr era
-> Address ByronAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra AddressTypeInEra ByronAddr era
forall era. AddressTypeInEra ByronAddr era
ByronAddressInAnyEra
shelleyAddressInEra :: IsShelleyBasedEra era
=> Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra :: Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra = AddressTypeInEra ShelleyAddr era
-> Address ShelleyAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra (ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
ShelleyAddressInEra ShelleyBasedEra era
forall era. IsShelleyBasedEra era => ShelleyBasedEra era
shelleyBasedEra)
anyAddressInShelleyBasedEra :: IsShelleyBasedEra era
=> AddressAny -> AddressInEra era
anyAddressInShelleyBasedEra :: AddressAny -> AddressInEra era
anyAddressInShelleyBasedEra (AddressByron Address ByronAddr
addr) = Address ByronAddr -> AddressInEra era
forall era. Address ByronAddr -> AddressInEra era
byronAddressInEra Address ByronAddr
addr
anyAddressInShelleyBasedEra (AddressShelley Address ShelleyAddr
addr) = Address ShelleyAddr -> AddressInEra era
forall era.
IsShelleyBasedEra era =>
Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra Address ShelleyAddr
addr
anyAddressInEra :: CardanoEra era
-> AddressAny
-> Maybe (AddressInEra era)
anyAddressInEra :: CardanoEra era -> AddressAny -> Maybe (AddressInEra era)
anyAddressInEra CardanoEra era
_ (AddressByron Address ByronAddr
addr) =
AddressInEra era -> Maybe (AddressInEra era)
forall a. a -> Maybe a
Just (AddressTypeInEra ByronAddr era
-> Address ByronAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra AddressTypeInEra ByronAddr era
forall era. AddressTypeInEra ByronAddr era
ByronAddressInAnyEra Address ByronAddr
addr)
anyAddressInEra CardanoEra era
era (AddressShelley Address ShelleyAddr
addr) =
case CardanoEra era -> CardanoEraStyle era
forall era. CardanoEra era -> CardanoEraStyle era
cardanoEraStyle CardanoEra era
era of
CardanoEraStyle era
LegacyByronEra -> Maybe (AddressInEra era)
forall a. Maybe a
Nothing
ShelleyBasedEra ShelleyBasedEra era
era' -> AddressInEra era -> Maybe (AddressInEra era)
forall a. a -> Maybe a
Just (AddressTypeInEra ShelleyAddr era
-> Address ShelleyAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra (ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
ShelleyAddressInEra ShelleyBasedEra era
era') Address ShelleyAddr
addr)
toAddressAny :: Address addr -> AddressAny
toAddressAny :: Address addr -> AddressAny
toAddressAny a :: Address addr
a@ShelleyAddress{} = Address ShelleyAddr -> AddressAny
AddressShelley Address addr
Address ShelleyAddr
a
toAddressAny a :: Address addr
a@ByronAddress{} = Address ByronAddr -> AddressAny
AddressByron Address addr
Address ByronAddr
a
makeByronAddressInEra :: NetworkId
-> VerificationKey ByronKey
-> AddressInEra era
makeByronAddressInEra :: NetworkId -> VerificationKey ByronKey -> AddressInEra era
makeByronAddressInEra NetworkId
nw VerificationKey ByronKey
vk =
Address ByronAddr -> AddressInEra era
forall era. Address ByronAddr -> AddressInEra era
byronAddressInEra (NetworkId -> VerificationKey ByronKey -> Address ByronAddr
makeByronAddress NetworkId
nw VerificationKey ByronKey
vk)
makeShelleyAddressInEra :: IsShelleyBasedEra era
=> NetworkId
-> PaymentCredential
-> StakeAddressReference
-> AddressInEra era
makeShelleyAddressInEra :: NetworkId
-> PaymentCredential -> StakeAddressReference -> AddressInEra era
makeShelleyAddressInEra NetworkId
nw PaymentCredential
pc StakeAddressReference
scr =
Address ShelleyAddr -> AddressInEra era
forall era.
IsShelleyBasedEra era =>
Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra (NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
makeShelleyAddress NetworkId
nw PaymentCredential
pc StakeAddressReference
scr)
data StakeAddress where
StakeAddress
:: Shelley.Network
-> Shelley.StakeCredential StandardCrypto
-> StakeAddress
deriving (StakeAddress -> StakeAddress -> Bool
(StakeAddress -> StakeAddress -> Bool)
-> (StakeAddress -> StakeAddress -> Bool) -> Eq StakeAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakeAddress -> StakeAddress -> Bool
$c/= :: StakeAddress -> StakeAddress -> Bool
== :: StakeAddress -> StakeAddress -> Bool
$c== :: StakeAddress -> StakeAddress -> Bool
Eq, Eq StakeAddress
Eq StakeAddress
-> (StakeAddress -> StakeAddress -> Ordering)
-> (StakeAddress -> StakeAddress -> Bool)
-> (StakeAddress -> StakeAddress -> Bool)
-> (StakeAddress -> StakeAddress -> Bool)
-> (StakeAddress -> StakeAddress -> Bool)
-> (StakeAddress -> StakeAddress -> StakeAddress)
-> (StakeAddress -> StakeAddress -> StakeAddress)
-> Ord StakeAddress
StakeAddress -> StakeAddress -> Bool
StakeAddress -> StakeAddress -> Ordering
StakeAddress -> StakeAddress -> StakeAddress
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
min :: StakeAddress -> StakeAddress -> StakeAddress
$cmin :: StakeAddress -> StakeAddress -> StakeAddress
max :: StakeAddress -> StakeAddress -> StakeAddress
$cmax :: StakeAddress -> StakeAddress -> StakeAddress
>= :: StakeAddress -> StakeAddress -> Bool
$c>= :: StakeAddress -> StakeAddress -> Bool
> :: StakeAddress -> StakeAddress -> Bool
$c> :: StakeAddress -> StakeAddress -> Bool
<= :: StakeAddress -> StakeAddress -> Bool
$c<= :: StakeAddress -> StakeAddress -> Bool
< :: StakeAddress -> StakeAddress -> Bool
$c< :: StakeAddress -> StakeAddress -> Bool
compare :: StakeAddress -> StakeAddress -> Ordering
$ccompare :: StakeAddress -> StakeAddress -> Ordering
$cp1Ord :: Eq StakeAddress
Ord, Int -> StakeAddress -> ShowS
[StakeAddress] -> ShowS
StakeAddress -> String
(Int -> StakeAddress -> ShowS)
-> (StakeAddress -> String)
-> ([StakeAddress] -> ShowS)
-> Show StakeAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakeAddress] -> ShowS
$cshowList :: [StakeAddress] -> ShowS
show :: StakeAddress -> String
$cshow :: StakeAddress -> String
showsPrec :: Int -> StakeAddress -> ShowS
$cshowsPrec :: Int -> StakeAddress -> ShowS
Show)
data PaymentCredential
= PaymentCredentialByKey (Hash PaymentKey)
| PaymentCredentialByScript ScriptHash
deriving (PaymentCredential -> PaymentCredential -> Bool
(PaymentCredential -> PaymentCredential -> Bool)
-> (PaymentCredential -> PaymentCredential -> Bool)
-> Eq PaymentCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentCredential -> PaymentCredential -> Bool
$c/= :: PaymentCredential -> PaymentCredential -> Bool
== :: PaymentCredential -> PaymentCredential -> Bool
$c== :: PaymentCredential -> PaymentCredential -> Bool
Eq, Eq PaymentCredential
Eq PaymentCredential
-> (PaymentCredential -> PaymentCredential -> Ordering)
-> (PaymentCredential -> PaymentCredential -> Bool)
-> (PaymentCredential -> PaymentCredential -> Bool)
-> (PaymentCredential -> PaymentCredential -> Bool)
-> (PaymentCredential -> PaymentCredential -> Bool)
-> (PaymentCredential -> PaymentCredential -> PaymentCredential)
-> (PaymentCredential -> PaymentCredential -> PaymentCredential)
-> Ord PaymentCredential
PaymentCredential -> PaymentCredential -> Bool
PaymentCredential -> PaymentCredential -> Ordering
PaymentCredential -> PaymentCredential -> PaymentCredential
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
min :: PaymentCredential -> PaymentCredential -> PaymentCredential
$cmin :: PaymentCredential -> PaymentCredential -> PaymentCredential
max :: PaymentCredential -> PaymentCredential -> PaymentCredential
$cmax :: PaymentCredential -> PaymentCredential -> PaymentCredential
>= :: PaymentCredential -> PaymentCredential -> Bool
$c>= :: PaymentCredential -> PaymentCredential -> Bool
> :: PaymentCredential -> PaymentCredential -> Bool
$c> :: PaymentCredential -> PaymentCredential -> Bool
<= :: PaymentCredential -> PaymentCredential -> Bool
$c<= :: PaymentCredential -> PaymentCredential -> Bool
< :: PaymentCredential -> PaymentCredential -> Bool
$c< :: PaymentCredential -> PaymentCredential -> Bool
compare :: PaymentCredential -> PaymentCredential -> Ordering
$ccompare :: PaymentCredential -> PaymentCredential -> Ordering
$cp1Ord :: Eq PaymentCredential
Ord, Int -> PaymentCredential -> ShowS
[PaymentCredential] -> ShowS
PaymentCredential -> String
(Int -> PaymentCredential -> ShowS)
-> (PaymentCredential -> String)
-> ([PaymentCredential] -> ShowS)
-> Show PaymentCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentCredential] -> ShowS
$cshowList :: [PaymentCredential] -> ShowS
show :: PaymentCredential -> String
$cshow :: PaymentCredential -> String
showsPrec :: Int -> PaymentCredential -> ShowS
$cshowsPrec :: Int -> PaymentCredential -> ShowS
Show)
data StakeCredential
= StakeCredentialByKey (Hash StakeKey)
| StakeCredentialByScript ScriptHash
deriving (StakeCredential -> StakeCredential -> Bool
(StakeCredential -> StakeCredential -> Bool)
-> (StakeCredential -> StakeCredential -> Bool)
-> Eq StakeCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakeCredential -> StakeCredential -> Bool
$c/= :: StakeCredential -> StakeCredential -> Bool
== :: StakeCredential -> StakeCredential -> Bool
$c== :: StakeCredential -> StakeCredential -> Bool
Eq, Eq StakeCredential
Eq StakeCredential
-> (StakeCredential -> StakeCredential -> Ordering)
-> (StakeCredential -> StakeCredential -> Bool)
-> (StakeCredential -> StakeCredential -> Bool)
-> (StakeCredential -> StakeCredential -> Bool)
-> (StakeCredential -> StakeCredential -> Bool)
-> (StakeCredential -> StakeCredential -> StakeCredential)
-> (StakeCredential -> StakeCredential -> StakeCredential)
-> Ord StakeCredential
StakeCredential -> StakeCredential -> Bool
StakeCredential -> StakeCredential -> Ordering
StakeCredential -> StakeCredential -> StakeCredential
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
min :: StakeCredential -> StakeCredential -> StakeCredential
$cmin :: StakeCredential -> StakeCredential -> StakeCredential
max :: StakeCredential -> StakeCredential -> StakeCredential
$cmax :: StakeCredential -> StakeCredential -> StakeCredential
>= :: StakeCredential -> StakeCredential -> Bool
$c>= :: StakeCredential -> StakeCredential -> Bool
> :: StakeCredential -> StakeCredential -> Bool
$c> :: StakeCredential -> StakeCredential -> Bool
<= :: StakeCredential -> StakeCredential -> Bool
$c<= :: StakeCredential -> StakeCredential -> Bool
< :: StakeCredential -> StakeCredential -> Bool
$c< :: StakeCredential -> StakeCredential -> Bool
compare :: StakeCredential -> StakeCredential -> Ordering
$ccompare :: StakeCredential -> StakeCredential -> Ordering
$cp1Ord :: Eq StakeCredential
Ord, Int -> StakeCredential -> ShowS
[StakeCredential] -> ShowS
StakeCredential -> String
(Int -> StakeCredential -> ShowS)
-> (StakeCredential -> String)
-> ([StakeCredential] -> ShowS)
-> Show StakeCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakeCredential] -> ShowS
$cshowList :: [StakeCredential] -> ShowS
show :: StakeCredential -> String
$cshow :: StakeCredential -> String
showsPrec :: Int -> StakeCredential -> ShowS
$cshowsPrec :: Int -> StakeCredential -> ShowS
Show)
instance ToJSON StakeCredential where
toJSON :: StakeCredential -> Value
toJSON =
[Pair] -> Value
Aeson.object
([Pair] -> Value)
-> (StakeCredential -> [Pair]) -> StakeCredential -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
StakeCredentialByKey Hash StakeKey
keyHash ->
[Key
"stakingKeyHash" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Hash StakeKey -> Text
forall a. SerialiseAsRawBytes a => a -> Text
serialiseToRawBytesHexText Hash StakeKey
keyHash]
StakeCredentialByScript ScriptHash
scriptHash ->
[Key
"stakingScriptHash" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ScriptHash -> Text
forall a. SerialiseAsRawBytes a => a -> Text
serialiseToRawBytesHexText ScriptHash
scriptHash]
data StakeAddressReference
= StakeAddressByValue StakeCredential
| StakeAddressByPointer StakeAddressPointer
| NoStakeAddress
deriving (StakeAddressReference -> StakeAddressReference -> Bool
(StakeAddressReference -> StakeAddressReference -> Bool)
-> (StakeAddressReference -> StakeAddressReference -> Bool)
-> Eq StakeAddressReference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakeAddressReference -> StakeAddressReference -> Bool
$c/= :: StakeAddressReference -> StakeAddressReference -> Bool
== :: StakeAddressReference -> StakeAddressReference -> Bool
$c== :: StakeAddressReference -> StakeAddressReference -> Bool
Eq, Int -> StakeAddressReference -> ShowS
[StakeAddressReference] -> ShowS
StakeAddressReference -> String
(Int -> StakeAddressReference -> ShowS)
-> (StakeAddressReference -> String)
-> ([StakeAddressReference] -> ShowS)
-> Show StakeAddressReference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakeAddressReference] -> ShowS
$cshowList :: [StakeAddressReference] -> ShowS
show :: StakeAddressReference -> String
$cshow :: StakeAddressReference -> String
showsPrec :: Int -> StakeAddressReference -> ShowS
$cshowsPrec :: Int -> StakeAddressReference -> ShowS
Show)
newtype StakeAddressPointer = StakeAddressPointer
{ StakeAddressPointer -> Ptr
unStakeAddressPointer :: Shelley.Ptr
}
deriving (StakeAddressPointer -> StakeAddressPointer -> Bool
(StakeAddressPointer -> StakeAddressPointer -> Bool)
-> (StakeAddressPointer -> StakeAddressPointer -> Bool)
-> Eq StakeAddressPointer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakeAddressPointer -> StakeAddressPointer -> Bool
$c/= :: StakeAddressPointer -> StakeAddressPointer -> Bool
== :: StakeAddressPointer -> StakeAddressPointer -> Bool
$c== :: StakeAddressPointer -> StakeAddressPointer -> Bool
Eq, Int -> StakeAddressPointer -> ShowS
[StakeAddressPointer] -> ShowS
StakeAddressPointer -> String
(Int -> StakeAddressPointer -> ShowS)
-> (StakeAddressPointer -> String)
-> ([StakeAddressPointer] -> ShowS)
-> Show StakeAddressPointer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakeAddressPointer] -> ShowS
$cshowList :: [StakeAddressPointer] -> ShowS
show :: StakeAddressPointer -> String
$cshow :: StakeAddressPointer -> String
showsPrec :: Int -> StakeAddressPointer -> ShowS
$cshowsPrec :: Int -> StakeAddressPointer -> ShowS
Show)
instance HasTypeProxy StakeAddress where
data AsType StakeAddress = AsStakeAddress
proxyToAsType :: Proxy StakeAddress -> AsType StakeAddress
proxyToAsType Proxy StakeAddress
_ = AsType StakeAddress
AsStakeAddress
instance SerialiseAsRawBytes StakeAddress where
serialiseToRawBytes :: StakeAddress -> ByteString
serialiseToRawBytes (StakeAddress Network
nw StakeCredential StandardCrypto
sc) =
RewardAcnt StandardCrypto -> ByteString
forall crypto. RewardAcnt crypto -> ByteString
Shelley.serialiseRewardAcnt (Network
-> StakeCredential StandardCrypto -> RewardAcnt StandardCrypto
forall crypto.
Network -> Credential 'Staking crypto -> RewardAcnt crypto
Shelley.RewardAcnt Network
nw StakeCredential StandardCrypto
sc)
deserialiseFromRawBytes :: AsType StakeAddress -> ByteString -> Maybe StakeAddress
deserialiseFromRawBytes AsType StakeAddress
AsStakeAddress ByteString
bs =
case ByteString -> Maybe (RewardAcnt StandardCrypto)
forall crypto.
Crypto crypto =>
ByteString -> Maybe (RewardAcnt crypto)
Shelley.deserialiseRewardAcnt ByteString
bs of
Maybe (RewardAcnt StandardCrypto)
Nothing -> Maybe StakeAddress
forall a. Maybe a
Nothing
Just (Shelley.RewardAcnt Network
nw StakeCredential StandardCrypto
sc) -> StakeAddress -> Maybe StakeAddress
forall a. a -> Maybe a
Just (Network -> StakeCredential StandardCrypto -> StakeAddress
StakeAddress Network
nw StakeCredential StandardCrypto
sc)
instance SerialiseAsBech32 StakeAddress where
bech32PrefixFor :: StakeAddress -> Text
bech32PrefixFor (StakeAddress Network
Shelley.Mainnet StakeCredential StandardCrypto
_) = Text
"stake"
bech32PrefixFor (StakeAddress Network
Shelley.Testnet StakeCredential StandardCrypto
_) = Text
"stake_test"
bech32PrefixesPermitted :: AsType StakeAddress -> [Text]
bech32PrefixesPermitted AsType StakeAddress
AsStakeAddress = [Text
"stake", Text
"stake_test"]
instance SerialiseAddress StakeAddress where
serialiseAddress :: StakeAddress -> Text
serialiseAddress addr :: StakeAddress
addr@StakeAddress{} =
StakeAddress -> Text
forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 StakeAddress
addr
deserialiseAddress :: AsType StakeAddress -> Text -> Maybe StakeAddress
deserialiseAddress AsType StakeAddress
AsStakeAddress Text
t =
(Bech32DecodeError -> Maybe StakeAddress)
-> (StakeAddress -> Maybe StakeAddress)
-> Either Bech32DecodeError StakeAddress
-> Maybe StakeAddress
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe StakeAddress -> Bech32DecodeError -> Maybe StakeAddress
forall a b. a -> b -> a
const Maybe StakeAddress
forall a. Maybe a
Nothing) StakeAddress -> Maybe StakeAddress
forall a. a -> Maybe a
Just (Either Bech32DecodeError StakeAddress -> Maybe StakeAddress)
-> Either Bech32DecodeError StakeAddress -> Maybe StakeAddress
forall a b. (a -> b) -> a -> b
$
AsType StakeAddress
-> Text -> Either Bech32DecodeError StakeAddress
forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 AsType StakeAddress
AsStakeAddress Text
t
instance ToJSON StakeAddress where
toJSON :: StakeAddress -> Value
toJSON StakeAddress
s = Text -> Value
Aeson.String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ StakeAddress -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress StakeAddress
s
instance FromJSON StakeAddress where
parseJSON :: Value -> Parser StakeAddress
parseJSON = String
-> (Text -> Parser StakeAddress) -> Value -> Parser StakeAddress
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"StakeAddress" ((Text -> Parser StakeAddress) -> Value -> Parser StakeAddress)
-> (Text -> Parser StakeAddress) -> Value -> Parser StakeAddress
forall a b. (a -> b) -> a -> b
$ \Text
str ->
case AsType StakeAddress -> Text -> Maybe StakeAddress
forall addr.
SerialiseAddress addr =>
AsType addr -> Text -> Maybe addr
deserialiseAddress AsType StakeAddress
AsStakeAddress Text
str of
Maybe StakeAddress
Nothing ->
String -> Parser StakeAddress
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser StakeAddress) -> String -> Parser StakeAddress
forall a b. (a -> b) -> a -> b
$ String
"Error while deserialising StakeAddress: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
Text.unpack Text
str
Just StakeAddress
sAddr -> StakeAddress -> Parser StakeAddress
forall (f :: * -> *) a. Applicative f => a -> f a
pure StakeAddress
sAddr
makeStakeAddress :: NetworkId
-> StakeCredential
-> StakeAddress
makeStakeAddress :: NetworkId -> StakeCredential -> StakeAddress
makeStakeAddress NetworkId
nw StakeCredential
sc =
Network -> StakeCredential StandardCrypto -> StakeAddress
StakeAddress
(NetworkId -> Network
toShelleyNetwork NetworkId
nw)
(StakeCredential -> StakeCredential StandardCrypto
toShelleyStakeCredential StakeCredential
sc)
isKeyAddress :: AddressInEra era -> Bool
isKeyAddress :: AddressInEra era -> Bool
isKeyAddress (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
_) = Bool
True
isKeyAddress (AddressInEra (ShelleyAddressInEra ShelleyBasedEra era
_) (ShelleyAddress Network
_ PaymentCredential StandardCrypto
pCred StakeReference StandardCrypto
_)) =
case PaymentCredential StandardCrypto -> PaymentCredential
fromShelleyPaymentCredential PaymentCredential StandardCrypto
pCred of
PaymentCredentialByKey Hash PaymentKey
_ -> Bool
True
PaymentCredentialByScript ScriptHash
_ -> Bool
False
shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe Plutus.PubKeyHash
shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PubKeyHash
shelleyPayAddrToPlutusPubKHash (ShelleyAddress Network
_ PaymentCredential StandardCrypto
payCred StakeReference StandardCrypto
_) =
case PaymentCredential StandardCrypto
payCred of
Shelley.ScriptHashObj ScriptHash StandardCrypto
_ -> Maybe PubKeyHash
forall a. Maybe a
Nothing
Shelley.KeyHashObj KeyHash 'Payment StandardCrypto
kHash -> PubKeyHash -> Maybe PubKeyHash
forall a. a -> Maybe a
Just (PubKeyHash -> Maybe PubKeyHash) -> PubKeyHash -> Maybe PubKeyHash
forall a b. (a -> b) -> a -> b
$ KeyHash 'Payment StandardCrypto -> PubKeyHash
forall (d :: KeyRole) c. KeyHash d c -> PubKeyHash
Alonzo.transKeyHash KeyHash 'Payment StandardCrypto
kHash
toShelleyAddr :: AddressInEra era -> Shelley.Addr StandardCrypto
toShelleyAddr :: AddressInEra era -> Addr StandardCrypto
toShelleyAddr (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra (ByronAddress Address
addr)) =
BootstrapAddress StandardCrypto -> Addr StandardCrypto
forall crypto. BootstrapAddress crypto -> Addr crypto
Shelley.AddrBootstrap (Address -> BootstrapAddress StandardCrypto
forall crypto. Address -> BootstrapAddress crypto
Shelley.BootstrapAddress Address
addr)
toShelleyAddr (AddressInEra (ShelleyAddressInEra ShelleyBasedEra era
_)
(ShelleyAddress Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr)) =
Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Addr StandardCrypto
forall crypto.
Network
-> PaymentCredential crypto -> StakeReference crypto -> Addr crypto
Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr
toShelleyStakeAddr :: StakeAddress -> Shelley.RewardAcnt StandardCrypto
toShelleyStakeAddr :: StakeAddress -> RewardAcnt StandardCrypto
toShelleyStakeAddr (StakeAddress Network
nw StakeCredential StandardCrypto
sc) =
RewardAcnt :: forall crypto.
Network -> Credential 'Staking crypto -> RewardAcnt crypto
Shelley.RewardAcnt {
getRwdNetwork :: Network
Shelley.getRwdNetwork = Network
nw,
getRwdCred :: StakeCredential StandardCrypto
Shelley.getRwdCred = StakeCredential StandardCrypto
sc
}
toShelleyPaymentCredential :: PaymentCredential
-> Shelley.PaymentCredential StandardCrypto
toShelleyPaymentCredential :: PaymentCredential -> PaymentCredential StandardCrypto
toShelleyPaymentCredential (PaymentCredentialByKey (PaymentKeyHash kh)) =
KeyHash 'Payment StandardCrypto -> PaymentCredential StandardCrypto
forall (kr :: KeyRole) crypto.
KeyHash kr crypto -> Credential kr crypto
Shelley.KeyHashObj KeyHash 'Payment StandardCrypto
kh
toShelleyPaymentCredential (PaymentCredentialByScript ScriptHash
sh) =
ScriptHash StandardCrypto -> PaymentCredential StandardCrypto
forall (kr :: KeyRole) crypto.
ScriptHash crypto -> Credential kr crypto
Shelley.ScriptHashObj (ScriptHash -> ScriptHash StandardCrypto
toShelleyScriptHash ScriptHash
sh)
toShelleyStakeCredential :: StakeCredential
-> Shelley.StakeCredential StandardCrypto
toShelleyStakeCredential :: StakeCredential -> StakeCredential StandardCrypto
toShelleyStakeCredential (StakeCredentialByKey (StakeKeyHash kh)) =
KeyHash 'Staking StandardCrypto -> StakeCredential StandardCrypto
forall (kr :: KeyRole) crypto.
KeyHash kr crypto -> Credential kr crypto
Shelley.KeyHashObj KeyHash 'Staking StandardCrypto
kh
toShelleyStakeCredential (StakeCredentialByScript ScriptHash
sh) =
ScriptHash StandardCrypto -> StakeCredential StandardCrypto
forall (kr :: KeyRole) crypto.
ScriptHash crypto -> Credential kr crypto
Shelley.ScriptHashObj (ScriptHash -> ScriptHash StandardCrypto
toShelleyScriptHash ScriptHash
sh)
toShelleyStakeReference :: StakeAddressReference
-> Shelley.StakeReference StandardCrypto
toShelleyStakeReference :: StakeAddressReference -> StakeReference StandardCrypto
toShelleyStakeReference (StakeAddressByValue StakeCredential
stakecred) =
StakeCredential StandardCrypto -> StakeReference StandardCrypto
forall crypto. StakeCredential crypto -> StakeReference crypto
Shelley.StakeRefBase (StakeCredential -> StakeCredential StandardCrypto
toShelleyStakeCredential StakeCredential
stakecred)
toShelleyStakeReference (StakeAddressByPointer StakeAddressPointer
ptr) =
Ptr -> StakeReference StandardCrypto
forall crypto. Ptr -> StakeReference crypto
Shelley.StakeRefPtr (StakeAddressPointer -> Ptr
unStakeAddressPointer StakeAddressPointer
ptr)
toShelleyStakeReference StakeAddressReference
NoStakeAddress =
StakeReference StandardCrypto
forall crypto. StakeReference crypto
Shelley.StakeRefNull
fromShelleyAddrIsSbe :: IsShelleyBasedEra era
=> Shelley.Addr StandardCrypto -> AddressInEra era
fromShelleyAddrIsSbe :: Addr StandardCrypto -> AddressInEra era
fromShelleyAddrIsSbe (Shelley.AddrBootstrap (Shelley.BootstrapAddress Address
addr)) =
AddressTypeInEra ByronAddr era
-> Address ByronAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra AddressTypeInEra ByronAddr era
forall era. AddressTypeInEra ByronAddr era
ByronAddressInAnyEra (Address -> Address ByronAddr
ByronAddress Address
addr)
fromShelleyAddrIsSbe (Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) =
AddressTypeInEra ShelleyAddr era
-> Address ShelleyAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra
(ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
ShelleyAddressInEra ShelleyBasedEra era
forall era. IsShelleyBasedEra era => ShelleyBasedEra era
shelleyBasedEra)
(Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Address ShelleyAddr
ShelleyAddress Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr)
fromShelleyAddr
:: ShelleyBasedEra era
-> Shelley.Addr StandardCrypto
-> AddressInEra era
fromShelleyAddr :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era
fromShelleyAddr ShelleyBasedEra era
_ (Shelley.AddrBootstrap (Shelley.BootstrapAddress Address
addr)) =
AddressTypeInEra ByronAddr era
-> Address ByronAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra AddressTypeInEra ByronAddr era
forall era. AddressTypeInEra ByronAddr era
ByronAddressInAnyEra (Address -> Address ByronAddr
ByronAddress Address
addr)
fromShelleyAddr ShelleyBasedEra era
sBasedEra (Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) =
AddressTypeInEra ShelleyAddr era
-> Address ShelleyAddr -> AddressInEra era
forall addrtype era.
AddressTypeInEra addrtype era
-> Address addrtype -> AddressInEra era
AddressInEra
(ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
ShelleyAddressInEra ShelleyBasedEra era
sBasedEra)
(Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Address ShelleyAddr
ShelleyAddress Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr)
fromShelleyStakeAddr :: Shelley.RewardAcnt StandardCrypto -> StakeAddress
fromShelleyStakeAddr :: RewardAcnt StandardCrypto -> StakeAddress
fromShelleyStakeAddr (Shelley.RewardAcnt Network
nw StakeCredential StandardCrypto
sc) = Network -> StakeCredential StandardCrypto -> StakeAddress
StakeAddress Network
nw StakeCredential StandardCrypto
sc
fromShelleyStakeCredential :: Shelley.StakeCredential StandardCrypto
-> StakeCredential
fromShelleyStakeCredential :: StakeCredential StandardCrypto -> StakeCredential
fromShelleyStakeCredential (Shelley.KeyHashObj KeyHash 'Staking StandardCrypto
kh) =
Hash StakeKey -> StakeCredential
StakeCredentialByKey (KeyHash 'Staking StandardCrypto -> Hash StakeKey
StakeKeyHash KeyHash 'Staking StandardCrypto
kh)
fromShelleyStakeCredential (Shelley.ScriptHashObj ScriptHash StandardCrypto
sh) =
ScriptHash -> StakeCredential
StakeCredentialByScript (ScriptHash StandardCrypto -> ScriptHash
fromShelleyScriptHash ScriptHash StandardCrypto
sh)
fromShelleyPaymentCredential :: Shelley.PaymentCredential StandardCrypto
-> PaymentCredential
fromShelleyPaymentCredential :: PaymentCredential StandardCrypto -> PaymentCredential
fromShelleyPaymentCredential (Shelley.KeyHashObj KeyHash 'Payment StandardCrypto
kh) =
Hash PaymentKey -> PaymentCredential
PaymentCredentialByKey (KeyHash 'Payment StandardCrypto -> Hash PaymentKey
PaymentKeyHash KeyHash 'Payment StandardCrypto
kh)
fromShelleyPaymentCredential (Shelley.ScriptHashObj ScriptHash StandardCrypto
sh) =
ScriptHash -> PaymentCredential
PaymentCredentialByScript (ScriptHash StandardCrypto -> ScriptHash
ScriptHash ScriptHash StandardCrypto
sh)
fromShelleyStakeReference :: Shelley.StakeReference StandardCrypto
-> StakeAddressReference
fromShelleyStakeReference :: StakeReference StandardCrypto -> StakeAddressReference
fromShelleyStakeReference (Shelley.StakeRefBase StakeCredential StandardCrypto
stakecred) =
StakeCredential -> StakeAddressReference
StakeAddressByValue (StakeCredential StandardCrypto -> StakeCredential
fromShelleyStakeCredential StakeCredential StandardCrypto
stakecred)
fromShelleyStakeReference (Shelley.StakeRefPtr Ptr
ptr) =
StakeAddressPointer -> StakeAddressReference
StakeAddressByPointer (Ptr -> StakeAddressPointer
StakeAddressPointer Ptr
ptr)
fromShelleyStakeReference StakeReference StandardCrypto
Shelley.StakeRefNull =
StakeAddressReference
NoStakeAddress