{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module Test.Cardano.Ledger.Mary.Golden (
goldenScaledMinDeposit,
pid1,
pid2,
pid3,
smallName,
smallestName,
realName,
minUTxO,
largestName,
) where
import Cardano.Ledger.Allegra.Scripts (
pattern RequireTimeExpire,
pattern RequireTimeStart,
)
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Core (hashScript)
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Mary.TxOut (scaledMinDeposit)
import Cardano.Ledger.Mary.Value (AssetName (..), MaryValue (..), MultiAsset (..), PolicyID (..))
import Cardano.Ledger.Shelley.Scripts
import Cardano.Ledger.Slot (SlotNo (..))
import qualified Data.ByteString.Short as SBS
import qualified Data.Map.Strict as Map
import qualified Data.Sequence.Strict as StrictSeq
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.Word (Word8)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (testCase, (@?=))
pid1 :: PolicyID
pid1 :: PolicyID
pid1 =
ScriptHash -> PolicyID
PolicyID (ScriptHash -> PolicyID) -> ScriptHash -> PolicyID
forall a b. (a -> b) -> a -> b
$
forall era. EraScript era => Script era -> ScriptHash
hashScript @MaryEra (Script MaryEra -> ScriptHash) -> Script MaryEra -> ScriptHash
forall a b. (a -> b) -> a -> b
$
StrictSeq (NativeScript MaryEra) -> NativeScript MaryEra
forall era.
ShelleyEraScript era =>
StrictSeq (NativeScript era) -> NativeScript era
RequireAllOf ([Timelock MaryEra] -> StrictSeq (Timelock MaryEra)
forall a. [a] -> StrictSeq a
StrictSeq.fromList [])
pid2 :: PolicyID
pid2 :: PolicyID
pid2 =
ScriptHash -> PolicyID
PolicyID (ScriptHash -> PolicyID) -> ScriptHash -> PolicyID
forall a b. (a -> b) -> a -> b
$
forall era. EraScript era => Script era -> ScriptHash
hashScript @MaryEra (Script MaryEra -> ScriptHash) -> Script MaryEra -> ScriptHash
forall a b. (a -> b) -> a -> b
$
StrictSeq (NativeScript MaryEra) -> NativeScript MaryEra
forall era.
ShelleyEraScript era =>
StrictSeq (NativeScript era) -> NativeScript era
RequireAllOf ([Timelock MaryEra] -> StrictSeq (Timelock MaryEra)
forall a. [a] -> StrictSeq a
StrictSeq.fromList [SlotNo -> NativeScript MaryEra
forall era. AllegraEraScript era => SlotNo -> NativeScript era
RequireTimeStart (Word64 -> SlotNo
SlotNo Word64
1)])
pid3 :: PolicyID
pid3 :: PolicyID
pid3 =
ScriptHash -> PolicyID
PolicyID (ScriptHash -> PolicyID) -> ScriptHash -> PolicyID
forall a b. (a -> b) -> a -> b
$
forall era. EraScript era => Script era -> ScriptHash
hashScript @MaryEra (Script MaryEra -> ScriptHash) -> Script MaryEra -> ScriptHash
forall a b. (a -> b) -> a -> b
$
StrictSeq (NativeScript MaryEra) -> NativeScript MaryEra
forall era.
ShelleyEraScript era =>
StrictSeq (NativeScript era) -> NativeScript era
RequireAllOf ([Timelock MaryEra] -> StrictSeq (Timelock MaryEra)
forall a. [a] -> StrictSeq a
StrictSeq.fromList [SlotNo -> NativeScript MaryEra
forall era. AllegraEraScript era => SlotNo -> NativeScript era
RequireTimeExpire (Word64 -> SlotNo
SlotNo Word64
1)])
smallestName :: AssetName
smallestName :: AssetName
smallestName = ShortByteString -> AssetName
AssetName (ShortByteString -> AssetName) -> ShortByteString -> AssetName
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
SBS.pack []
smallName :: Word8 -> AssetName
smallName :: Word8 -> AssetName
smallName Word8
c = ShortByteString -> AssetName
AssetName (ShortByteString -> AssetName) -> ShortByteString -> AssetName
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
SBS.pack [Word8
c]
largestName :: Word8 -> AssetName
largestName :: Word8 -> AssetName
largestName Word8
c = ShortByteString -> AssetName
AssetName (ShortByteString -> AssetName)
-> ([Word8] -> ShortByteString) -> [Word8] -> AssetName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ShortByteString
SBS.pack ([Word8] -> AssetName) -> [Word8] -> AssetName
forall a b. (a -> b) -> a -> b
$ Word8
c Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
: [Word8
1 .. Word8
31]
realName :: AssetName
realName :: AssetName
realName = ShortByteString -> AssetName
AssetName (ShortByteString -> AssetName)
-> (String -> ShortByteString) -> String -> AssetName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
SBS.toShort (ByteString -> ShortByteString)
-> (String -> ByteString) -> String -> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> AssetName) -> String -> AssetName
forall a b. (a -> b) -> a -> b
$ String
"ATADAcoin"
minUTxO :: Coin
minUTxO :: Coin
minUTxO = Integer -> Coin
Coin (Integer -> Coin) -> Integer -> Coin
forall a b. (a -> b) -> a -> b
$ Integer
1000 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
1000
goldenScaledMinDeposit :: TestTree
goldenScaledMinDeposit :: TestTree
goldenScaledMinDeposit =
String -> [TestTree] -> TestTree
testGroup
String
"golden tests - scaledMinDeposit"
[ String -> Assertion -> TestTree
testCase String
"one policy, one (smallest) name" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1407406) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
PolicyID
-> Map AssetName Integer -> Map PolicyID (Map AssetName Integer)
forall k a. k -> a -> Map k a
Map.singleton PolicyID
pid1 ([(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(AssetName
smallestName, Integer
1)])
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1407406
, String -> Assertion -> TestTree
testCase String
"one policy, one (small) name" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1444443) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
PolicyID
-> Map AssetName Integer -> Map PolicyID (Map AssetName Integer)
forall k a. k -> a -> Map k a
Map.singleton
PolicyID
pid1
([(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Word8 -> AssetName
smallName Word8
1, Integer
1)])
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1444443
, String -> Assertion -> TestTree
testCase String
"one policy, one (real) name" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1444443) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
PolicyID
-> Map AssetName Integer -> Map PolicyID (Map AssetName Integer)
forall k a. k -> a -> Map k a
Map.singleton
PolicyID
pid1
([(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(AssetName
realName, Integer
1)])
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1481480
, String -> Assertion -> TestTree
testCase String
"one policy, three (small) name" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1555554) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
PolicyID
-> Map AssetName Integer -> Map PolicyID (Map AssetName Integer)
forall k a. k -> a -> Map k a
Map.singleton
PolicyID
pid1
( [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[ (Word8 -> AssetName
smallName Word8
1, Integer
1)
, (Word8 -> AssetName
smallName Word8
2, Integer
1)
, (Word8 -> AssetName
smallName Word8
3, Integer
1)
]
)
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1555554
, String -> Assertion -> TestTree
testCase String
"one policy, one (largest) name" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1555554) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
PolicyID
-> Map AssetName Integer -> Map PolicyID (Map AssetName Integer)
forall k a. k -> a -> Map k a
Map.singleton
PolicyID
pid1
([(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Word8 -> AssetName
largestName Word8
65, Integer
1)])
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1555554
, String -> Assertion -> TestTree
testCase String
"one policy, three (largest) name" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1962961) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
PolicyID
-> Map AssetName Integer -> Map PolicyID (Map AssetName Integer)
forall k a. k -> a -> Map k a
Map.singleton
PolicyID
pid1
( [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[ (Word8 -> AssetName
largestName Word8
65, Integer
1)
, (Word8 -> AssetName
largestName Word8
66, Integer
1)
, (Word8 -> AssetName
largestName Word8
67, Integer
1)
]
)
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1962961
, String -> Assertion -> TestTree
testCase String
"two policies, one (smallest) name" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1592591) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
[(PolicyID, Map AssetName Integer)]
-> Map PolicyID (Map AssetName Integer)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[
( PolicyID
pid1
, [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(AssetName
smallestName, Integer
1)]
)
,
( PolicyID
pid2
, [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(AssetName
smallestName, Integer
1)]
)
]
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1592591
, String -> Assertion -> TestTree
testCase String
"two policies, two (small) names" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
1629628) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
[(PolicyID, Map AssetName Integer)]
-> Map PolicyID (Map AssetName Integer)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[
( PolicyID
pid1
, [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Word8 -> AssetName
smallName Word8
1, Integer
1)]
)
,
( PolicyID
pid2
, [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Word8 -> AssetName
smallName Word8
2, Integer
1)]
)
]
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
1629628
, String -> Assertion -> TestTree
testCase String
"three policies, ninety-six (small) names" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
MaryValue -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit
( Coin -> MultiAsset -> MaryValue
MaryValue (Integer -> Coin
Coin Integer
7407400) (MultiAsset -> MaryValue) -> MultiAsset -> MaryValue
forall a b. (a -> b) -> a -> b
$
Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (Map PolicyID (Map AssetName Integer) -> MultiAsset)
-> Map PolicyID (Map AssetName Integer) -> MultiAsset
forall a b. (a -> b) -> a -> b
$
[(PolicyID, Map AssetName Integer)]
-> Map PolicyID (Map AssetName Integer)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[
( PolicyID
pid1
, [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(AssetName, Integer)] -> Map AssetName Integer)
-> [(AssetName, Integer)] -> Map AssetName Integer
forall a b. (a -> b) -> a -> b
$ (Word8 -> (AssetName, Integer))
-> [Word8] -> [(AssetName, Integer)]
forall a b. (a -> b) -> [a] -> [b]
map ((,Integer
1) (AssetName -> (AssetName, Integer))
-> (Word8 -> AssetName) -> Word8 -> (AssetName, Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> AssetName
smallName) [Word8
32 .. Word8
63]
)
,
( PolicyID
pid2
, [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(AssetName, Integer)] -> Map AssetName Integer)
-> [(AssetName, Integer)] -> Map AssetName Integer
forall a b. (a -> b) -> a -> b
$ (Word8 -> (AssetName, Integer))
-> [Word8] -> [(AssetName, Integer)]
forall a b. (a -> b) -> [a] -> [b]
map ((,Integer
1) (AssetName -> (AssetName, Integer))
-> (Word8 -> AssetName) -> Word8 -> (AssetName, Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> AssetName
smallName) [Word8
64 .. Word8
95]
)
,
( PolicyID
pid3
, [(AssetName, Integer)] -> Map AssetName Integer
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(AssetName, Integer)] -> Map AssetName Integer)
-> [(AssetName, Integer)] -> Map AssetName Integer
forall a b. (a -> b) -> a -> b
$ (Word8 -> (AssetName, Integer))
-> [Word8] -> [(AssetName, Integer)]
forall a b. (a -> b) -> [a] -> [b]
map ((,Integer
1) (AssetName -> (AssetName, Integer))
-> (Word8 -> AssetName) -> Word8 -> (AssetName, Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> AssetName
smallName) [Word8
96 .. Word8
127]
)
]
)
Coin
minUTxO
Coin -> Coin -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Integer -> Coin
Coin Integer
7407400
]