{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
module Test.Cardano.Ledger.ValueFromList where
import Cardano.Ledger.Coin
import Cardano.Ledger.Crypto
import Cardano.Ledger.Mary.Value as Mary (
AssetName,
MaryValue (..),
MultiAsset (..),
PolicyID (..),
insertMultiAsset,
multiAssetFromList,
)
import Cardano.Ledger.Val as Val
import Data.Map.Strict as Map
class Val.Val val => ValueFromList val c | val -> c where
valueFromList :: Integer -> [(PolicyID c, AssetName, Integer)] -> val
insert :: (Integer -> Integer -> Integer) -> PolicyID c -> AssetName -> Integer -> val -> val
gettriples :: val -> (Integer, [(PolicyID c, AssetName, Integer)])
instance Crypto c => ValueFromList (MaryValue c) c where
valueFromList :: Integer -> [(PolicyID c, AssetName, Integer)] -> MaryValue c
valueFromList Integer
c [(PolicyID c, AssetName, Integer)]
triples = forall c. Coin -> MultiAsset c -> MaryValue c
MaryValue (Integer -> Coin
Coin Integer
c) (forall era. [(PolicyID era, AssetName, Integer)] -> MultiAsset era
Mary.multiAssetFromList [(PolicyID c, AssetName, Integer)]
triples)
insert :: (Integer -> Integer -> Integer)
-> PolicyID c -> AssetName -> Integer -> MaryValue c -> MaryValue c
insert Integer -> Integer -> Integer
combine PolicyID c
pid AssetName
an Integer
new (MaryValue Coin
c MultiAsset c
ma) = forall c. Coin -> MultiAsset c -> MaryValue c
MaryValue Coin
c forall a b. (a -> b) -> a -> b
$ forall c.
(Integer -> Integer -> Integer)
-> PolicyID c
-> AssetName
-> Integer
-> MultiAsset c
-> MultiAsset c
Mary.insertMultiAsset Integer -> Integer -> Integer
combine PolicyID c
pid AssetName
an Integer
new MultiAsset c
ma
gettriples :: MaryValue c -> (Integer, [(PolicyID c, AssetName, Integer)])
gettriples (MaryValue (Coin Integer
c) (MultiAsset Map (PolicyID c) (Map AssetName Integer)
m1)) = (Integer
c, [(PolicyID c, AssetName, Integer)]
triples)
where
triples :: [(PolicyID c, AssetName, Integer)]
triples =
[ (PolicyID c
policyId, AssetName
aname, Integer
amount)
| (PolicyID c
policyId, Map AssetName Integer
m2) <- forall k a. Map k a -> [(k, a)]
Map.toList Map (PolicyID c) (Map AssetName Integer)
m1
, (AssetName
aname, Integer
amount) <- forall k a. Map k a -> [(k, a)]
Map.toList Map AssetName Integer
m2
]