Skip to content

Commit

Permalink
golden for min-utxo
Browse files Browse the repository at this point in the history
  • Loading branch information
polinavino committed Apr 16, 2021
1 parent 7a24a6e commit d6ee968
Show file tree
Hide file tree
Showing 2 changed files with 138 additions and 0 deletions.
1 change: 1 addition & 0 deletions alonzo/impl/cardano-ledger-alonzo.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,7 @@ test-suite cardano-ledger-alonzo-test
other-modules:
Test.Cardano.Ledger.Alonzo.Serialisation.Tripping
Test.Cardano.Ledger.Alonzo.Serialisation.CDDL
Test.Cardano.Ledger.Alonzo.Golden
build-depends:
base16-bytestring,
bytestring,
Expand Down
137 changes: 137 additions & 0 deletions alonzo/impl/test/test/Test/Cardano/Ledger/Alonzo/Golden.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,137 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}

-- |
-- Module : Test.Cardano.Ledger.Mary.Golden
-- Description : Golden Tests for the Mary era
module Test.Cardano.Ledger.Alonzo.Golden
( goldenUTxOEntryMinAda
)
where

import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Mary.Value (AssetName (..), PolicyID (..), Value (..))
import Cardano.Ledger.ShelleyMA.Rules.Utxo (scaledMinDeposit)
import Cardano.Ledger.ShelleyMA.Timelocks (Timelock (..))
import qualified Data.ByteString.Char8 as BS
import Data.Char (chr)
import qualified Data.Map.Strict as Map
import qualified Data.Sequence.Strict as StrictSeq
import Shelley.Spec.Ledger.Slot (SlotNo (..))
import Shelley.Spec.Ledger.Tx (hashScript)
import Test.Cardano.Ledger.EraBuffet (StandardCrypto)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (testCase, (@?=))
import Test.Cardano.Ledger.Mary.Golden

goldenScaledMinDeposit :: TestTree
goldenScaledMinDeposit =
testGroup
"golden tests - UTxOEntryMinAda"
[ testCase "one policy, one (smallest) name, no datum hash" $
scaledMinDeposit
( Value 1407406 $
Map.singleton pid1 (Map.fromList [(smallestName, 1)])
)
minUTxO
@?= Coin 1407406,
testCase "one policy, one (smallest) name, yes datum hash" $
scaledMinDeposit
( Value 1407406 $
Map.singleton pid1 (Map.fromList [(smallestName, 1)])
)
minUTxO
@?= Coin 1407406,
testCase "one policy, one (small) name" $
scaledMinDeposit
( Value 1444443 $
Map.singleton
pid1
(Map.fromList [(smallName '1', 1)])
)
minUTxO
@?= Coin 1444443,
testCase "one policy, three (small) name" $
scaledMinDeposit
( Value 1555554 $
Map.singleton
pid1
( Map.fromList
[ (smallName '1', 1),
(smallName '2', 1),
(smallName '3', 1)
]
)
)
minUTxO
@?= Coin 1555554,
testCase "one policy, one (largest) name" $
scaledMinDeposit
( Value 1555554 $
Map.singleton
pid1
(Map.fromList [(largestName 'a', 1)])
)
minUTxO
@?= Coin 1555554,
testCase "one policy, three (largest) name" $
scaledMinDeposit
( Value 1962961 $
Map.singleton
pid1
( Map.fromList
[ (largestName 'a', 1),
(largestName 'b', 1),
(largestName 'c', 1)
]
)
)
minUTxO
@?= Coin 1962961,
testCase "two policies, one (smallest) name" $
scaledMinDeposit
( Value 1592591 $
Map.fromList
[ ( pid1,
(Map.fromList [(smallestName, 1)])
),
( pid2,
(Map.fromList [(smallestName, 1)])
)
]
)
minUTxO
@?= Coin 1592591,
testCase "two policies, two (small) names" $
scaledMinDeposit
( Value 1629628 $
Map.fromList
[ ( pid1,
(Map.fromList [(smallName '1', 1)])
),
( pid2,
(Map.fromList [(smallName '2', 1)])
)
]
)
minUTxO
@?= Coin 1629628,
testCase "three policies, ninety-six (small) names" $
scaledMinDeposit
( Value 7407400 $
Map.fromList
[ ( pid1,
(Map.fromList $ map ((,1) . smallName . chr) [32 .. 63])
),
( pid2,
(Map.fromList $ map ((,1) . smallName . chr) [64 .. 95])
),
( pid3,
(Map.fromList $ map ((,1) . smallName . chr) [96 .. 127])
)
]
)
minUTxO
@?= Coin 7407400
]

0 comments on commit d6ee968

Please sign in to comment.