-
Notifications
You must be signed in to change notification settings - Fork 155
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Start establishing the framework for Alonzo tests, so far just including roundtrip tests. We include a roundtrip CBOR test for TxWitness.
- Loading branch information
Showing
5 changed files
with
160 additions
and
1 deletion.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
49 changes: 49 additions & 0 deletions
49
alonzo/impl/test/lib/Test/Cardano/Ledger/Alonzo/Serialisation/Generators.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,49 @@ | ||
{-# LANGUAGE FlexibleContexts #-} | ||
{-# LANGUAGE FlexibleInstances #-} | ||
{-# LANGUAGE TypeFamilies #-} | ||
{-# LANGUAGE UndecidableInstances #-} | ||
|
||
module Test.Cardano.Ledger.Alonzo.Serialisation.Generators where | ||
|
||
import Cardano.Ledger.Alonzo (AlonzoEra) | ||
import Cardano.Ledger.Alonzo.Data (Data (..)) | ||
import Cardano.Ledger.Alonzo.Scripts | ||
import Cardano.Ledger.Alonzo.TxWitness | ||
import qualified Cardano.Ledger.Core as Core | ||
import qualified Cardano.Ledger.Crypto as CC | ||
import Cardano.Ledger.Era (Crypto) | ||
import Cardano.Ledger.Shelley.Constraints (ShelleyBased) | ||
import Cardano.Ledger.ShelleyMA.Timelocks | ||
import Cardano.Slotting.Slot (SlotNo (..)) | ||
import Test.QuickCheck | ||
import Test.Shelley.Spec.Ledger.ConcreteCryptoTypes (Mock) | ||
import Test.Shelley.Spec.Ledger.Serialisation.EraIndepGenerators () | ||
|
||
-- TODO correct arbitrary generator for Data | ||
instance Arbitrary (Data era) where | ||
arbitrary = pure NotReallyData | ||
|
||
instance Arbitrary Tag where | ||
arbitrary = elements [Input, Mint, Cert, Wdrl] | ||
|
||
instance Arbitrary RdmrPtr where | ||
arbitrary = RdmrPtr <$> arbitrary <*> arbitrary | ||
|
||
-- TODO correct arbitrary generator for Alonzo scripts | ||
instance CC.Crypto c => Arbitrary (Timelock (AlonzoEra c)) where | ||
arbitrary = pure $ RequireTimeStart (SlotNo 0) | ||
|
||
instance | ||
( ShelleyBased era, | ||
Mock (Crypto era), | ||
Arbitrary (Core.Script era) | ||
) => | ||
Arbitrary (TxWitness era) | ||
where | ||
arbitrary = | ||
TxWitness | ||
<$> arbitrary | ||
<*> arbitrary | ||
<*> arbitrary | ||
<*> arbitrary | ||
<*> arbitrary |
44 changes: 44 additions & 0 deletions
44
alonzo/impl/test/test/Test/Cardano/Ledger/Alonzo/Serialisation/Tripping.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,44 @@ | ||
{-# LANGUAGE FlexibleContexts #-} | ||
{-# LANGUAGE TypeApplications #-} | ||
|
||
module Test.Cardano.Ledger.Alonzo.Serialisation.Tripping where | ||
|
||
import Cardano.Binary | ||
import Cardano.Ledger.Alonzo | ||
import Cardano.Ledger.Alonzo.Scripts (Script) | ||
import Cardano.Ledger.Alonzo.TxWitness (TxWitness) | ||
import qualified Data.ByteString.Lazy.Char8 as BSL | ||
import Test.Cardano.Ledger.Alonzo.Serialisation.Generators () | ||
import Test.Cardano.Ledger.ShelleyMA.Serialisation.Coders | ||
import Test.Shelley.Spec.Ledger.ConcreteCryptoTypes | ||
import Test.Tasty | ||
import Test.Tasty.QuickCheck | ||
|
||
trippingAnn :: | ||
( Eq t, | ||
Show t, | ||
ToCBOR t, | ||
FromCBOR (Annotator t) | ||
) => | ||
t -> | ||
Property | ||
trippingAnn x = case roundTripAnn x of | ||
Right (remaining, y) | BSL.null remaining -> x === y | ||
Right (remaining, _) -> | ||
counterexample | ||
("Unconsumed trailing bytes:\n" <> BSL.unpack remaining) | ||
False | ||
Left stuff -> | ||
counterexample | ||
("Failed to decode: " <> show stuff) | ||
False | ||
|
||
tests :: TestTree | ||
tests = | ||
testGroup | ||
"Alonzo CBOR round-trip" | ||
[ testProperty "alonzo/script" $ | ||
trippingAnn @(Script (AlonzoEra C_Crypto)), | ||
testProperty "alonzo/TxWitness" $ | ||
trippingAnn @(TxWitness (AlonzoEra C_Crypto)) | ||
] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,14 @@ | ||
module Main where | ||
|
||
import qualified Test.Cardano.Ledger.Alonzo.Serialisation.Tripping as Tripping | ||
import Test.Tasty | ||
|
||
tests :: TestTree | ||
tests = | ||
testGroup | ||
"Alonzo tests" | ||
[ Tripping.tests | ||
] | ||
|
||
main :: IO () | ||
main = defaultMain tests |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters