11{-# LANGUAGE NamedFieldPuns #-}
22
3- module Spec.NatLedger
4- ( NatValue (PValue )
5- , NatTxOut (NatTxOut , natTxOutAddress , natTxOutValue , natTxOutDatumHash )
6- , NatTxOutRef (NatTxOutRef , natTxOutRefId , natTxRefIdx )
7- , toLedgerTxOut
8- , toLedgerTxOutRef
9- , toLedgerValue
10- )
11- where
3+ module Spec.NatLedger (
4+ NatValue (PValue ),
5+ NatTxOut (NatTxOut , natTxOutAddress , natTxOutValue , natTxOutDatumHash ),
6+ NatTxOutRef (NatTxOutRef , natTxOutRefId , natTxRefIdx ),
7+ toLedgerTxOut ,
8+ toLedgerTxOutRef ,
9+ toLedgerValue ,
10+ ) where
1211
1312import BotPlutusInterface.Types ()
1413
1514import Data.Bifunctor (second )
1615import GHC.Natural (Natural )
17- import Ledger.Tx (TxOut (.. ), TxOutRef (.. ), Address )
18- import Ledger.Value (Value (Value ), CurrencySymbol , TokenName )
16+ import Ledger.Tx (Address , TxOut (.. ), TxOutRef (.. ))
17+ import Ledger.Value (CurrencySymbol , TokenName , Value (Value ))
18+ import Plutus.V1.Ledger.Api (DatumHash , TxId )
1919import PlutusTx.AssocMap qualified as AssocMap
20- import Plutus.V1.Ledger.Api (TxId , DatumHash )
21- import Test.QuickCheck (Arbitrary (arbitrary ))
20+ import Test.QuickCheck (Arbitrary (arbitrary ))
2221import Prelude
2322
24- newtype NatValue = PValue { getNatValue :: AssocMap. Map CurrencySymbol
25- (AssocMap. Map TokenName Natural )
26- } deriving newtype (Arbitrary , Show )
23+ newtype NatValue = PValue
24+ { getNatValue ::
25+ AssocMap. Map
26+ CurrencySymbol
27+ (AssocMap. Map TokenName Natural )
28+ }
29+ deriving newtype (Arbitrary , Show )
2730
2831toLedgerValue :: NatValue -> Value
29- toLedgerValue = Value
30- . AssocMap. fromList
31- . map (second $ AssocMap. fromList
32- . map (second toInteger )
33- . AssocMap. toList)
34- . AssocMap. toList . getNatValue
32+ toLedgerValue =
33+ Value
34+ . AssocMap. fromList
35+ . map
36+ ( second $
37+ AssocMap. fromList
38+ . map (second toInteger )
39+ . AssocMap. toList
40+ )
41+ . AssocMap. toList
42+ . getNatValue
3543
36- data NatTxOutRef = NatTxOutRef { natTxOutRefId :: TxId
37- , natTxRefIdx :: Natural
38- } deriving stock (Show )
44+ data NatTxOutRef = NatTxOutRef
45+ { natTxOutRefId :: TxId
46+ , natTxRefIdx :: Natural
47+ }
48+ deriving stock (Show )
3949
4050instance Arbitrary NatTxOutRef where
4151 arbitrary = do
@@ -46,10 +56,12 @@ instance Arbitrary NatTxOutRef where
4656toLedgerTxOutRef :: NatTxOutRef -> TxOutRef
4757toLedgerTxOutRef NatTxOutRef {natTxRefIdx, natTxOutRefId} = TxOutRef natTxOutRefId (toInteger natTxRefIdx)
4858
49- data NatTxOut = NatTxOut { natTxOutAddress :: Address
50- , natTxOutValue :: NatValue
51- , natTxOutDatumHash :: Maybe DatumHash
52- } deriving stock (Show )
59+ data NatTxOut = NatTxOut
60+ { natTxOutAddress :: Address
61+ , natTxOutValue :: NatValue
62+ , natTxOutDatumHash :: Maybe DatumHash
63+ }
64+ deriving stock (Show )
5365
5466instance Arbitrary NatTxOut where
5567 arbitrary = do
@@ -59,5 +71,5 @@ instance Arbitrary NatTxOut where
5971 return (NatTxOut addr value datumhash)
6072
6173toLedgerTxOut :: NatTxOut -> TxOut
62- toLedgerTxOut NatTxOut {natTxOutAddress, natTxOutValue, natTxOutDatumHash}
63- = TxOut natTxOutAddress (toLedgerValue natTxOutValue) natTxOutDatumHash
74+ toLedgerTxOut NatTxOut {natTxOutAddress, natTxOutValue, natTxOutDatumHash} =
75+ TxOut natTxOutAddress (toLedgerValue natTxOutValue) natTxOutDatumHash
0 commit comments