{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{- HLINT ignore "Avoid lambda using `infix`" -}

-- | Cardano addresses: payment and stake addresses.
module Cardano.Api.Address
  ( -- * Payment addresses

    -- | Constructing and inspecting normal payment addresses
    Address (..)

    -- ** Byron addresses
  , ByronAddr
  , makeByronAddress

    -- ** Shelley addresses
  , ShelleyAddr
  , makeShelleyAddress
  , PaymentCredential (..)
  , StakeAddressReference (..)
  , StakeAddressPointer (..)

    -- ** Addresses in any era
  , AddressAny (..)
  , lexPlausibleAddressString
  , parseAddressAny

    -- ** Addresses in specific eras
  , AddressInEra (..)
  , AddressTypeInEra (..)
  , byronAddressInEra
  , shelleyAddressInEra
  , anyAddressInShelleyBasedEra
  , anyAddressInEra
  , toAddressAny
  , makeByronAddressInEra
  , makeShelleyAddressInEra

    -- * Stake addresses

    -- | Constructing and inspecting stake addresses
  , StakeAddress (..)
  , StakeCredential (..)
  , makeStakeAddress
  , stakeAddressCredential
  , StakeKey
  , StakeExtendedKey

    -- * Conversion functions
  , shelleyPayAddrToPlutusPubKHash

    -- * Internal conversion functions
  , toShelleyAddr
  , toShelleyStakeAddr
  , toShelleyStakeCredential
  , fromShelleyAddr
  , fromShelleyAddrIsSbe
  , fromShelleyAddrToAny
  , fromShelleyPaymentCredential
  , fromShelleyStakeAddr
  , fromShelleyStakeCredential
  , fromShelleyStakeReference

    -- * Serialising addresses
  , SerialiseAddress (..)

    -- * Data family instances
  , AsType
    ( AsByronAddr
    , AsShelleyAddr
    , AsByronAddress
    , AsShelleyAddress
    , AsAddress
    , AsAddressAny
    , AsAddressInEra
    , AsStakeAddress
    )

    -- * Helpers
  , isKeyAddress
  )
where

import           Cardano.Api.Eon.ShelleyBasedEra
import           Cardano.Api.Eras
import           Cardano.Api.Hash
import           Cardano.Api.HasTypeProxy
import           Cardano.Api.Keys.Byron
import           Cardano.Api.Keys.Shelley
import           Cardano.Api.NetworkId
import           Cardano.Api.Script
import           Cardano.Api.SerialiseBech32
import           Cardano.Api.SerialiseRaw
import           Cardano.Api.Utils

import qualified Cardano.Chain.Common as Byron
import qualified Cardano.Ledger.Address as Shelley
import qualified Cardano.Ledger.BaseTypes as Shelley
import qualified Cardano.Ledger.Credential as Shelley
import           Cardano.Ledger.Crypto (StandardCrypto)
import qualified Cardano.Ledger.Plutus.TxInfo as Plutus
import qualified PlutusLedgerApi.V1 as PlutusAPI

import           Control.Applicative ((<|>))
import           Control.DeepSeq (NFData (..), deepseq)
import           Data.Aeson (FromJSON (..), ToJSON (..), withText, (.=))
import qualified Data.Aeson as Aeson
import           Data.Bifunctor (first)
import qualified Data.ByteString.Base58 as Base58
import           Data.Char (isAsciiLower, isAsciiUpper, isDigit)
import           Data.Either.Combinators (rightToMaybe)
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

-- ----------------------------------------------------------------------------
-- Address Serialisation
--

-- | Address serialisation uses different serialisation formats for different
-- kinds of addresses, so it needs its own class.
--
-- In particular, Byron addresses are typically formatted in base 58, while
-- Shelley addresses (payment and stake) are formatted using Bech32.
class HasTypeProxy addr => SerialiseAddress addr where
  serialiseAddress :: addr -> Text

  deserialiseAddress :: AsType addr -> Text -> Maybe addr

-- TODO: consider adding data AddressDecodeError

-- ----------------------------------------------------------------------------
-- Payment address types
--

-- | A type used as a tag to distinguish Byron addresses.
data ByronAddr

-- | A type used as a tag to distinguish Shelley addresses.
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

-- ----------------------------------------------------------------------------
-- Payment addresses
--

-- | Addresses are used as locations where assets live. The address determines
-- the rights needed to spend assets at the address: in particular holding some
-- signing key or being able to satisfy the conditions of a script.
--
-- There are currently two types of address:
--
-- * Byron addresses, which use the type tag 'ByronAddr'; and
-- * Shelley addresses, which use the type tag 'ShelleyAddr'. Notably, Shelley
--   addresses support scripts and stake delegation.
--
-- The /address type/ is subtly from the /ledger era/ in which each
-- address type is valid: while Byron addresses are the only choice in the
-- Byron era, the Shelley era and all subsequent eras support both Byron and
-- Shelley addresses. The 'Address' type param only says the type of the address
-- (either Byron or Shelley). The 'AddressInEra' type connects the address type
-- with the era in which it is supported.
data Address addrtype where
  -- | Byron addresses were the only supported address type in the original
  -- Byron era.
  ByronAddress
    :: Byron.Address
    -> Address ByronAddr
  -- | Shelley addresses allow delegation. Shelley addresses were introduced
  -- in Shelley era and are thus supported from the Shelley era onwards
  ShelleyAddress
    :: Shelley.Network
    -> Shelley.PaymentCredential StandardCrypto
    -> Shelley.StakeReference StandardCrypto
    -> Address ShelleyAddr

-- Note that the two ledger credential types here are parametrised by
-- the era, but in fact this is a phantom type parameter and they are
-- the same for all eras. See 'toShelleyAddr' below.

deriving instance Eq (Address addrtype)

deriving instance Ord (Address addrtype)

deriving instance Show (Address addrtype)

instance NFData (Address addrtype) where
  rnf :: Address addrtype -> ()
rnf = \case
    ByronAddress Address
address -> Address -> () -> ()
forall a b. NFData a => a -> b -> b
deepseq Address
address ()
    ShelleyAddress Network
n PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
sr -> StakeReference StandardCrypto -> () -> ()
forall a b. NFData a => a -> b -> b
deepseq (PaymentCredential StandardCrypto
-> StakeReference StandardCrypto -> StakeReference StandardCrypto
forall a b. NFData a => a -> b -> b
deepseq (Network
-> PaymentCredential StandardCrypto
-> PaymentCredential StandardCrypto
forall a b. NFData a => a -> b -> b
deepseq Network
n PaymentCredential StandardCrypto
pc) StakeReference StandardCrypto
sr) ()

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 $mAsByronAddress :: forall {r}.
AsType (Address ByronAddr) -> ((# #) -> r) -> ((# #) -> r) -> r
$bAsByronAddress :: AsType (Address ByronAddr)
AsByronAddress = AsAddress AsByronAddr

{-# COMPLETE AsByronAddress #-}

pattern AsShelleyAddress :: AsType (Address ShelleyAddr)
pattern $mAsShelleyAddress :: forall {r}.
AsType (Address ShelleyAddr) -> ((# #) -> r) -> ((# #) -> r) -> r
$bAsShelleyAddress :: AsType (Address ShelleyAddr)
AsShelleyAddress = AsAddress AsShelleyAddr

{-# COMPLETE AsShelleyAddress #-}

instance SerialiseAsRawBytes (Address ByronAddr) where
  serialiseToRawBytes :: Address ByronAddr -> ByteString
serialiseToRawBytes (ByronAddress Address
addr) =
    Addr Any -> ByteString
forall c. Addr c -> 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 c. BootstrapAddress c -> Addr c
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 c. Address -> BootstrapAddress c
Shelley.BootstrapAddress
      (Address -> ByteString) -> Address -> ByteString
forall a b. (a -> b) -> a -> b
$ Address
addr

  deserialiseFromRawBytes :: AsType (Address ByronAddr)
-> ByteString
-> Either SerialiseAsRawBytesError (Address ByronAddr)
deserialiseFromRawBytes (AsAddress AsType ByronAddr
R:AsTypeByronAddr
AsByronAddr) ByteString
bs =
    case ByteString -> Maybe (Addr StandardCrypto)
forall c (m :: * -> *).
(Crypto c, MonadFail m) =>
ByteString -> m (Addr c)
Shelley.decodeAddr ByteString
bs :: Maybe (Shelley.Addr StandardCrypto) of
      Maybe (Addr StandardCrypto)
Nothing -> SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (Address ByronAddr)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Address ByronAddr")
      Just Shelley.Addr{} -> SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (Address ByronAddr)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise Address ByronAddr")
      Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress Address
addr)) ->
        Address ByronAddr
-> Either SerialiseAsRawBytesError (Address ByronAddr)
forall a b. b -> Either a b
Right (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 c. Addr c -> ByteString
Shelley.serialiseAddr (Network
-> PaymentCredential StandardCrypto
-> StakeReference StandardCrypto
-> Addr StandardCrypto
forall c.
Network -> PaymentCredential c -> StakeReference c -> Addr c
Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr)

  deserialiseFromRawBytes :: AsType (Address ShelleyAddr)
-> ByteString
-> Either SerialiseAsRawBytesError (Address ShelleyAddr)
deserialiseFromRawBytes (AsAddress AsType ShelleyAddr
R:AsTypeShelleyAddr
AsShelleyAddr) ByteString
bs =
    case ByteString -> Maybe (Addr StandardCrypto)
forall c (m :: * -> *).
(Crypto c, MonadFail m) =>
ByteString -> m (Addr c)
Shelley.decodeAddr ByteString
bs of
      Maybe (Addr StandardCrypto)
Nothing ->
        SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (Address ShelleyAddr)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise bootstrap Address ShelleyAddr")
      Just Shelley.AddrBootstrap{} -> SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError (Address ShelleyAddr)
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise bootstrap Address ShelleyAddr")
      Just (Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) -> Address ShelleyAddr
-> Either SerialiseAsRawBytesError (Address ShelleyAddr)
forall a b. b -> Either a b
Right (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 AsType ShelleyAddr
R:AsTypeShelleyAddr
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 AsType ByronAddr
R:AsTypeByronAddr
AsByronAddr) Text
txt = do
    ByteString
bs <- Alphabet -> ByteString -> Maybe ByteString
Base58.decodeBase58 Alphabet
Base58.bitcoinAlphabet (Text -> ByteString
Text.encodeUtf8 Text
txt)
    Either SerialiseAsRawBytesError (Address ByronAddr)
-> Maybe (Address ByronAddr)
forall a b. Either a b -> Maybe b
rightToMaybe (AsType (Address ByronAddr)
-> ByteString
-> Either SerialiseAsRawBytesError (Address ByronAddr)
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError 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 AsType ShelleyAddr
R:AsTypeShelleyAddr
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

instance ToJSON (Address ShelleyAddr) where
  toJSON :: Address ShelleyAddr -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value)
-> (Address ShelleyAddr -> Text) -> Address ShelleyAddr -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address ShelleyAddr -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress

instance ToJSON (Address ByronAddr) where
  toJSON :: Address ByronAddr -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value)
-> (Address ByronAddr -> Text) -> Address ByronAddr -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address ByronAddr -> Text
forall addr. SerialiseAddress addr => addr -> Text
serialiseAddress

instance FromJSON (Address ByronAddr) where
  parseJSON :: Value -> Parser (Address ByronAddr)
parseJSON = String
-> (Text -> Parser (Address ByronAddr))
-> Value
-> Parser (Address ByronAddr)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText String
"Address" ((Text -> Parser (Address ByronAddr))
 -> Value -> Parser (Address ByronAddr))
-> (Text -> Parser (Address ByronAddr))
-> Value
-> Parser (Address ByronAddr)
forall a b. (a -> b) -> a -> b
$ \Text
txt ->
    Parser (Address ByronAddr)
-> (Address ByronAddr -> Parser (Address ByronAddr))
-> Maybe (Address ByronAddr)
-> Parser (Address ByronAddr)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      (String -> Parser (Address ByronAddr)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Cardano.Api.Address.FromJSON: Invalid Byron address.")
      Address ByronAddr -> Parser (Address ByronAddr)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
      (AsType (Address ByronAddr) -> Text -> Maybe (Address ByronAddr)
forall addr.
SerialiseAddress addr =>
AsType addr -> Text -> Maybe addr
deserialiseAddress AsType (Address ByronAddr)
AsByronAddress Text
txt)

instance FromJSON (Address ShelleyAddr) where
  parseJSON :: Value -> Parser (Address ShelleyAddr)
parseJSON = String
-> (Text -> Parser (Address ShelleyAddr))
-> Value
-> Parser (Address ShelleyAddr)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText String
"Address" ((Text -> Parser (Address ShelleyAddr))
 -> Value -> Parser (Address ShelleyAddr))
-> (Text -> Parser (Address ShelleyAddr))
-> Value
-> Parser (Address ShelleyAddr)
forall a b. (a -> b) -> a -> b
$ \Text
txt ->
    Parser (Address ShelleyAddr)
-> (Address ShelleyAddr -> Parser (Address ShelleyAddr))
-> Maybe (Address ShelleyAddr)
-> Parser (Address ShelleyAddr)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
      (String -> Parser (Address ShelleyAddr)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Cardano.Api.Address.FromJSON: Invalid Shelley address.")
      Address ShelleyAddr -> Parser (Address ShelleyAddr)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
      (AsType (Address ShelleyAddr) -> Text -> Maybe (Address ShelleyAddr)
forall addr.
SerialiseAddress addr =>
AsType addr -> Text -> Maybe addr
deserialiseAddress AsType (Address ShelleyAddr)
AsShelleyAddress Text
txt)

makeByronAddress
  :: NetworkId
  -> VerificationKey ByronKey
  -> Address ByronAddr
makeByronAddress :: NetworkId -> VerificationKey ByronKey -> Address ByronAddr
makeByronAddress NetworkId
nw (ByronVerificationKey VerificationKey
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)

-- ----------------------------------------------------------------------------
-- Either type of address
--

-- | Either a Byron address or a Shelley address.
--
-- Sometimes we need to be able to work with either of the two types of
-- address (Byron or Shelley addresses), but without reference to an era in
-- which the address will be used. This type serves that purpose.
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
$c== :: AddressAny -> AddressAny -> Bool
== :: AddressAny -> AddressAny -> Bool
$c/= :: AddressAny -> AddressAny -> Bool
/= :: 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
$ccompare :: AddressAny -> AddressAny -> Ordering
compare :: AddressAny -> AddressAny -> Ordering
$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
>= :: AddressAny -> AddressAny -> Bool
$cmax :: AddressAny -> AddressAny -> AddressAny
max :: AddressAny -> AddressAny -> AddressAny
$cmin :: AddressAny -> AddressAny -> AddressAny
min :: AddressAny -> AddressAny -> 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
$cshowsPrec :: Int -> AddressAny -> ShowS
showsPrec :: Int -> AddressAny -> ShowS
$cshow :: AddressAny -> String
show :: AddressAny -> String
$cshowList :: [AddressAny] -> ShowS
showList :: [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 -> Either SerialiseAsRawBytesError AddressAny
deserialiseFromRawBytes AsType AddressAny
R:AsTypeAddressAny
AsAddressAny ByteString
bs =
    case ByteString -> Maybe (Addr StandardCrypto)
forall c (m :: * -> *).
(Crypto c, MonadFail m) =>
ByteString -> m (Addr c)
Shelley.decodeAddr ByteString
bs of
      Maybe (Addr StandardCrypto)
Nothing -> SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError AddressAny
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise AddressAny")
      Just (Shelley.AddrBootstrap (Shelley.BootstrapAddress Address
addr)) ->
        AddressAny -> Either SerialiseAsRawBytesError AddressAny
forall a b. b -> Either a b
Right (Address ByronAddr -> AddressAny
AddressByron (Address -> Address ByronAddr
ByronAddress Address
addr))
      Just (Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr) ->
        AddressAny -> Either SerialiseAsRawBytesError AddressAny
forall a b. b -> Either a b
Right (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
R:AsTypeAddressAny
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 a. Maybe a -> Maybe a -> Maybe a
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

-- ----------------------------------------------------------------------------
-- Addresses in the context of a ledger era
--

-- | An 'Address' that can be used in a particular ledger era.
--
-- All current ledger eras support Byron addresses. Shelley addresses are
-- supported in the 'ShelleyEra' and later eras.
data AddressInEra era where
  AddressInEra
    :: AddressTypeInEra addrtype era
    -> Address addrtype
    -> AddressInEra era

instance NFData (AddressInEra era) where
  rnf :: AddressInEra era -> ()
rnf (AddressInEra AddressTypeInEra addrtype era
t Address addrtype
a) = Address addrtype -> () -> ()
forall a b. NFData a => a -> b -> b
deepseq (AddressTypeInEra addrtype era
-> Address addrtype -> Address addrtype
forall a b. NFData a => a -> b -> b
deepseq AddressTypeInEra addrtype era
t Address addrtype
a) ()

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 =
    let sbe :: ShelleyBasedEra era
sbe = forall era. IsShelleyBasedEra era => ShelleyBasedEra era
shelleyBasedEra @era
     in 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 a. a -> Parser a
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
$ ShelleyBasedEra era -> AddressAny -> AddressInEra era
forall era. ShelleyBasedEra era -> AddressAny -> AddressInEra era
anyAddressInShelleyBasedEra ShelleyBasedEra era
sbe AddressAny
addressAny

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 a. String -> ParsecT String () Identity a
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 a. a -> ParsecT String () Identity a
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 u (m :: * -> *) a. 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
  -- Covers both base58 and bech32 (with constrained prefixes)
  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

instance Ord (AddressInEra era) where
  compare :: AddressInEra era -> AddressInEra era -> Ordering
compare
    (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
addr1)
    (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
addr2) = Address addrtype -> Address addrtype -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Address addrtype
addr1 Address addrtype
Address addrtype
addr2
  compare
    (AddressInEra ShelleyAddressInEra{} Address addrtype
addr1)
    (AddressInEra ShelleyAddressInEra{} Address addrtype
addr2) = Address addrtype -> Address addrtype -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Address addrtype
addr1 Address addrtype
Address addrtype
addr2
  compare
    (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
_)
    (AddressInEra ShelleyAddressInEra{} Address addrtype
_) = Ordering
LT
  compare
    (AddressInEra ShelleyAddressInEra{} Address addrtype
_)
    (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra Address addrtype
_) = Ordering
GT

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 NFData (AddressTypeInEra addrtype era) where
  rnf :: AddressTypeInEra addrtype era -> ()
rnf = \case
    AddressTypeInEra addrtype era
ByronAddressInAnyEra -> ()
    ShelleyAddressInEra ShelleyBasedEra era
sbe -> ShelleyBasedEra era -> () -> ()
forall a b. NFData a => a -> b -> b
deepseq ShelleyBasedEra era
sbe ()

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 -> Either SerialiseAsRawBytesError (AddressInEra era)
deserialiseFromRawBytes AsType (AddressInEra era)
_ ByteString
bs =
    (String -> SerialiseAsRawBytesError)
-> Either String (AddressInEra era)
-> Either SerialiseAsRawBytesError (AddressInEra era)
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (SerialiseAsRawBytesError -> String -> SerialiseAsRawBytesError
forall a b. a -> b -> a
const (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise AddressInEra era")) (Either String (AddressInEra era)
 -> Either SerialiseAsRawBytesError (AddressInEra era))
-> Either String (AddressInEra era)
-> Either SerialiseAsRawBytesError (AddressInEra era)
forall a b. (a -> b) -> a -> b
$
      CardanoEra era -> AddressAny -> Either String (AddressInEra era)
forall era.
CardanoEra era -> AddressAny -> Either String (AddressInEra era)
anyAddressInEra CardanoEra era
forall era. IsCardanoEra era => CardanoEra era
cardanoEra
        (AddressAny -> Either String (AddressInEra era))
-> Either String AddressAny -> Either String (AddressInEra era)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (SerialiseAsRawBytesError -> String)
-> Either SerialiseAsRawBytesError AddressAny
-> Either String AddressAny
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first SerialiseAsRawBytesError -> String
unSerialiseAsRawBytesError (AsType AddressAny
-> ByteString -> Either SerialiseAsRawBytesError AddressAny
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError 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 =
    Either String (AddressInEra era) -> Maybe (AddressInEra era)
forall a b. Either a b -> Maybe b
rightToMaybe (Either String (AddressInEra era) -> Maybe (AddressInEra era))
-> (AddressAny -> Either String (AddressInEra era))
-> AddressAny
-> Maybe (AddressInEra era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoEra era -> AddressAny -> Either String (AddressInEra era)
forall era.
CardanoEra era -> AddressAny -> Either String (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

byronAddressInEra :: Address ByronAddr -> AddressInEra era
byronAddressInEra :: forall era. 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
  :: ()
  => ShelleyBasedEra era
  -> Address ShelleyAddr
  -> AddressInEra era
shelleyAddressInEra :: forall era.
ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra ShelleyBasedEra era
sbe =
  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
sbe)

anyAddressInShelleyBasedEra
  :: ()
  => ShelleyBasedEra era
  -> AddressAny
  -> AddressInEra era
anyAddressInShelleyBasedEra :: forall era. ShelleyBasedEra era -> AddressAny -> AddressInEra era
anyAddressInShelleyBasedEra ShelleyBasedEra era
sbe = \case
  AddressByron Address ByronAddr
addr -> Address ByronAddr -> AddressInEra era
forall era. Address ByronAddr -> AddressInEra era
byronAddressInEra Address ByronAddr
addr
  AddressShelley Address ShelleyAddr
addr -> ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
forall era.
ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra ShelleyBasedEra era
sbe Address ShelleyAddr
addr

anyAddressInEra
  :: CardanoEra era
  -> AddressAny
  -> Either String (AddressInEra era)
anyAddressInEra :: forall era.
CardanoEra era -> AddressAny -> Either String (AddressInEra era)
anyAddressInEra CardanoEra era
era = \case
  AddressByron Address ByronAddr
addr ->
    AddressInEra era -> Either String (AddressInEra era)
forall a b. b -> Either a b
Right (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)
  AddressShelley Address ShelleyAddr
addr ->
    CardanoEra era
-> Either String (AddressInEra era)
-> (ShelleyBasedEra era -> Either String (AddressInEra era))
-> Either String (AddressInEra era)
forall (eon :: * -> *) era a.
Eon eon =>
CardanoEra era -> a -> (eon era -> a) -> a
forEraInEon
      CardanoEra era
era
      (String -> Either String (AddressInEra era)
forall a b. a -> Either a b
Left String
"Expected Byron based era address")
      (\ShelleyBasedEra era
sbe -> AddressInEra era -> Either String (AddressInEra era)
forall a b. b -> Either a b
Right (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
sbe) Address ShelleyAddr
addr))

toAddressAny :: Address addr -> AddressAny
toAddressAny :: forall addr. 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 :: forall era.
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
  :: ()
  => ShelleyBasedEra era
  -> NetworkId
  -> PaymentCredential
  -> StakeAddressReference
  -> AddressInEra era
makeShelleyAddressInEra :: forall era.
ShelleyBasedEra era
-> NetworkId
-> PaymentCredential
-> StakeAddressReference
-> AddressInEra era
makeShelleyAddressInEra ShelleyBasedEra era
sbe NetworkId
nw PaymentCredential
pc StakeAddressReference
scr =
  ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
forall era.
ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
shelleyAddressInEra ShelleyBasedEra era
sbe (NetworkId
-> PaymentCredential
-> StakeAddressReference
-> Address ShelleyAddr
makeShelleyAddress NetworkId
nw PaymentCredential
pc StakeAddressReference
scr)

-- ----------------------------------------------------------------------------
-- Stake addresses
--

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
$c== :: StakeAddress -> StakeAddress -> Bool
== :: StakeAddress -> StakeAddress -> Bool
$c/= :: StakeAddress -> StakeAddress -> Bool
/= :: 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
$ccompare :: StakeAddress -> StakeAddress -> Ordering
compare :: StakeAddress -> StakeAddress -> Ordering
$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
>= :: StakeAddress -> StakeAddress -> Bool
$cmax :: StakeAddress -> StakeAddress -> StakeAddress
max :: StakeAddress -> StakeAddress -> StakeAddress
$cmin :: StakeAddress -> StakeAddress -> StakeAddress
min :: StakeAddress -> StakeAddress -> 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
$cshowsPrec :: Int -> StakeAddress -> ShowS
showsPrec :: Int -> StakeAddress -> ShowS
$cshow :: StakeAddress -> String
show :: StakeAddress -> String
$cshowList :: [StakeAddress] -> ShowS
showList :: [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
$c== :: PaymentCredential -> PaymentCredential -> Bool
== :: PaymentCredential -> PaymentCredential -> Bool
$c/= :: PaymentCredential -> PaymentCredential -> Bool
/= :: 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
$ccompare :: PaymentCredential -> PaymentCredential -> Ordering
compare :: PaymentCredential -> PaymentCredential -> Ordering
$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
>= :: PaymentCredential -> PaymentCredential -> Bool
$cmax :: PaymentCredential -> PaymentCredential -> PaymentCredential
max :: PaymentCredential -> PaymentCredential -> PaymentCredential
$cmin :: PaymentCredential -> PaymentCredential -> PaymentCredential
min :: PaymentCredential -> PaymentCredential -> 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
$cshowsPrec :: Int -> PaymentCredential -> ShowS
showsPrec :: Int -> PaymentCredential -> ShowS
$cshow :: PaymentCredential -> String
show :: PaymentCredential -> String
$cshowList :: [PaymentCredential] -> ShowS
showList :: [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
$c== :: StakeCredential -> StakeCredential -> Bool
== :: StakeCredential -> StakeCredential -> Bool
$c/= :: StakeCredential -> StakeCredential -> Bool
/= :: 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
$ccompare :: StakeCredential -> StakeCredential -> Ordering
compare :: StakeCredential -> StakeCredential -> Ordering
$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
>= :: StakeCredential -> StakeCredential -> Bool
$cmax :: StakeCredential -> StakeCredential -> StakeCredential
max :: StakeCredential -> StakeCredential -> StakeCredential
$cmin :: StakeCredential -> StakeCredential -> StakeCredential
min :: StakeCredential -> StakeCredential -> 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
$cshowsPrec :: Int -> StakeCredential -> ShowS
showsPrec :: Int -> StakeCredential -> ShowS
$cshow :: StakeCredential -> String
show :: StakeCredential -> String
$cshowList :: [StakeCredential] -> ShowS
showList :: [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 v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e 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 v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e 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
$c== :: StakeAddressReference -> StakeAddressReference -> Bool
== :: StakeAddressReference -> StakeAddressReference -> Bool
$c/= :: StakeAddressReference -> StakeAddressReference -> Bool
/= :: 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
$cshowsPrec :: Int -> StakeAddressReference -> ShowS
showsPrec :: Int -> StakeAddressReference -> ShowS
$cshow :: StakeAddressReference -> String
show :: StakeAddressReference -> String
$cshowList :: [StakeAddressReference] -> ShowS
showList :: [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
$c== :: StakeAddressPointer -> StakeAddressPointer -> Bool
== :: StakeAddressPointer -> StakeAddressPointer -> Bool
$c/= :: StakeAddressPointer -> StakeAddressPointer -> Bool
/= :: 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
$cshowsPrec :: Int -> StakeAddressPointer -> ShowS
showsPrec :: Int -> StakeAddressPointer -> ShowS
$cshow :: StakeAddressPointer -> String
show :: StakeAddressPointer -> String
$cshowList :: [StakeAddressPointer] -> ShowS
showList :: [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 c. RewardAcnt c -> ByteString
Shelley.serialiseRewardAccount (Network
-> StakeCredential StandardCrypto -> RewardAcnt StandardCrypto
forall c. Network -> Credential 'Staking c -> RewardAccount c
Shelley.RewardAccount Network
nw StakeCredential StandardCrypto
sc)

  deserialiseFromRawBytes :: AsType StakeAddress
-> ByteString -> Either SerialiseAsRawBytesError StakeAddress
deserialiseFromRawBytes AsType StakeAddress
R:AsTypeStakeAddress
AsStakeAddress ByteString
bs =
    case ByteString -> Maybe (RewardAcnt StandardCrypto)
forall c. Crypto c => ByteString -> Maybe (RewardAcnt c)
Shelley.deserialiseRewardAccount ByteString
bs of
      Maybe (RewardAcnt StandardCrypto)
Nothing -> SerialiseAsRawBytesError
-> Either SerialiseAsRawBytesError StakeAddress
forall a b. a -> Either a b
Left (String -> SerialiseAsRawBytesError
SerialiseAsRawBytesError String
"Unable to deserialise StakeAddress")
      Just (Shelley.RewardAccount Network
nw StakeCredential StandardCrypto
sc) -> StakeAddress -> Either SerialiseAsRawBytesError StakeAddress
forall a b. b -> Either a b
Right (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
R:AsTypeStakeAddress
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
R:AsTypeStakeAddress
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 a. String -> Parser a
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 a. a -> Parser a
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)

-- ----------------------------------------------------------------------------
-- Helpers
--

-- | Is the UTxO at the address only spendable via a key witness.
isKeyAddress :: AddressInEra era -> Bool
isKeyAddress :: forall era. 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

-- | Converts a Shelley payment address to a Plutus public key hash.
shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PlutusAPI.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
Plutus.transKeyHash KeyHash 'Payment StandardCrypto
kHash

-- ----------------------------------------------------------------------------
-- Internal conversion functions
--

toShelleyAddr :: AddressInEra era -> Shelley.Addr StandardCrypto
toShelleyAddr :: forall era. AddressInEra era -> Addr StandardCrypto
toShelleyAddr (AddressInEra AddressTypeInEra addrtype era
ByronAddressInAnyEra (ByronAddress Address
addr)) =
  BootstrapAddress StandardCrypto -> Addr StandardCrypto
forall c. BootstrapAddress c -> Addr c
Shelley.AddrBootstrap (Address -> BootstrapAddress StandardCrypto
forall c. Address -> BootstrapAddress c
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 c.
Network -> PaymentCredential c -> StakeReference c -> Addr c
Shelley.Addr Network
nw PaymentCredential StandardCrypto
pc StakeReference StandardCrypto
scr

toShelleyStakeAddr :: StakeAddress -> Shelley.RewardAccount StandardCrypto
toShelleyStakeAddr :: StakeAddress -> RewardAcnt StandardCrypto
toShelleyStakeAddr (StakeAddress Network
nw StakeCredential StandardCrypto
sc) =
  Shelley.RewardAccount
    { raNetwork :: Network
Shelley.raNetwork = Network
nw
    , raCredential :: StakeCredential StandardCrypto
Shelley.raCredential = StakeCredential StandardCrypto
sc
    }

toShelleyPaymentCredential
  :: PaymentCredential
  -> Shelley.PaymentCredential StandardCrypto
toShelleyPaymentCredential :: PaymentCredential -> PaymentCredential StandardCrypto
toShelleyPaymentCredential (PaymentCredentialByKey (PaymentKeyHash KeyHash 'Payment StandardCrypto
kh)) =
  KeyHash 'Payment StandardCrypto -> PaymentCredential StandardCrypto
forall (kr :: KeyRole) c. KeyHash kr c -> Credential kr c
Shelley.KeyHashObj KeyHash 'Payment StandardCrypto
kh
toShelleyPaymentCredential (PaymentCredentialByScript ScriptHash
sh) =
  ScriptHash StandardCrypto -> PaymentCredential StandardCrypto
forall (kr :: KeyRole) c. ScriptHash c -> Credential kr c
Shelley.ScriptHashObj (ScriptHash -> ScriptHash StandardCrypto
toShelleyScriptHash ScriptHash
sh)

toShelleyStakeCredential
  :: StakeCredential
  -> Shelley.StakeCredential StandardCrypto
toShelleyStakeCredential :: StakeCredential -> StakeCredential StandardCrypto
toShelleyStakeCredential (StakeCredentialByKey (StakeKeyHash KeyHash 'Staking StandardCrypto
kh)) =
  KeyHash 'Staking StandardCrypto -> StakeCredential StandardCrypto
forall (kr :: KeyRole) c. KeyHash kr c -> Credential kr c
Shelley.KeyHashObj KeyHash 'Staking StandardCrypto
kh
toShelleyStakeCredential (StakeCredentialByScript ScriptHash
sh) =
  ScriptHash StandardCrypto -> StakeCredential StandardCrypto
forall (kr :: KeyRole) c. ScriptHash c -> Credential kr c
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 c. StakeCredential c -> StakeReference c
Shelley.StakeRefBase (StakeCredential -> StakeCredential StandardCrypto
toShelleyStakeCredential StakeCredential
stakecred)
toShelleyStakeReference (StakeAddressByPointer StakeAddressPointer
ptr) =
  Ptr -> StakeReference StandardCrypto
forall c. Ptr -> StakeReference c
Shelley.StakeRefPtr (StakeAddressPointer -> Ptr
unStakeAddressPointer StakeAddressPointer
ptr)
toShelleyStakeReference StakeAddressReference
NoStakeAddress =
  StakeReference StandardCrypto
forall c. StakeReference c
Shelley.StakeRefNull

fromShelleyAddrIsSbe
  :: ()
  => ShelleyBasedEra era
  -> Shelley.Addr StandardCrypto
  -> AddressInEra era
fromShelleyAddrIsSbe :: forall era.
ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era
fromShelleyAddrIsSbe ShelleyBasedEra era
sbe = \case
  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)
  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
sbe) (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 :: forall era.
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.RewardAccount StandardCrypto -> StakeAddress
fromShelleyStakeAddr :: RewardAcnt StandardCrypto -> StakeAddress
fromShelleyStakeAddr (Shelley.RewardAccount 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

-- | Get a stake credential from a stake address.
-- This drops the network information.
stakeAddressCredential :: StakeAddress -> StakeCredential
stakeAddressCredential :: StakeAddress -> StakeCredential
stakeAddressCredential (StakeAddress Network
_ StakeCredential StandardCrypto
scred) = StakeCredential StandardCrypto -> StakeCredential
fromShelleyStakeCredential StakeCredential StandardCrypto
scred