{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-specialise #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
module PlutusLedgerApi.V1.Address
( Address (..)
, pubKeyHashAddress
, scriptHashAddress
, toPubKeyHash
, toScriptHash
, stakingCredential
) where
import Control.DeepSeq (NFData)
import GHC.Generics (Generic)
import PlutusTx qualified
import PlutusTx.Bool qualified as PlutusTx
import PlutusTx.Eq qualified as PlutusTx
import Prettyprinter
import PlutusLedgerApi.V1.Credential (Credential (..), StakingCredential)
import PlutusLedgerApi.V1.Crypto
import PlutusLedgerApi.V1.Scripts
data Address = Address{ Address -> Credential
addressCredential :: Credential, Address -> Maybe StakingCredential
addressStakingCredential :: Maybe StakingCredential }
deriving stock (Address -> Address -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Address -> Address -> Bool
$c/= :: Address -> Address -> Bool
== :: Address -> Address -> Bool
$c== :: Address -> Address -> Bool
Eq, Eq Address
Address -> Address -> Bool
Address -> Address -> Ordering
Address -> Address -> Address
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 :: Address -> Address -> Address
$cmin :: Address -> Address -> Address
max :: Address -> Address -> Address
$cmax :: Address -> Address -> Address
>= :: Address -> Address -> Bool
$c>= :: Address -> Address -> Bool
> :: Address -> Address -> Bool
$c> :: Address -> Address -> Bool
<= :: Address -> Address -> Bool
$c<= :: Address -> Address -> Bool
< :: Address -> Address -> Bool
$c< :: Address -> Address -> Bool
compare :: Address -> Address -> Ordering
$ccompare :: Address -> Address -> Ordering
Ord, Int -> Address -> ShowS
[Address] -> ShowS
Address -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Address] -> ShowS
$cshowList :: [Address] -> ShowS
show :: Address -> String
$cshow :: Address -> String
showsPrec :: Int -> Address -> ShowS
$cshowsPrec :: Int -> Address -> ShowS
Show, forall x. Rep Address x -> Address
forall x. Address -> Rep Address x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Address x -> Address
$cfrom :: forall x. Address -> Rep Address x
Generic)
deriving anyclass (Address -> ()
forall a. (a -> ()) -> NFData a
rnf :: Address -> ()
$crnf :: Address -> ()
NFData)
instance Pretty Address where
pretty :: forall ann. Address -> Doc ann
pretty (Address Credential
cred Maybe StakingCredential
stakingCred) =
let staking :: Doc ann
staking = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc ann
"no staking credential" forall a ann. Pretty a => a -> Doc ann
pretty Maybe StakingCredential
stakingCred in
forall a ann. Pretty a => a -> Doc ann
pretty Credential
cred forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall ann. Doc ann -> Doc ann
parens forall {ann}. Doc ann
staking
instance PlutusTx.Eq Address where
{-# INLINABLE (==) #-}
Address Credential
cred Maybe StakingCredential
stakingCred == :: Address -> Address -> Bool
== Address Credential
cred' Maybe StakingCredential
stakingCred' =
Credential
cred forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
cred'
Bool -> Bool -> Bool
PlutusTx.&& Maybe StakingCredential
stakingCred forall a. Eq a => a -> a -> Bool
PlutusTx.== Maybe StakingCredential
stakingCred'
{-# INLINABLE pubKeyHashAddress #-}
pubKeyHashAddress :: PubKeyHash -> Address
pubKeyHashAddress :: PubKeyHash -> Address
pubKeyHashAddress PubKeyHash
pkh = Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) forall a. Maybe a
Nothing
{-# INLINABLE toPubKeyHash #-}
toPubKeyHash :: Address -> Maybe PubKeyHash
toPubKeyHash :: Address -> Maybe PubKeyHash
toPubKeyHash (Address (PubKeyCredential PubKeyHash
k) Maybe StakingCredential
_) = forall a. a -> Maybe a
Just PubKeyHash
k
toPubKeyHash Address
_ = forall a. Maybe a
Nothing
{-# INLINABLE toScriptHash #-}
toScriptHash :: Address -> Maybe ScriptHash
toScriptHash :: Address -> Maybe ScriptHash
toScriptHash (Address (ScriptCredential ScriptHash
k) Maybe StakingCredential
_) = forall a. a -> Maybe a
Just ScriptHash
k
toScriptHash Address
_ = forall a. Maybe a
Nothing
{-# INLINABLE scriptHashAddress #-}
scriptHashAddress :: ScriptHash -> Address
scriptHashAddress :: ScriptHash -> Address
scriptHashAddress ScriptHash
vh = Credential -> Maybe StakingCredential -> Address
Address (ScriptHash -> Credential
ScriptCredential ScriptHash
vh) forall a. Maybe a
Nothing
{-# INLINABLE stakingCredential #-}
stakingCredential :: Address -> Maybe StakingCredential
stakingCredential :: Address -> Maybe StakingCredential
stakingCredential (Address Credential
_ Maybe StakingCredential
s) = Maybe StakingCredential
s
PlutusTx.makeIsDataIndexed ''Address [('Address,0)]
PlutusTx.makeLift ''Address