11module Cardano.CEM.Address (
2- AddressBech32 (MkAddressBech32 , unAddressBech32 ),
3- cardanoAddressBech32 ,
4- scriptCredential ,
5- scriptCardanoAddress ,
62 cemScriptAddress ,
3+ cemScriptPlutusCredential ,
4+ cemScriptPlutusAddress ,
75 plutusAddressToShelleyAddress ,
86) where
97
10- import Cardano.Api qualified
11- import Cardano.Api.Address qualified
12- import Cardano.Api.Ledger qualified
8+ import Cardano.Api qualified as C
9+ import Cardano.Api.Address qualified as C ( Address ( .. ))
10+ import Cardano.Api.Ledger qualified as C
1311import Cardano.CEM.OnChain (CEMScriptCompiled (cemScriptCompiled ))
14- import Cardano.CEM.OnChain qualified as Compiled
15- import Cardano.Crypto.Hash qualified as Cardano.Hash
16- import Cardano.Ledger.BaseTypes qualified as Ledger
17- import Cardano.Ledger.Credential qualified as Cred
18- import Cardano.Ledger.Hashes qualified
19- import Cardano.Ledger.Keys qualified as Ledger.Keys
12+ import Cardano.Crypto.Hash qualified as Crypto
13+ import Cardano.Ledger.BaseTypes qualified as L
14+ import Cardano.Ledger.Credential qualified as L
15+ import Cardano.Ledger.Hashes qualified as L
16+ import Cardano.Ledger.Keys qualified as L
2017import Data.Proxy (Proxy )
21- import Data.String (IsString )
22- import Data.Text qualified as T
2318import Plutarch.LedgerApi (scriptHash )
2419import Plutarch.Script (serialiseScript )
2520import Plutus.Extras (scriptValidatorHash )
26- import PlutusLedgerApi.V1 qualified
27- import PlutusLedgerApi.V1.Address ( Address , scriptHashAddress )
21+ import PlutusLedgerApi.V1 qualified as P
22+ import PlutusLedgerApi.V1.Address qualified as P ( scriptHashAddress )
2823import Prelude
2924
30- newtype AddressBech32 = MkAddressBech32 { unAddressBech32 :: T. Text}
31- deriving newtype (Eq , Show , IsString )
32-
33- cardanoAddressBech32 :: Cardano.Api. Address Cardano.Api. ShelleyAddr -> AddressBech32
34- cardanoAddressBech32 = MkAddressBech32 . Cardano.Api. serialiseToBech32
35-
36- {-# INLINEABLE cemScriptAddress #-}
3725cemScriptAddress ::
38- forall script . (CEMScriptCompiled script ) => Proxy script -> Address
39- cemScriptAddress =
40- scriptHashAddress . scriptValidatorHash . serialiseScript . cemScriptCompiled
41-
42- scriptCardanoAddress ::
4326 forall script .
44- (Compiled. CEMScriptCompiled script ) =>
45- Cardano.Api.Ledger . Network ->
27+ (CEMScriptCompiled script ) =>
28+ C . Network ->
4629 Proxy script ->
47- Either String (Cardano.Api. Address Cardano.Api . ShelleyAddr )
48- scriptCardanoAddress network =
30+ Either String (C. Address C . ShelleyAddr )
31+ cemScriptAddress network =
4932 plutusAddressToShelleyAddress network
50- . flip PlutusLedgerApi.V1. Address Nothing
51- . scriptCredential
33+ . flip P. Address Nothing
34+ . cemScriptPlutusCredential
35+
36+ {-# INLINEABLE cemScriptPlutusAddress #-}
37+ cemScriptPlutusAddress ::
38+ forall script . (CEMScriptCompiled script ) => Proxy script -> P. Address
39+ cemScriptPlutusAddress =
40+ P. scriptHashAddress
41+ . scriptValidatorHash
42+ . serialiseScript
43+ . cemScriptCompiled
5244
53- scriptCredential ::
45+ cemScriptPlutusCredential ::
5446 forall script .
55- (Compiled. CEMScriptCompiled script ) =>
47+ (CEMScriptCompiled script ) =>
5648 Proxy script ->
57- PlutusLedgerApi.V1 . Credential
58- scriptCredential =
59- PlutusLedgerApi.V1 . ScriptCredential
49+ P . Credential
50+ cemScriptPlutusCredential =
51+ P . ScriptCredential
6052 . scriptHash
61- . Compiled. cemScriptCompiled
53+ . cemScriptCompiled
6254
6355plutusAddressToShelleyAddress ::
64- Cardano.Api.Ledger . Network ->
65- PlutusLedgerApi.V1 . Address ->
66- Either String (Cardano.Api. Address Cardano.Api . ShelleyAddr )
67- plutusAddressToShelleyAddress network (PlutusLedgerApi.V1 . Address payment stake) = do
56+ L . Network ->
57+ P . Address ->
58+ Either String (C. Address C . ShelleyAddr )
59+ plutusAddressToShelleyAddress network (P . Address payment stake) = do
6860 paymentCred <-
6961 maybe
7062 (Left " plutusAddressToShelleyAddress:can't decode payment credential" )
@@ -75,36 +67,36 @@ plutusAddressToShelleyAddress network (PlutusLedgerApi.V1.Address payment stake)
7567 (Left " plutusAddressToShelleyAddress:can't decode stake credential" )
7668 Right
7769 stakeCredential
78- pure $ Cardano.Api.Address . ShelleyAddress network paymentCred stakeCred
70+ pure $ C . ShelleyAddress network paymentCred stakeCred
7971 where
8072 credentialToCardano
81- ( PlutusLedgerApi.V1 . PubKeyCredential
82- (PlutusLedgerApi.V1 . PubKeyHash pkh)
73+ ( P . PubKeyCredential
74+ (P . PubKeyHash pkh)
8375 ) =
84- Cred . KeyHashObj
85- . Ledger.Keys . KeyHash
86- <$> Cardano.Hash . hashFromBytes
87- (PlutusLedgerApi.V1 . fromBuiltin pkh)
76+ L . KeyHashObj
77+ . L . KeyHash
78+ <$> Crypto . hashFromBytes
79+ (P . fromBuiltin pkh)
8880 credentialToCardano
89- ( PlutusLedgerApi.V1 . ScriptCredential
90- (PlutusLedgerApi.V1. ScriptHash hash)
81+ ( P . ScriptCredential
82+ (P. ScriptHash hash' )
9183 ) =
92- Cred . ScriptHashObj
93- . Cardano.Ledger.Hashes . ScriptHash
94- <$> Cardano.Hash . hashFromBytes
95- (PlutusLedgerApi.V1. fromBuiltin hash)
84+ L . ScriptHashObj
85+ . L . ScriptHash
86+ <$> Crypto . hashFromBytes
87+ (P. fromBuiltin hash' )
9688
9789 paymentCredential = credentialToCardano payment
9890 stakeCredential = case stake of
99- Nothing -> Just Cardano.Api.Ledger . StakeRefNull
91+ Nothing -> Just L . StakeRefNull
10092 Just ref -> case ref of
101- PlutusLedgerApi.V1 . StakingHash cred ->
102- Cardano.Api.Ledger . StakeRefBase
93+ P . StakingHash cred ->
94+ L . StakeRefBase
10395 <$> credentialToCardano cred
104- PlutusLedgerApi.V1 . StakingPtr slotNo txIx sertId ->
96+ P . StakingPtr slotNo txIx sertId ->
10597 Just $
106- Cardano.Api.Ledger . StakeRefPtr $
107- Cred . Ptr
108- (Ledger . SlotNo $ fromInteger slotNo)
109- (Ledger . TxIx $ fromInteger txIx)
110- (Ledger . CertIx $ fromInteger sertId)
98+ L . StakeRefPtr $
99+ L . Ptr
100+ (L . SlotNo $ fromInteger slotNo)
101+ (L . TxIx $ fromInteger txIx)
102+ (L . CertIx $ fromInteger sertId)
0 commit comments