Skip to content

Commit f710b2b

Browse files
committed
test(golden): add comprehensive golden tests for TxOut JSON serialization
Implements a complete golden test suite for TxOut, TxOutValue, AddressInEra, and ReferenceScript types to ensure JSON format stability after migrating from IsShelleyBasedEra/IsCardanoEra constraints to Exp.IsEra constraints. Test Coverage: - TxOut variations: simple, with datum hash, inline datum, reference script, and full - TxOutValue: lovelace-only and multi-asset configurations - AddressInEra: payment address serialization - ReferenceScript: simple script reference handling - UTxO: complete UTxO map serialization with multiple outputs Golden Test Infrastructure: - Helper functions for constructing test addresses, values, and scripts - Pretty JSON encoding for readable golden files - Comprehensive test data builders with realistic hash values - Support for ConwayEra and future eras (Dijkstra) This test suite ensures backwards compatibility of the JSON format is maintained during the constraint migration, preventing breaking changes in API consumers that depend on JSON serialization.
1 parent 7beb3c4 commit f710b2b

File tree

12 files changed

+448
-0
lines changed

12 files changed

+448
-0
lines changed

cardano-api/cardano-api.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -437,6 +437,7 @@ test-suite cardano-api-golden
437437
buildable: False
438438
build-depends:
439439
aeson,
440+
aeson-pretty,
440441
base64-bytestring,
441442
bech32 >=1.1.0,
442443
bytestring,
@@ -475,5 +476,6 @@ test-suite cardano-api-golden
475476
Test.Golden.Cardano.Api.Genesis
476477
Test.Golden.Cardano.Api.Ledger
477478
Test.Golden.Cardano.Api.Script
479+
Test.Golden.Cardano.Api.TxOut
478480
Test.Golden.Cardano.Api.Value
479481
Test.Golden.ErrorsSpec
Lines changed: 323 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,323 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE FlexibleContexts #-}
3+
{-# LANGUAGE GADTs #-}
4+
{-# LANGUAGE LambdaCase #-}
5+
{-# LANGUAGE NumericUnderscores #-}
6+
{-# LANGUAGE OverloadedStrings #-}
7+
{-# LANGUAGE ScopedTypeVariables #-}
8+
9+
-- | Golden tests for TxOut, TxOutValue, AddressInEra, and ReferenceScript JSON serialization.
10+
--
11+
-- These tests ensure backwards compatibility of the JSON format for types whose
12+
-- ToJSON/FromJSON instances were migrated from IsShelleyBasedEra/IsCardanoEra
13+
-- constraints to Exp.IsEra constraints.
14+
module Test.Golden.Cardano.Api.TxOut
15+
( -- * TxOut golden tests
16+
tasty_golden_TxOut_ConwayEra_simple
17+
, tasty_golden_TxOut_ConwayEra_datumHash
18+
, tasty_golden_TxOut_ConwayEra_inlineDatum
19+
, tasty_golden_TxOut_ConwayEra_referenceScript
20+
, tasty_golden_TxOut_ConwayEra_full
21+
22+
-- * TxOutValue golden tests
23+
, tasty_golden_TxOutValue_ConwayEra_lovelaceOnly
24+
, tasty_golden_TxOutValue_ConwayEra_multiAsset
25+
26+
-- * AddressInEra golden tests
27+
, tasty_golden_AddressInEra_ConwayEra
28+
29+
-- * ReferenceScript golden tests
30+
, tasty_golden_ReferenceScript_ConwayEra
31+
32+
-- * UTxO golden tests
33+
, tasty_golden_UTxO_ConwayEra
34+
)
35+
where
36+
37+
import Cardano.Api
38+
import Cardano.Api.Ledger qualified as L
39+
40+
import Control.Error.Util (hush)
41+
import Data.Aeson qualified as Aeson
42+
import Data.Aeson.Encode.Pretty (encodePretty)
43+
import Data.ByteString (ByteString)
44+
import Data.ByteString.Lazy.Char8 qualified as BL8
45+
import Data.Maybe (fromJust)
46+
import GHC.Exts (IsList (..))
47+
import System.FilePath ((</>))
48+
49+
import Hedgehog.Extras (UnitIO)
50+
import Hedgehog.Extras qualified as H
51+
52+
-- -----------------------------------------------------------------------------
53+
-- Test data construction helpers
54+
-- -----------------------------------------------------------------------------
55+
56+
goldenPath :: FilePath
57+
goldenPath = "test/cardano-api-golden/files/TxOut"
58+
59+
-- | Helper to encode value as pretty JSON string
60+
toJsonString :: Aeson.ToJSON a => a -> String
61+
toJsonString a = BL8.unpack (encodePretty a)
62+
63+
-- | Create a simple payment address for testing
64+
mkTestAddress :: ShelleyBasedEra era -> AddressInEra era
65+
mkTestAddress sbe =
66+
shelleyAddressInEra sbe $
67+
makeShelleyAddress
68+
Mainnet
69+
(PaymentCredentialByKey testPaymentKeyHash)
70+
NoStakeAddress
71+
72+
testPaymentKeyHash :: Hash PaymentKey
73+
testPaymentKeyHash =
74+
fromJust $
75+
hush $
76+
deserialiseFromRawBytesHex "1c14ee8e58fbcbd48dc7367c95a63fd1d937ba989820015db16ac7e5"
77+
78+
-- | Create a test TxOutValue with only lovelace
79+
mkLovelaceValue :: ShelleyBasedEra era -> L.Coin -> TxOutValue era
80+
mkLovelaceValue = lovelaceToTxOutValue
81+
82+
-- | Create a test TxOutValue with multi-assets
83+
mkMultiAssetValue :: ShelleyBasedEra era -> TxOutValue era
84+
mkMultiAssetValue sbe =
85+
shelleyBasedEraConstraints sbe $
86+
TxOutValueShelleyBased sbe $
87+
toLedgerValue (maryEraOnwardsToMaryEraOnwards sbe) testMultiAssetValue
88+
where
89+
maryEraOnwardsToMaryEraOnwards :: ShelleyBasedEra era -> MaryEraOnwards era
90+
maryEraOnwardsToMaryEraOnwards = \case
91+
ShelleyBasedEraConway -> MaryEraOnwardsConway
92+
ShelleyBasedEraDijkstra -> MaryEraOnwardsDijkstra
93+
_ -> error "mkMultiAssetValue: unsupported era"
94+
95+
testMultiAssetValue :: Value
96+
testMultiAssetValue =
97+
fromList
98+
[ (AdaAssetId, Quantity 2_000_000)
99+
, (AssetId testPolicyId testAssetName, Quantity 100)
100+
]
101+
102+
testPolicyId :: PolicyId
103+
testPolicyId =
104+
fromJust $
105+
hush $
106+
deserialiseFromRawBytesHex "a0000000000000000000000000000000000000000000000000000000"
107+
108+
testAssetName :: AssetName
109+
testAssetName =
110+
fromJust $
111+
hush $
112+
deserialiseFromRawBytes AsAssetName "TestToken"
113+
114+
-- | Create a test datum hash
115+
testDatumHash :: Hash ScriptData
116+
testDatumHash =
117+
fromJust $
118+
hush $
119+
deserialiseFromRawBytesHex "ffd29f3e52e7cf2eb451a59448fd55f9c64e4c1ad1ab0e500d6ceb6d7ff97e9c"
120+
121+
-- | Create test inline datum (ScriptData)
122+
testScriptData :: HashableScriptData
123+
testScriptData =
124+
fromJust $
125+
hush $
126+
deserialiseFromCBOR AsHashableScriptData testScriptDataCBOR
127+
where
128+
-- CBOR encoding of ScriptDataNumber 42
129+
testScriptDataCBOR :: ByteString
130+
testScriptDataCBOR = "\24\42"
131+
132+
-- | Create a test simple script for reference script testing
133+
testSimpleScript :: Script SimpleScript'
134+
testSimpleScript =
135+
SimpleScript $
136+
RequireAllOf
137+
[ RequireSignature testPaymentKeyHash
138+
]
139+
140+
-- | Create a test reference script
141+
mkTestReferenceScript :: ShelleyBasedEra era -> ReferenceScript era
142+
mkTestReferenceScript = \case
143+
ShelleyBasedEraConway ->
144+
ReferenceScript BabbageEraOnwardsConway (ScriptInAnyLang SimpleScriptLanguage testSimpleScript)
145+
ShelleyBasedEraDijkstra ->
146+
ReferenceScript BabbageEraOnwardsDijkstra (ScriptInAnyLang SimpleScriptLanguage testSimpleScript)
147+
_ -> error "mkTestReferenceScript: unsupported era"
148+
149+
-- -----------------------------------------------------------------------------
150+
-- TxOut golden tests - Conway Era
151+
-- -----------------------------------------------------------------------------
152+
153+
tasty_golden_TxOut_ConwayEra_simple :: UnitIO ()
154+
tasty_golden_TxOut_ConwayEra_simple =
155+
H.diffVsGoldenFile
156+
(toJsonString txOut)
157+
(goldenPath </> "conway" </> "txout-simple.json")
158+
where
159+
txOut :: TxOut CtxTx ConwayEra
160+
txOut =
161+
TxOut
162+
(mkTestAddress ShelleyBasedEraConway)
163+
(mkLovelaceValue ShelleyBasedEraConway (L.Coin 1_000_000))
164+
TxOutDatumNone
165+
ReferenceScriptNone
166+
167+
tasty_golden_TxOut_ConwayEra_datumHash :: UnitIO ()
168+
tasty_golden_TxOut_ConwayEra_datumHash =
169+
H.diffVsGoldenFile
170+
(toJsonString txOut)
171+
(goldenPath </> "conway" </> "txout-datumhash.json")
172+
where
173+
txOut :: TxOut CtxTx ConwayEra
174+
txOut =
175+
TxOut
176+
(mkTestAddress ShelleyBasedEraConway)
177+
(mkLovelaceValue ShelleyBasedEraConway (L.Coin 2_000_000))
178+
(TxOutDatumHash AlonzoEraOnwardsConway testDatumHash)
179+
ReferenceScriptNone
180+
181+
tasty_golden_TxOut_ConwayEra_inlineDatum :: UnitIO ()
182+
tasty_golden_TxOut_ConwayEra_inlineDatum =
183+
H.diffVsGoldenFile
184+
(toJsonString txOut)
185+
(goldenPath </> "conway" </> "txout-inlinedatum.json")
186+
where
187+
txOut :: TxOut CtxTx ConwayEra
188+
txOut =
189+
TxOut
190+
(mkTestAddress ShelleyBasedEraConway)
191+
(mkLovelaceValue ShelleyBasedEraConway (L.Coin 3_000_000))
192+
(TxOutDatumInline BabbageEraOnwardsConway testScriptData)
193+
ReferenceScriptNone
194+
195+
tasty_golden_TxOut_ConwayEra_referenceScript :: UnitIO ()
196+
tasty_golden_TxOut_ConwayEra_referenceScript =
197+
H.diffVsGoldenFile
198+
(toJsonString txOut)
199+
(goldenPath </> "conway" </> "txout-referencescript.json")
200+
where
201+
txOut :: TxOut CtxTx ConwayEra
202+
txOut =
203+
TxOut
204+
(mkTestAddress ShelleyBasedEraConway)
205+
(mkLovelaceValue ShelleyBasedEraConway (L.Coin 4_000_000))
206+
TxOutDatumNone
207+
(mkTestReferenceScript ShelleyBasedEraConway)
208+
209+
tasty_golden_TxOut_ConwayEra_full :: UnitIO ()
210+
tasty_golden_TxOut_ConwayEra_full =
211+
H.diffVsGoldenFile
212+
(toJsonString txOut)
213+
(goldenPath </> "conway" </> "txout-full.json")
214+
where
215+
txOut :: TxOut CtxTx ConwayEra
216+
txOut =
217+
TxOut
218+
(mkTestAddress ShelleyBasedEraConway)
219+
(mkMultiAssetValue ShelleyBasedEraConway)
220+
(TxOutDatumInline BabbageEraOnwardsConway testScriptData)
221+
(mkTestReferenceScript ShelleyBasedEraConway)
222+
223+
-- -----------------------------------------------------------------------------
224+
-- TxOutValue golden tests
225+
-- -----------------------------------------------------------------------------
226+
227+
tasty_golden_TxOutValue_ConwayEra_lovelaceOnly :: UnitIO ()
228+
tasty_golden_TxOutValue_ConwayEra_lovelaceOnly =
229+
H.diffVsGoldenFile
230+
(toJsonString txOutValue)
231+
(goldenPath </> "conway" </> "txoutvalue-lovelace.json")
232+
where
233+
txOutValue :: TxOutValue ConwayEra
234+
txOutValue = mkLovelaceValue ShelleyBasedEraConway (L.Coin 5_000_000)
235+
236+
tasty_golden_TxOutValue_ConwayEra_multiAsset :: UnitIO ()
237+
tasty_golden_TxOutValue_ConwayEra_multiAsset =
238+
H.diffVsGoldenFile
239+
(toJsonString txOutValue)
240+
(goldenPath </> "conway" </> "txoutvalue-multiasset.json")
241+
where
242+
txOutValue :: TxOutValue ConwayEra
243+
txOutValue = mkMultiAssetValue ShelleyBasedEraConway
244+
245+
-- -----------------------------------------------------------------------------
246+
-- AddressInEra golden tests
247+
-- -----------------------------------------------------------------------------
248+
249+
tasty_golden_AddressInEra_ConwayEra :: UnitIO ()
250+
tasty_golden_AddressInEra_ConwayEra =
251+
H.diffVsGoldenFile
252+
(toJsonString addr)
253+
(goldenPath </> "conway" </> "address.json")
254+
where
255+
addr :: AddressInEra ConwayEra
256+
addr = mkTestAddress ShelleyBasedEraConway
257+
258+
-- -----------------------------------------------------------------------------
259+
-- ReferenceScript golden tests
260+
-- -----------------------------------------------------------------------------
261+
262+
tasty_golden_ReferenceScript_ConwayEra :: UnitIO ()
263+
tasty_golden_ReferenceScript_ConwayEra =
264+
H.diffVsGoldenFile
265+
(toJsonString refScript)
266+
(goldenPath </> "conway" </> "referencescript.json")
267+
where
268+
refScript :: ReferenceScript ConwayEra
269+
refScript = mkTestReferenceScript ShelleyBasedEraConway
270+
271+
-- -----------------------------------------------------------------------------
272+
-- UTxO golden tests
273+
-- -----------------------------------------------------------------------------
274+
275+
tasty_golden_UTxO_ConwayEra :: UnitIO ()
276+
tasty_golden_UTxO_ConwayEra =
277+
H.diffVsGoldenFile
278+
(toJsonString utxo)
279+
(goldenPath </> "conway" </> "utxo.json")
280+
where
281+
utxo :: UTxO ConwayEra
282+
utxo =
283+
UTxO $
284+
fromList
285+
[ (testTxIn, txOut1)
286+
, (testTxIn2, txOut2)
287+
]
288+
289+
txOut1 :: TxOut CtxUTxO ConwayEra
290+
txOut1 =
291+
TxOut
292+
(mkTestAddress ShelleyBasedEraConway)
293+
(mkLovelaceValue ShelleyBasedEraConway (L.Coin 1_000_000))
294+
TxOutDatumNone
295+
ReferenceScriptNone
296+
297+
txOut2 :: TxOut CtxUTxO ConwayEra
298+
txOut2 =
299+
TxOut
300+
(mkTestAddress ShelleyBasedEraConway)
301+
(mkMultiAssetValue ShelleyBasedEraConway)
302+
(TxOutDatumHash AlonzoEraOnwardsConway testDatumHash)
303+
ReferenceScriptNone
304+
305+
testTxIn :: TxIn
306+
testTxIn =
307+
TxIn testTxId1 (TxIx 0)
308+
309+
testTxIn2 :: TxIn
310+
testTxIn2 =
311+
TxIn testTxId2 (TxIx 1)
312+
313+
testTxId1 :: TxId
314+
testTxId1 =
315+
fromJust $
316+
hush $
317+
deserialiseFromRawBytesHex "0000000000000000000000000000000000000000000000000000000000000001"
318+
319+
testTxId2 :: TxId
320+
testTxId2 =
321+
fromJust $
322+
hush $
323+
deserialiseFromRawBytesHex "0000000000000000000000000000000000000000000000000000000000000002"
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
"addr1vywpfm5wtrauh4ydcum8e9dx8lgajda6nzvzqq2ak94v0eg88t7u2"
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
{
2+
"referenceScript": {
3+
"script": {
4+
"cborHex": "8201818200581c1c14ee8e58fbcbd48dc7367c95a63fd1d937ba989820015db16ac7e5",
5+
"description": "",
6+
"type": "SimpleScript"
7+
},
8+
"scriptLanguage": "SimpleScriptLanguage"
9+
}
10+
}
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
{
2+
"address": "addr1vywpfm5wtrauh4ydcum8e9dx8lgajda6nzvzqq2ak94v0eg88t7u2",
3+
"datum": null,
4+
"datumhash": "ffd29f3e52e7cf2eb451a59448fd55f9c64e4c1ad1ab0e500d6ceb6d7ff97e9c",
5+
"inlineDatum": null,
6+
"inlineDatumRaw": null,
7+
"referenceScript": null,
8+
"value": {
9+
"lovelace": 2000000
10+
}
11+
}
Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
{
2+
"address": "addr1vywpfm5wtrauh4ydcum8e9dx8lgajda6nzvzqq2ak94v0eg88t7u2",
3+
"datum": null,
4+
"inlineDatum": {
5+
"int": 42
6+
},
7+
"inlineDatumRaw": "182a",
8+
"inlineDatumhash": "9e1199a988ba72ffd6e9c269cadb3b53b5f360ff99f112d9b2ee30c4d74ad88b",
9+
"referenceScript": {
10+
"script": {
11+
"cborHex": "8201818200581c1c14ee8e58fbcbd48dc7367c95a63fd1d937ba989820015db16ac7e5",
12+
"description": "",
13+
"type": "SimpleScript"
14+
},
15+
"scriptLanguage": "SimpleScriptLanguage"
16+
},
17+
"value": {
18+
"a0000000000000000000000000000000000000000000000000000000": {
19+
"54657374546f6b656e": 100
20+
},
21+
"lovelace": 2000000
22+
}
23+
}

0 commit comments

Comments
 (0)