Skip to content

Commit e961553

Browse files
committed
Remove tasty-th because it generated deprecated code
1 parent 32b9071 commit e961553

File tree

21 files changed

+244
-207
lines changed

21 files changed

+244
-207
lines changed

bench/locli/src/Cardano/Analysis/Chain.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,9 @@
11
{-# LANGUAGE GeneralizedNewtypeDeriving#-}
2-
{-# OPTIONS_GHC -Wno-deprecations -Wno-orphans #-}
2+
3+
{-# OPTIONS_GHC -Wno-orphans #-}
4+
35
{- HLINT ignore "Use head" -}
6+
47
module Cardano.Analysis.Chain (module Cardano.Analysis.Chain) where
58

69
import Cardano.Prelude hiding (head)

bench/locli/src/Cardano/Analysis/ChainFilter.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
{-# LANGUAGE DeriveAnyClass #-}
22
{-# LANGUAGE StrictData #-}
3-
{-# OPTIONS_GHC -Wno-deprecations -Wno-orphans #-}
3+
44
{- HLINT ignore "Use head" -}
5+
56
module Cardano.Analysis.ChainFilter (module Cardano.Analysis.ChainFilter) where
67

78
import Cardano.Prelude hiding (head)

cardano-api/cardano-api.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -217,7 +217,6 @@ test-suite cardano-api-test
217217
, tasty
218218
, tasty-hedgehog
219219
, tasty-quickcheck
220-
, tasty-th
221220
, time
222221

223222
other-modules: Test.Cardano.Api.Crypto

cardano-api/test/Test/Cardano/Api/Json.hs

Lines changed: 17 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,29 +1,23 @@
11
{-# LANGUAGE FlexibleContexts #-}
22
{-# LANGUAGE GADTs #-}
33
{-# LANGUAGE LambdaCase #-}
4-
{-# LANGUAGE TemplateHaskell #-}
5-
6-
{-# OPTIONS_GHC -Wno-deprecations #-} -- TODO Fix deprecations
74

85
module Test.Cardano.Api.Json
96
( tests
107
) where
118

9+
import Cardano.Api.Orphans ()
10+
import Cardano.Api.Shelley
1211
import Cardano.Prelude
13-
1412
import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON), eitherDecode, encode)
1513
import Data.Aeson.Types (Parser, parseEither)
16-
import Hedgehog (Property, forAll, tripping)
17-
import qualified Hedgehog as H
18-
import Test.Tasty (TestTree)
19-
import Test.Tasty.Hedgehog (testProperty)
20-
import Test.Tasty.TH (testGroupGenerator)
21-
22-
import Cardano.Api
23-
import Cardano.Api.Orphans ()
24-
import Cardano.Api.Shelley
2514
import Gen.Cardano.Api (genAlonzoGenesis)
2615
import Gen.Cardano.Api.Typed
16+
import Hedgehog (Property, forAll, tripping)
17+
import Test.Tasty (TestTree, testGroup)
18+
import Test.Tasty.Hedgehog (testPropertyNamed)
19+
20+
import qualified Hedgehog as H
2721

2822
{- HLINT ignore "Use camelCase" -}
2923

@@ -89,4 +83,13 @@ prop_json_roundtrip_scriptdata_detailed_json = H.property $ do
8983
tripping sData scriptDataToJsonDetailedSchema scriptDataFromJsonDetailedSchema
9084

9185
tests :: TestTree
92-
tests = $testGroupGenerator
86+
tests = testGroup "Test.Cardano.Api.Json"
87+
[ testPropertyNamed "json roundtrip alonzo genesis" "json roundtrip alonzo genesis" prop_json_roundtrip_alonzo_genesis
88+
, testPropertyNamed "json roundtrip utxo" "json roundtrip utxo" prop_json_roundtrip_utxo
89+
, testPropertyNamed "json roundtrip reference scripts" "json roundtrip reference scripts" prop_json_roundtrip_reference_scripts
90+
, testPropertyNamed "json roundtrip txoutvalue" "json roundtrip txoutvalue" prop_json_roundtrip_txoutvalue
91+
, testPropertyNamed "json roundtrip txout tx context" "json roundtrip txout tx context" prop_json_roundtrip_txout_tx_context
92+
, testPropertyNamed "json roundtrip txout utxo context" "json roundtrip txout utxo context" prop_json_roundtrip_txout_utxo_context
93+
, testPropertyNamed "json roundtrip eraInMode" "json roundtrip eraInMode" prop_json_roundtrip_eraInMode
94+
, testPropertyNamed "json roundtrip scriptdata detailed json" "json roundtrip scriptdata detailed json" prop_json_roundtrip_scriptdata_detailed_json
95+
]
Lines changed: 8 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,23 +1,18 @@
11
{-# LANGUAGE FlexibleContexts #-}
2-
{-# LANGUAGE TemplateHaskell #-}
3-
4-
{-# OPTIONS_GHC -Wno-deprecations #-} -- TODO Fix deprecations
52

63
module Test.Cardano.Api.KeysByron
74
( tests
85
) where
96

10-
import Cardano.Prelude
11-
7+
import Cardano.Api (AsType(AsByronKey, AsSigningKey), Key(deterministicSigningKey))
8+
import Cardano.Prelude ((<$>))
9+
import Gen.Hedgehog.Roundtrip.CBOR (roundtrip_CBOR)
1210
import Hedgehog (Property)
1311
import Test.Cardano.Api.Typed.Orphans ()
14-
import Test.Tasty (TestTree)
15-
import Test.Tasty.Hedgehog (testProperty)
16-
import Test.Tasty.TH (testGroupGenerator)
12+
import Test.Tasty (TestTree, testGroup)
13+
import Test.Tasty.Hedgehog (testPropertyNamed)
1714

18-
import Cardano.Api
1915
import qualified Gen.Cardano.Crypto.Seed as Gen
20-
import Gen.Hedgehog.Roundtrip.CBOR (roundtrip_CBOR)
2116

2217
{- HLINT ignore "Use camelCase" -}
2318

@@ -26,4 +21,6 @@ prop_roundtrip_byron_key_CBOR =
2621
roundtrip_CBOR (AsSigningKey AsByronKey) (deterministicSigningKey AsByronKey <$> Gen.genSeedForKey AsByronKey)
2722

2823
tests :: TestTree
29-
tests = $testGroupGenerator
24+
tests = testGroup "Test.Cardano.Api.KeysByron"
25+
[ testPropertyNamed "roundtrip byron key CBOR" "roundtrip byron key CBOR" prop_roundtrip_byron_key_CBOR
26+
]
Lines changed: 12 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,26 +1,20 @@
1-
{-# LANGUAGE StandaloneDeriving #-}
2-
{-# LANGUAGE TemplateHaskell #-}
31
{-# LANGUAGE TypeApplications #-}
42

5-
{-# OPTIONS_GHC -Wno-deprecations #-} -- TODO Fix deprecations
6-
73
module Test.Cardano.Api.Ledger
84
( tests
95
) where
106

11-
import Cardano.Prelude
12-
13-
import Hedgehog (Property)
14-
import qualified Hedgehog as H
15-
import qualified Hedgehog.Extras.Aeson as H
16-
import Test.Tasty (TestTree)
17-
import Test.Tasty.Hedgehog (testProperty)
18-
import Test.Tasty.TH (testGroupGenerator)
19-
207
import Cardano.Ledger.Address (deserialiseAddr, serialiseAddr)
8+
import Cardano.Prelude (($))
9+
import Hedgehog (Property)
2110
import Ouroboros.Consensus.Shelley.Eras (StandardCrypto)
22-
import Test.Cardano.Api.Genesis
11+
import Test.Cardano.Api.Genesis (exampleShelleyGenesis)
2312
import Test.Cardano.Ledger.Shelley.Serialisation.Generators.Genesis (genAddress)
13+
import Test.Tasty (TestTree, testGroup)
14+
import Test.Tasty.Hedgehog (testPropertyNamed)
15+
16+
import qualified Hedgehog as H
17+
import qualified Hedgehog.Extras.Aeson as H
2418

2519
prop_golden_ShelleyGenesis :: Property
2620
prop_golden_ShelleyGenesis = H.goldenTestJsonValuePretty exampleShelleyGenesis "test/Golden/ShelleyGenesis"
@@ -37,4 +31,7 @@ prop_roundtrip_Address_CBOR = H.property $ do
3731
-- -----------------------------------------------------------------------------
3832

3933
tests :: TestTree
40-
tests = $testGroupGenerator
34+
tests = testGroup "Test.Cardano.Api.Ledger"
35+
[ testPropertyNamed "golden ShelleyGenesis" "golden ShelleyGenesis" prop_golden_ShelleyGenesis
36+
, testPropertyNamed "roundtrip Address CBOR" "roundtrip Address CBOR" prop_roundtrip_Address_CBOR
37+
]

cardano-api/test/Test/Cardano/Api/Metadata.hs

Lines changed: 18 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,26 +1,21 @@
11
{-# LANGUAGE OverloadedStrings #-}
2-
{-# LANGUAGE TemplateHaskell #-}
3-
4-
{-# OPTIONS_GHC -Wno-deprecations #-} -- TODO Fix deprecations
52

63
module Test.Cardano.Api.Metadata
74
( tests
85
, genTxMetadata
96
, genTxMetadataValue
107
) where
118

9+
import Cardano.Api
1210
import Cardano.Prelude
11+
import Gen.Cardano.Api.Metadata
12+
import Hedgehog (Property, property, (===))
13+
import Test.Tasty (TestTree, testGroup)
14+
import Test.Tasty.Hedgehog (testPropertyNamed)
1315

1416
import qualified Data.Aeson as Aeson
1517
import qualified Data.Map.Strict as Map
16-
import Hedgehog (Property, property, (===))
1718
import qualified Hedgehog
18-
import Test.Tasty (TestTree)
19-
import Test.Tasty.Hedgehog (testProperty)
20-
import Test.Tasty.TH (testGroupGenerator)
21-
22-
import Cardano.Api
23-
import Gen.Cardano.Api.Metadata
2419

2520
-- ----------------------------------------------------------------------------
2621
-- Golden / unit tests
@@ -126,4 +121,16 @@ prop_metadata_roundtrip_via_schema_json = Hedgehog.property $ do
126121
--
127122

128123
tests :: TestTree
129-
tests = $testGroupGenerator
124+
tests = testGroup "Test.Cardano.Api.Metadata"
125+
[ testPropertyNamed "golden 1" "golden 1" prop_golden_1
126+
, testPropertyNamed "golden 2" "golden 2" prop_golden_2
127+
, testPropertyNamed "golden 3" "golden 3" prop_golden_3
128+
, testPropertyNamed "golden 4" "golden 4" prop_golden_4
129+
, testPropertyNamed "golden 5" "golden 5" prop_golden_5
130+
, testPropertyNamed "golden 6" "golden 6" prop_golden_6
131+
, testPropertyNamed "golden 7" "golden 7" prop_golden_7
132+
, testPropertyNamed "golden 8" "golden 8" prop_golden_8
133+
, testPropertyNamed "noschema json roundtrip via metadata" "noschema json roundtrip via metadata" prop_noschema_json_roundtrip_via_metadata
134+
, testPropertyNamed "schema json roundtrip via metadata" "schema json roundtrip via metadata" prop_schema_json_roundtrip_via_metadata
135+
, testPropertyNamed "metadata roundtrip via schema json" "metadata roundtrip via schema json" prop_metadata_roundtrip_via_schema_json
136+
]

cardano-api/test/Test/Cardano/Api/Typed/Address.hs

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,23 +1,18 @@
11
{-# LANGUAGE FlexibleContexts #-}
2-
{-# LANGUAGE TemplateHaskell #-}
3-
4-
{-# OPTIONS_GHC -Wno-deprecations #-} -- TODO Fix deprecations
52

63
module Test.Cardano.Api.Typed.Address
74
( tests
85
) where
96

10-
import Cardano.Prelude
11-
12-
import Hedgehog (Property)
13-
import qualified Hedgehog as H
14-
import Test.Tasty (TestTree)
15-
import Test.Tasty.Hedgehog (testProperty)
16-
import Test.Tasty.TH (testGroupGenerator)
17-
187
import Cardano.Api
19-
import Gen.Cardano.Api.Typed
8+
import Cardano.Prelude (($), Eq, Show)
9+
import Gen.Cardano.Api.Typed (genAddressByron, genAddressShelley)
10+
import Hedgehog (Property)
2011
import Test.Cardano.Api.Typed.Orphans ()
12+
import Test.Tasty (TestTree, testGroup)
13+
import Test.Tasty.Hedgehog (testPropertyNamed)
14+
15+
import qualified Hedgehog as H
2116

2217
{- HLINT ignore "Use camelCase" -}
2318

@@ -48,4 +43,7 @@ roundtrip_serialise_address asType g =
4843
-- -----------------------------------------------------------------------------
4944

5045
tests :: TestTree
51-
tests = $testGroupGenerator
46+
tests = testGroup "Test.Cardano.Api.Typed.Address"
47+
[ testPropertyNamed "roundtrip shelley address" "roundtrip shelley address" prop_roundtrip_shelley_address
48+
, testPropertyNamed "roundtrip byron address" "roundtrip byron address" prop_roundtrip_byron_address
49+
]
Lines changed: 9 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,19 +1,13 @@
1-
{-# LANGUAGE TemplateHaskell #-}
2-
3-
{-# OPTIONS_GHC -Wno-deprecations #-} -- TODO Fix deprecations
4-
51
module Test.Cardano.Api.Typed.Bech32
62
( tests
73
) where
84

9-
import Hedgehog (Property)
10-
import Test.Tasty (TestTree)
11-
import Test.Tasty.Hedgehog (testProperty)
12-
import Test.Tasty.TH (testGroupGenerator)
13-
14-
import Cardano.Api
15-
import Gen.Cardano.Api.Typed
5+
import Cardano.Api (AsType(AsStakeAddress, AsShelleyAddress))
6+
import Gen.Cardano.Api.Typed( genAddressShelley, genStakeAddress)
167
import Gen.Hedgehog.Roundtrip.Bech32 (roundtrip_Bech32)
8+
import Hedgehog (Property)
9+
import Test.Tasty (TestTree, testGroup)
10+
import Test.Tasty.Hedgehog (testPropertyNamed)
1711

1812
prop_roundtrip_Address_Shelley :: Property
1913
prop_roundtrip_Address_Shelley = roundtrip_Bech32 AsShelleyAddress genAddressShelley
@@ -22,4 +16,7 @@ prop_roundtrip_StakeAddress :: Property
2216
prop_roundtrip_StakeAddress = roundtrip_Bech32 AsStakeAddress genStakeAddress
2317

2418
tests :: TestTree
25-
tests = $testGroupGenerator
19+
tests = testGroup "Test.Cardano.Api.Typed.Bech32"
20+
[ testPropertyNamed "roundtrip Address Shelley" "roundtrip Address Shelley" prop_roundtrip_Address_Shelley
21+
, testPropertyNamed "roundtrip StakeAddress" "roundtrip StakeAddress" prop_roundtrip_StakeAddress
22+
]

cardano-api/test/Test/Cardano/Api/Typed/CBOR.hs

Lines changed: 43 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,27 +1,20 @@
1-
{-# LANGUAGE EmptyCase #-}
21
{-# LANGUAGE FlexibleContexts #-}
32
{-# LANGUAGE GADTs #-}
43
{-# LANGUAGE RankNTypes #-}
5-
{-# LANGUAGE TemplateHaskell #-}
6-
7-
{-# OPTIONS_GHC -Wno-deprecations #-} -- TODO Fix deprecations
84

95
module Test.Cardano.Api.Typed.CBOR
106
( tests
117
) where
128

13-
import Cardano.Prelude
14-
15-
import Hedgehog (Property, forAll, property, success, tripping)
16-
import Test.Tasty (TestTree, testGroup)
17-
import Test.Tasty.Hedgehog (testProperty)
18-
import Test.Tasty.TH (testGroupGenerator)
19-
209
import Cardano.Api
21-
10+
import Cardano.Prelude
11+
import Data.String (IsString(..))
2212
import Gen.Cardano.Api.Typed
2313
import Gen.Hedgehog.Roundtrip.CBOR (roundtrip_CBOR)
14+
import Hedgehog (Property, forAll, property, success, tripping)
2415
import Test.Cardano.Api.Typed.Orphans ()
16+
import Test.Tasty (TestTree, testGroup)
17+
import Test.Tasty.Hedgehog (testPropertyNamed)
2518

2619
{- HLINT ignore "Use camelCase" -}
2720

@@ -30,14 +23,14 @@ import Test.Cardano.Api.Typed.Orphans ()
3023

3124
test_roundtrip_txbody_CBOR :: [TestTree]
3225
test_roundtrip_txbody_CBOR =
33-
[ testProperty (show era) $
26+
[ testPropertyNamed (show era) (fromString (show era)) $
3427
roundtrip_CBOR (proxyToAsType Proxy) (genTxBody era)
3528
| AnyCardanoEra era <- [minBound..(AnyCardanoEra AlonzoEra)] -- TODO: Babbage era
3629
]
3730

3831
test_roundtrip_tx_CBOR :: [TestTree]
3932
test_roundtrip_tx_CBOR =
40-
[ testProperty (show era) $ roundtrip_CBOR (proxyToAsType Proxy) (genTx era)
33+
[ testPropertyNamed (show era) (fromString (show era)) $ roundtrip_CBOR (proxyToAsType Proxy) (genTx era)
4134
| AnyCardanoEra era <- [minBound..(AnyCardanoEra AlonzoEra)] -- TODO: Babbage era
4235
]
4336

@@ -160,13 +153,13 @@ prop_roundtrip_UpdateProposal_CBOR =
160153

161154
test_roundtrip_Tx_Cddl :: [TestTree]
162155
test_roundtrip_Tx_Cddl =
163-
[ testProperty (show era) $ roundtrip_Tx_Cddl anyEra
156+
[ testPropertyNamed (show era) (fromString (show era)) $ roundtrip_Tx_Cddl anyEra
164157
| anyEra@(AnyCardanoEra era) <- [minBound..(AnyCardanoEra AlonzoEra)] --TODO: Babbage era
165158
]
166159

167160
test_roundtrip_TxWitness_Cddl :: [TestTree]
168161
test_roundtrip_TxWitness_Cddl =
169-
[ testProperty (show era) $ roundtrip_TxWitness_Cddl era
162+
[ testPropertyNamed (show era) (fromString (show era)) $ roundtrip_TxWitness_Cddl era
170163
| AnyCardanoEra era <- [minBound..(AnyCardanoEra AlonzoEra)] --TODO: Babbage era
171164
, AnyCardanoEra era /= AnyCardanoEra ByronEra
172165
]
@@ -193,4 +186,37 @@ roundtrip_Tx_Cddl (AnyCardanoEra era) =
193186
-- -----------------------------------------------------------------------------
194187

195188
tests :: TestTree
196-
tests = $testGroupGenerator
189+
tests = testGroup "Test.Cardano.Api.Typed.CBOR"
190+
[ testPropertyNamed "roundtrip witness byron CBOR" "roundtrip witness byron CBOR" prop_roundtrip_witness_byron_CBOR
191+
, testPropertyNamed "roundtrip witness shelley CBOR" "roundtrip witness shelley CBOR" prop_roundtrip_witness_shelley_CBOR
192+
, testPropertyNamed "roundtrip witness allegra CBOR" "roundtrip witness allegra CBOR" prop_roundtrip_witness_allegra_CBOR
193+
, testPropertyNamed "roundtrip witness mary CBOR" "roundtrip witness mary CBOR" prop_roundtrip_witness_mary_CBOR
194+
, testPropertyNamed "roundtrip witness alonzo CBOR" "roundtrip witness alonzo CBOR" prop_roundtrip_witness_alonzo_CBOR
195+
, testPropertyNamed "roundtrip operational certificate CBOR" "roundtrip operational certificate CBOR" prop_roundtrip_operational_certificate_CBOR
196+
, testPropertyNamed "roundtrip operational certificate issue counter CBOR" "roundtrip operational certificate issue counter CBOR" prop_roundtrip_operational_certificate_issue_counter_CBOR
197+
, testPropertyNamed "roundtrip verification key byron CBOR" "roundtrip verification key byron CBOR" prop_roundtrip_verification_key_byron_CBOR
198+
, testPropertyNamed "roundtrip signing key byron CBOR" "roundtrip signing key byron CBOR" prop_roundtrip_signing_key_byron_CBOR
199+
, testPropertyNamed "roundtrip verification key payment CBOR" "roundtrip verification key payment CBOR" prop_roundtrip_verification_key_payment_CBOR
200+
, testPropertyNamed "roundtrip signing key payment CBOR" "roundtrip signing key payment CBOR" prop_roundtrip_signing_key_payment_CBOR
201+
, testPropertyNamed "roundtrip verification key stake CBOR" "roundtrip verification key stake CBOR" prop_roundtrip_verification_key_stake_CBOR
202+
, testPropertyNamed "roundtrip signing key stake CBOR" "roundtrip signing key stake CBOR" prop_roundtrip_signing_key_stake_CBOR
203+
, testPropertyNamed "roundtrip verification key genesis CBOR" "roundtrip verification key genesis CBOR" prop_roundtrip_verification_key_genesis_CBOR
204+
, testPropertyNamed "roundtrip signing key genesis CBOR" "roundtrip signing key genesis CBOR" prop_roundtrip_signing_key_genesis_CBOR
205+
, testPropertyNamed "roundtrip verification key genesis delegate CBOR" "roundtrip verification key genesis delegate CBOR" prop_roundtrip_verification_key_genesis_delegate_CBOR
206+
, testPropertyNamed "roundtrip signing key genesis delegate CBOR" "roundtrip signing key genesis delegate CBOR" prop_roundtrip_signing_key_genesis_delegate_CBOR
207+
, testPropertyNamed "roundtrip verification key stake pool CBOR" "roundtrip verification key stake pool CBOR" prop_roundtrip_verification_key_stake_pool_CBOR
208+
, testPropertyNamed "roundtrip signing key stake pool CBOR" "roundtrip signing key stake pool CBOR" prop_roundtrip_signing_key_stake_pool_CBOR
209+
, testPropertyNamed "roundtrip verification key vrf CBOR" "roundtrip verification key vrf CBOR" prop_roundtrip_verification_key_vrf_CBOR
210+
, testPropertyNamed "roundtrip signing key vrf CBOR" "roundtrip signing key vrf CBOR" prop_roundtrip_signing_key_vrf_CBOR
211+
, testPropertyNamed "roundtrip verification key kes CBOR" "roundtrip verification key kes CBOR" prop_roundtrip_verification_key_kes_CBOR
212+
, testPropertyNamed "roundtrip signing key kes CBOR" "roundtrip signing key kes CBOR" prop_roundtrip_signing_key_kes_CBOR
213+
, testPropertyNamed "roundtrip script SimpleScriptV1 CBOR" "roundtrip script SimpleScriptV1 CBOR" prop_roundtrip_script_SimpleScriptV1_CBOR
214+
, testPropertyNamed "roundtrip script SimpleScriptV2 CBOR" "roundtrip script SimpleScriptV2 CBOR" prop_roundtrip_script_SimpleScriptV2_CBOR
215+
, testPropertyNamed "roundtrip script PlutusScriptV1 CBOR" "roundtrip script PlutusScriptV1 CBOR" prop_roundtrip_script_PlutusScriptV1_CBOR
216+
, testPropertyNamed "roundtrip script PlutusScriptV2 CBOR" "roundtrip script PlutusScriptV2 CBOR" prop_roundtrip_script_PlutusScriptV2_CBOR
217+
, testPropertyNamed "roundtrip UpdateProposal CBOR" "roundtrip UpdateProposal CBOR" prop_roundtrip_UpdateProposal_CBOR
218+
, testGroup "roundtrip txbody CBOR" test_roundtrip_txbody_CBOR
219+
, testGroup "roundtrip tx CBOR" test_roundtrip_tx_CBOR
220+
, testGroup "roundtrip Tx Cddl" test_roundtrip_Tx_Cddl
221+
, testGroup "roundtrip TxWitness Cddl" test_roundtrip_TxWitness_Cddl
222+
]

0 commit comments

Comments
 (0)