Skip to content

Commit

Permalink
Data-backed map for Plutus Tx
Browse files Browse the repository at this point in the history
  • Loading branch information
zliu41 committed Jan 4, 2024
1 parent c776fe7 commit 01986c3
Show file tree
Hide file tree
Showing 225 changed files with 2,551 additions and 441 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -113,8 +113,8 @@ import PlutusTx.Prelude (AdditiveGroup ((-)), AdditiveSemigroup ((+)), Bool (..)
not, otherwise, reverse, snd, ($), (&&), (++), (||))

import PlutusLedgerApi.V2 qualified as Val
import PlutusTx.AssocMap qualified as Map
import PlutusTx.Builtins qualified as Builtins
import PlutusTx.DataMap qualified as Map
import Prelude qualified as Haskell


Expand Down Expand Up @@ -322,19 +322,20 @@ evalObservation env state obs = let

-- | Pick the first account with money in it.
refundOne :: Accounts -> Maybe ((Party, Token, Integer), Accounts)
refundOne accounts = case Map.toList accounts of
[] -> Nothing
-- SCP-5126: The return value of this function differs from
-- Isabelle semantics in that it returns the least-recently
-- added account-token combination rather than the first
-- lexicographically ordered one. Also, the sequence
-- `Map.fromList . tail . Map.toList` preserves the
-- invariants of order and non-duplication.
((accId, token), balance) : rest ->
if balance > 0
then Just ((accId, token, balance), Map.fromList rest)
else refundOne (Map.fromList rest)

refundOne accounts =
if Map.null accounts
then Nothing
else
-- SCP-5126: The return value of this function differs from
-- Isabelle semantics in that it returns the least-recently
-- added account-token combination rather than the first
-- lexicographically ordered one. Also, the sequence
-- `Map.fromList . tail . Map.toList` preserves the
-- invariants of order and non-duplication.
let (((accId, token), balance), rest) = Map.unsafeUncons accounts
in if balance > 0
then Just ((accId, token, balance), rest)
else refundOne rest

-- | Obtains the amount of money available an account.
moneyInAccount :: AccountId -> Token -> Accounts -> Integer
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ import GHC.Generics (Generic)
import PlutusBenchmark.Marlowe.Core.V1.Semantics.Types.Address (Network)
import PlutusLedgerApi.V2 (CurrencySymbol, POSIXTime (..), TokenName)
import PlutusTx.AsData (asData)
import PlutusTx.AssocMap (Map)
import PlutusTx.DataMap (Map)
import PlutusTx.IsData (FromData, ToData, UnsafeFromData, makeIsDataIndexed, unstableMakeIsData)
import PlutusTx.Lift (makeLift)
import PlutusTx.Prelude (Bool (..), BuiltinByteString, Eq (..), Integer, Ord ((<=), (>=)), any,
Expand All @@ -52,7 +52,7 @@ import PlutusTx.Prelude (Bool (..), BuiltinByteString, Eq (..), Integer, Ord ((<
import PlutusLedgerApi.V1.Value qualified as Val
import PlutusLedgerApi.V2 qualified as Ledger (Address (..), Credential (..), PubKeyHash (..),
ScriptHash (..), StakingCredential (..))
import PlutusTx.AssocMap qualified as Map
import PlutusTx.DataMap qualified as Map
import Prelude qualified as Haskell

deriving stock instance Data POSIXTime
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -68,10 +68,9 @@ import PlutusTx.Plugin ()
import PlutusTx.Prelude as PlutusTxPrelude (AdditiveGroup ((-)), AdditiveMonoid (zero),
AdditiveSemigroup ((+)), Bool (..), BuiltinByteString,
BuiltinData, BuiltinString, Enum (fromEnum), Eq (..),
Functor (fmap), Integer, Maybe (..), Ord ((>)),
Semigroup ((<>)), all, any, check, elem, filter, find,
foldMap, null, otherwise, snd, toBuiltin, ($), (&&),
(.), (/=), (||))
Functor (fmap), Maybe (..), Ord ((>)), Semigroup ((<>)),
all, any, check, filter, find, foldMap, null, otherwise,
snd, toBuiltin, ($), (&&), (.), (/=), (||))

import Cardano.Crypto.Hash qualified as Hash
import Data.ByteString qualified as BS
Expand All @@ -82,6 +81,7 @@ import PlutusLedgerApi.V1.Value qualified as Val
import PlutusLedgerApi.V2 qualified as Ledger (Address (Address))
import PlutusTx qualified
import PlutusTx.AssocMap qualified as AssocMap
import PlutusTx.DataMap qualified as Map
import PlutusTx.Trace (traceError, traceIfFalse)
import Prelude qualified as Haskell

Expand Down Expand Up @@ -265,29 +265,16 @@ mkMarloweValidator
-- Check a state for the correct value, positive accounts, and no duplicates.
checkState :: BuiltinString -> Val.Value -> State -> Bool
checkState tag expected State{..} =
let
positiveBalance :: (a, Integer) -> Bool
positiveBalance (_, balance) = balance > 0
noDuplicates :: Eq k => AssocMap.Map k v -> Bool
noDuplicates am =
let
test [] = True -- An empty list has no duplicates.
test (x : xs) -- Look for a duplicate of the head in the tail.
| elem x xs = False -- A duplicate is present.
| otherwise = test xs -- Continue searching for a duplicate.
in
test $ AssocMap.keys am
in
-- [Marlowe-Cardano Specification: "Constraint 5. Input value from script".]
-- and/or
-- [Marlowe-Cardano Specification: "Constraint 18. Final balance."]
traceIfFalse ("v" <> tag) (totalBalance accounts == expected)
-- [Marlowe-Cardano Specification: "Constraint 13. Positive balances".]
&& traceIfFalse ("b" <> tag) (all positiveBalance $ AssocMap.toList accounts)
&& traceIfFalse ("b" <> tag) (Map.all (> 0) accounts)
-- [Marlowe-Cardano Specification: "Constraint 19. No duplicates".]
&& traceIfFalse ("ea" <> tag) (noDuplicates accounts)
&& traceIfFalse ("ec" <> tag) (noDuplicates choices)
&& traceIfFalse ("eb" <> tag) (noDuplicates boundValues)
&& traceIfFalse ("ea" <> tag) (Map.noDuplicateKeys accounts)
&& traceIfFalse ("ec" <> tag) (Map.noDuplicateKeys choices)
&& traceIfFalse ("eb" <> tag) (Map.noDuplicateKeys boundValues)

-- Look up the Datum hash for specific data.
findDatumHash' :: PlutusTx.ToData o => o -> Maybe DatumHash
Expand Down
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 215190496
| mem: 740280})
({cpu: 216800496
| mem: 747280})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 318563258
| mem: 1148984})
({cpu: 321921258
| mem: 1163584})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 233064631
| mem: 813142})
({cpu: 235778631
| mem: 824942})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 193813161
| mem: 665714})
({cpu: 195607161
| mem: 673514})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 215630084
| mem: 741820})
({cpu: 217332084
| mem: 749220})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 198410174
| mem: 675264})
({cpu: 199606174
| mem: 680464})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 196916597
| mem: 670062})
({cpu: 198112597
| mem: 675262})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 242350272
| mem: 842458})
({cpu: 244512272
| mem: 851858})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 231983448
| mem: 807632})
({cpu: 234099448
| mem: 816832})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 212366629
| mem: 731700})
({cpu: 214114629
| mem: 739300})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 228876366
| mem: 790180})
({cpu: 230486366
| mem: 797180})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 237522811
| mem: 833156})
({cpu: 239684811
| mem: 842556})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 271106152
| mem: 953580})
({cpu: 274464152
| mem: 968180})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 194025187
| mem: 663336})
({cpu: 195267187
| mem: 668736})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 211186829
| mem: 726696})
({cpu: 213348829
| mem: 736096})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 195543413
| mem: 663662})
({cpu: 197337413
| mem: 671462})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 231957108
| mem: 816128})
({cpu: 233659108
| mem: 823528})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 208852885
| mem: 721874})
({cpu: 211152885
| mem: 731874})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 210080867
| mem: 737000})
({cpu: 212334867
| mem: 746800})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 236972199
| mem: 830902})
({cpu: 240100199
| mem: 844502})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 197071500
| mem: 677660})
({cpu: 198359500
| mem: 683260})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 221821467
| mem: 767608})
({cpu: 223983467
| mem: 777008})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 215190496
| mem: 740280})
({cpu: 216800496
| mem: 747280})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 229625754
| mem: 799928})
({cpu: 231235754
| mem: 806928})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 201406281
| mem: 686966})
({cpu: 203108281
| mem: 694366})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 198198210
| mem: 677642})
({cpu: 199946210
| mem: 685242})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 197821685
| mem: 673962})
({cpu: 199017685
| mem: 679162})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 192531548
| mem: 658134})
({cpu: 193773548
| mem: 663534})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 218883854
| mem: 752828})
({cpu: 220585854
| mem: 760228})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 206252520
| mem: 706212})
({cpu: 207448520
| mem: 711412})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 223621194
| mem: 779702})
({cpu: 225783194
| mem: 789102})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 201406281
| mem: 686966})
({cpu: 203108281
| mem: 694366})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 188734988
| mem: 647508})
({cpu: 190022988
| mem: 653108})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 211833524
| mem: 731194})
({cpu: 213581524
| mem: 738794})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 194025125
| mem: 663336})
({cpu: 195267125
| mem: 668736})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 194025125
| mem: 663336})
({cpu: 195267125
| mem: 668736})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 233147796
| mem: 807900})
({cpu: 235171796
| mem: 816700})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 204935205
| mem: 705448})
({cpu: 206683205
| mem: 713048})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 232567113
| mem: 815654})
({cpu: 235189113
| mem: 827054})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 215190496
| mem: 740280})
({cpu: 216800496
| mem: 747280})
Loading

0 comments on commit 01986c3

Please sign in to comment.