{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
module Test.Cardano.Chain.UTxO.CBOR (
tests,
)
where
import Cardano.Chain.Common (AddrAttributes (..), Attributes (..), mkAttributes)
import Cardano.Chain.UTxO (
Tx (..),
TxIn (..),
TxInWitness (..),
TxOut (..),
TxSigData (..),
taTx,
taWitness,
)
import Cardano.Crypto (ProtocolMagicId (..), SignTag (..), Signature, sign)
import Cardano.Ledger.Binary (Case (..), EncCBOR, LengthOf, SizeOverride (..), szCases)
import Cardano.Prelude
import qualified Data.Map.Strict as M
import Data.Vector (Vector)
import GetDataFileName ((<:<))
import Hedgehog (Gen, Property)
import qualified Hedgehog as H
import Test.Cardano.Chain.UTxO.Example (
exampleHashTx,
exampleRedeemSignature,
exampleTxId,
exampleTxInList,
exampleTxInUtxo,
exampleTxOut,
exampleTxOut1,
exampleTxOutList,
exampleTxPayload1,
exampleTxProof,
exampleTxSig,
exampleTxSigData,
exampleTxWitness,
)
import Test.Cardano.Chain.UTxO.Gen (
genTx,
genTxAttributes,
genTxAux,
genTxHash,
genTxId,
genTxIn,
genTxInList,
genTxInWitness,
genTxOut,
genTxOutList,
genTxPayload,
genTxProof,
genTxSig,
genTxSigData,
genTxValidationError,
genTxWitness,
genUTxOConfiguration,
genUTxOError,
genUTxOValidationError,
)
import Test.Cardano.Crypto.Example (
exampleRedeemVerificationKey,
exampleSigningKey,
exampleVerificationKey,
)
import Test.Cardano.Crypto.Gen (feedPM)
import Test.Cardano.Ledger.Binary.Vintage.Helpers (SizeTestConfig (..), scfg, sizeTest)
import Test.Cardano.Ledger.Binary.Vintage.Helpers.GoldenRoundTrip (
goldenTestCBOR,
roundTripsCBORBuildable,
roundTripsCBORShow,
)
import Test.Cardano.Prelude
import Test.Options (TSGroup, TSProperty, concatTSGroups, eachOfTS)
goldenTx :: Property
goldenTx :: Property
goldenTx = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR Tx
tx (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/Tx"
where
tx :: Tx
tx = NonEmpty TxIn -> NonEmpty TxOut -> TxAttributes -> Tx
UnsafeTx NonEmpty TxIn
exampleTxInList NonEmpty TxOut
exampleTxOutList (forall h. h -> Attributes h
mkAttributes ())
ts_roundTripTx :: TSProperty
ts_roundTripTx :: TSProperty
ts_roundTripTx = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen Tx
genTx forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxAttributes :: Property
goldenTxAttributes :: Property
goldenTxAttributes = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxAttributes
txA (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxAttributes"
where
txA :: TxAttributes
txA = forall h. h -> Attributes h
mkAttributes ()
ts_roundTripTxAttributes :: TSProperty
ts_roundTripTxAttributes :: TSProperty
ts_roundTripTxAttributes = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
10 Gen TxAttributes
genTxAttributes forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
ts_roundTripTxAux :: TSProperty
ts_roundTripTxAux :: TSProperty
ts_roundTripTxAux = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 (forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxAux
genTxAux) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenHashTx :: Property
goldenHashTx :: Property
goldenHashTx = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxId
exampleHashTx (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/HashTx"
ts_roundTripHashTx :: TSProperty
ts_roundTripHashTx :: TSProperty
ts_roundTripHashTx = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen TxId
genTxHash forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxInUtxo :: Property
goldenTxInUtxo :: Property
goldenTxInUtxo =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxIn
exampleTxInUtxo (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxIn_Utxo"
ts_roundTripTxIn :: TSProperty
ts_roundTripTxIn :: TSProperty
ts_roundTripTxIn = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen TxIn
genTxIn forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxId :: Property
goldenTxId :: Property
goldenTxId = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxId
exampleTxId (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxId"
ts_roundTripTxId :: TSProperty
ts_roundTripTxId :: TSProperty
ts_roundTripTxId = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen TxId
genTxId forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxInList :: Property
goldenTxInList :: Property
goldenTxInList = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR NonEmpty TxIn
exampleTxInList (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxInList"
ts_roundTripTxInList :: TSProperty
ts_roundTripTxInList :: TSProperty
ts_roundTripTxInList = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen (NonEmpty TxIn)
genTxInList forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
goldenVKWitness :: Property
goldenVKWitness :: Property
goldenVKWitness =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR
TxInWitness
vkWitness
(FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxInWitness_VKWitness"
where
vkWitness :: TxInWitness
vkWitness = VerificationKey -> TxSig -> TxInWitness
VKWitness VerificationKey
exampleVerificationKey TxSig
exampleTxSig
goldenRedeemWitness :: Property
goldenRedeemWitness :: Property
goldenRedeemWitness =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR
TxInWitness
redeemWitness
(FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxInWitness_RedeemWitness"
where
redeemWitness :: TxInWitness
redeemWitness = RedeemVerificationKey -> RedeemSignature TxSigData -> TxInWitness
RedeemWitness RedeemVerificationKey
exampleRedeemVerificationKey RedeemSignature TxSigData
exampleRedeemSignature
ts_roundTripTxInWitness :: TSProperty
ts_roundTripTxInWitness :: TSProperty
ts_roundTripTxInWitness =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 (forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxInWitness
genTxInWitness) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxOutList :: Property
goldenTxOutList :: Property
goldenTxOutList =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR NonEmpty TxOut
exampleTxOutList (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxOutList"
ts_roundTripTxOutList :: TSProperty
ts_roundTripTxOutList :: TSProperty
ts_roundTripTxOutList = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen (NonEmpty TxOut)
genTxOutList forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
goldenTxOut :: Property
goldenTxOut :: Property
goldenTxOut = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxOut
exampleTxOut (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxOut"
goldenTxOut1 :: Property
goldenTxOut1 :: Property
goldenTxOut1 = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxOut
exampleTxOut1 (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxOut1"
ts_roundTripTxOut :: TSProperty
ts_roundTripTxOut :: TSProperty
ts_roundTripTxOut = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen TxOut
genTxOut forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxPayload1 :: Property
goldenTxPayload1 :: Property
goldenTxPayload1 =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxPayload
exampleTxPayload1 (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxPayload1"
ts_roundTripTxPayload :: TSProperty
ts_roundTripTxPayload :: TSProperty
ts_roundTripTxPayload = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 (forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxPayload
genTxPayload) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
goldenTxProof :: Property
goldenTxProof :: Property
goldenTxProof = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxProof
exampleTxProof (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxProof"
ts_roundTripTxProof :: TSProperty
ts_roundTripTxProof :: TSProperty
ts_roundTripTxProof = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 (forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxProof
genTxProof) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxSig :: Property
goldenTxSig :: Property
goldenTxSig = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxSig
txSigGold (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxSig"
where
txSigGold :: TxSig
txSigGold =
forall a.
EncCBOR a =>
ProtocolMagicId -> SignTag -> SigningKey -> a -> Signature a
sign
(Word32 -> ProtocolMagicId
ProtocolMagicId Word32
0)
SignTag
SignForTestingOnly
SigningKey
exampleSigningKey
TxSigData
exampleTxSigData
ts_roundTripTxSig :: TSProperty
ts_roundTripTxSig :: TSProperty
ts_roundTripTxSig = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 (forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxSig
genTxSig) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenTxSigData :: Property
goldenTxSigData :: Property
goldenTxSigData =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR TxSigData
exampleTxSigData (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxSigData"
ts_roundTripTxSigData :: TSProperty
ts_roundTripTxSigData :: TSProperty
ts_roundTripTxSigData = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen TxSigData
genTxSigData forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
ts_roundTripTxValidationError :: TSProperty
ts_roundTripTxValidationError :: TSProperty
ts_roundTripTxValidationError =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen TxValidationError
genTxValidationError forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
goldenTxWitness :: Property
goldenTxWitness :: Property
goldenTxWitness =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR Vector TxInWitness
exampleTxWitness (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/utxo/TxWitness"
ts_roundTripTxWitness :: TSProperty
ts_roundTripTxWitness :: TSProperty
ts_roundTripTxWitness = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
20 (forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen (Vector TxInWitness)
genTxWitness) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
ts_roundTripUTxOError :: TSProperty
ts_roundTripUTxOError :: TSProperty
ts_roundTripUTxOError =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen UTxOError
genUTxOError forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
ts_roundTripUTxOValidationError :: TSProperty
ts_roundTripUTxOValidationError :: TSProperty
ts_roundTripUTxOValidationError =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
50 Gen UTxOValidationError
genUTxOValidationError forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
ts_roundTripUTxOConfiguration :: TSProperty
ts_roundTripUTxOConfiguration :: TSProperty
ts_roundTripUTxOConfiguration =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
500 Gen UTxOConfiguration
genUTxOConfiguration forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
sizeEstimates :: H.Group
sizeEstimates :: Group
sizeEstimates =
let sizeTestGen :: (Show a, EncCBOR a) => Gen a -> Property
sizeTestGen :: forall a. (Show a, EncCBOR a) => Gen a -> Property
sizeTestGen Gen a
g = forall a. EncCBOR a => SizeTestConfig a -> Property
sizeTest forall a b. (a -> b) -> a -> b
$ forall a. Show a => SizeTestConfig a
scfg {gen :: Gen a
gen = Gen a
g}
pm :: ProtocolMagicId
pm = Word32 -> ProtocolMagicId
ProtocolMagicId Word32
0
attrUnitSize :: (TypeRep, SizeOverride)
attrUnitSize = (forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(Attributes ())), Size -> SizeOverride
SizeConstant Size
1)
attrAddrSize :: (TypeRep, SizeOverride)
attrAddrSize =
( forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(Attributes AddrAttributes))
, Size -> SizeOverride
SizeConstant ([Case Size] -> Size
szCases [forall t. Text -> t -> Case t
Case Text
"min" Size
1, forall t. Text -> t -> Case t
Case Text
"max" Size
1024])
)
txSigSize :: (TypeRep, SizeOverride)
txSigSize = (forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(Signature TxSigData)), Size -> SizeOverride
SizeConstant Size
66)
in GroupName -> [(PropertyName, Property)] -> Group
H.Group
GroupName
"Encoded size bounds for core types."
[ (PropertyName
"TxId", forall a. (Show a, EncCBOR a) => Gen a -> Property
sizeTestGen Gen TxId
genTxId)
,
( PropertyName
"Tx"
, forall a. EncCBOR a => SizeTestConfig a -> Property
sizeTest
forall a b. (a -> b) -> a -> b
$ forall a. Show a => SizeTestConfig a
scfg
{ gen :: Gen Tx
gen = Gen Tx
genTx
, addlCtx :: Map TypeRep SizeOverride
addlCtx = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(TypeRep, SizeOverride)
attrUnitSize, (TypeRep, SizeOverride)
attrAddrSize]
, computedCtx :: Tx -> Map TypeRep SizeOverride
computedCtx = \Tx
tx ->
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[
( forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(LengthOf [TxIn]))
, Size -> SizeOverride
SizeConstant (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. HasLength a => a -> Int
length forall a b. (a -> b) -> a -> b
$ Tx -> NonEmpty TxIn
txInputs Tx
tx)
)
,
( forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(LengthOf [TxOut]))
, Size -> SizeOverride
SizeConstant (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. HasLength a => a -> Int
length forall a b. (a -> b) -> a -> b
$ Tx -> NonEmpty TxOut
txOutputs Tx
tx)
)
]
}
)
, (PropertyName
"TxIn", forall a. (Show a, EncCBOR a) => Gen a -> Property
sizeTestGen Gen TxIn
genTxIn)
,
( PropertyName
"TxOut"
, forall a. EncCBOR a => SizeTestConfig a -> Property
sizeTest
forall a b. (a -> b) -> a -> b
$ forall a. Show a => SizeTestConfig a
scfg {gen :: Gen TxOut
gen = Gen TxOut
genTxOut, addlCtx :: Map TypeRep SizeOverride
addlCtx = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(TypeRep, SizeOverride)
attrAddrSize]}
)
,
( PropertyName
"TxAux"
, forall a. EncCBOR a => SizeTestConfig a -> Property
sizeTest
forall a b. (a -> b) -> a -> b
$ forall a. Show a => SizeTestConfig a
scfg
{ gen :: Gen TxAux
gen = ProtocolMagicId -> Gen TxAux
genTxAux ProtocolMagicId
pm
, addlCtx :: Map TypeRep SizeOverride
addlCtx = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(TypeRep, SizeOverride)
attrUnitSize, (TypeRep, SizeOverride)
attrAddrSize, (TypeRep, SizeOverride)
txSigSize]
, computedCtx :: TxAux -> Map TypeRep SizeOverride
computedCtx = \TxAux
ta ->
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[
( forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(LengthOf [TxIn]))
, Size -> SizeOverride
SizeConstant (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. HasLength a => a -> Int
length forall a b. (a -> b) -> a -> b
$ Tx -> NonEmpty TxIn
txInputs forall a b. (a -> b) -> a -> b
$ forall a. ATxAux a -> Tx
taTx TxAux
ta)
)
,
( forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(LengthOf (Vector TxInWitness)))
, Size -> SizeOverride
SizeConstant (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. HasLength a => a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. ATxAux a -> Vector TxInWitness
taWitness TxAux
ta)
)
,
( forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall {k} (t :: k). Proxy t
Proxy @(LengthOf [TxOut]))
, Size -> SizeOverride
SizeConstant (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. HasLength a => a -> Int
length forall a b. (a -> b) -> a -> b
$ Tx -> NonEmpty TxOut
txOutputs forall a b. (a -> b) -> a -> b
$ forall a. ATxAux a -> Tx
taTx TxAux
ta)
)
]
}
)
,
( PropertyName
"TxInWitness"
, forall a. EncCBOR a => SizeTestConfig a -> Property
sizeTest
forall a b. (a -> b) -> a -> b
$ forall a. Show a => SizeTestConfig a
scfg {gen :: Gen TxInWitness
gen = ProtocolMagicId -> Gen TxInWitness
genTxInWitness ProtocolMagicId
pm, addlCtx :: Map TypeRep SizeOverride
addlCtx = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(TypeRep, SizeOverride)
txSigSize]}
)
, (PropertyName
"TxSigData", forall a. (Show a, EncCBOR a) => Gen a -> Property
sizeTestGen Gen TxSigData
genTxSigData)
,
( PropertyName
"Signature TxSigData"
, forall a. EncCBOR a => SizeTestConfig a -> Property
sizeTest
forall a b. (a -> b) -> a -> b
$ forall a. Show a => SizeTestConfig a
scfg {gen :: Gen TxSig
gen = ProtocolMagicId -> Gen TxSig
genTxSig ProtocolMagicId
pm, addlCtx :: Map TypeRep SizeOverride
addlCtx = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(TypeRep, SizeOverride)
txSigSize]}
)
]
tests :: TSGroup
tests :: TSGroup
tests =
[TSGroup] -> TSGroup
concatTSGroups
[forall a b. a -> b -> a
const $$FilePath
[(PropertyName, Property)]
Property
FilePath -> PropertyName
FilePath -> GroupName
GroupName -> [(PropertyName, Property)] -> Group
goldenTxWitness :: Property
goldenTxSigData :: Property
goldenTxSig :: Property
goldenTxProof :: Property
goldenTxPayload1 :: Property
goldenTxOut1 :: Property
goldenTxOut :: Property
goldenTxOutList :: Property
goldenRedeemWitness :: Property
goldenVKWitness :: Property
goldenTxInList :: Property
goldenTxId :: Property
goldenTxInUtxo :: Property
goldenHashTx :: Property
goldenTxAttributes :: Property
goldenTx :: Property
discoverGolden, $$discoverRoundTripArg, forall a b. a -> b -> a
const Group
sizeEstimates]