{-# LANGUAGE TemplateHaskell #-}
module Test.Cardano.Chain.Slotting.CBOR (
tests,
)
where
import Cardano.Chain.Slotting (EpochSlots (..), SlotNumber)
import Cardano.Prelude
import GetDataFileName ((<:<))
import Hedgehog (Property)
import Test.Cardano.Chain.Slotting.Example (
exampleEpochAndSlotCount,
exampleEpochNumber,
)
import Test.Cardano.Chain.Slotting.Gen (
feedPMEpochSlots,
genEpochAndSlotCount,
genEpochNumber,
genEpochSlots,
genSlotNumber,
)
import Test.Cardano.Ledger.Binary.Vintage.Helpers.GoldenRoundTrip (
goldenTestCBOR,
roundTripsCBORBuildable,
)
import Test.Cardano.Prelude
import Test.Options (TSGroup, TSProperty, concatTSGroups, eachOfTS)
golden_EpochNumber :: Property
golden_EpochNumber :: Property
golden_EpochNumber =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR EpochNumber
exampleEpochNumber (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/slotting/EpochNumber"
ts_roundTripEpochNumberCBOR :: TSProperty
ts_roundTripEpochNumberCBOR :: TSProperty
ts_roundTripEpochNumberCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 Gen EpochNumber
genEpochNumber forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
golden_SlotNumber :: Property
golden_SlotNumber :: Property
golden_SlotNumber = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR SlotNumber
fsi (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/slotting/SlotNumber"
where
fsi :: SlotNumber
fsi = SlotNumber
5001 :: SlotNumber
ts_roundTripSlotNumberCBOR :: TSProperty
ts_roundTripSlotNumberCBOR :: TSProperty
ts_roundTripSlotNumberCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 Gen SlotNumber
genSlotNumber forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
golden_EpochSlots :: Property
golden_EpochSlots :: Property
golden_EpochSlots = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR EpochSlots
sc (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/slotting/EpochSlots"
where
sc :: EpochSlots
sc = Word64 -> EpochSlots
EpochSlots Word64
474747
ts_roundTripEpochSlotsCBOR :: TSProperty
ts_roundTripEpochSlotsCBOR :: TSProperty
ts_roundTripEpochSlotsCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 Gen EpochSlots
genEpochSlots forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
golden_EpochAndSlotCount :: Property
golden_EpochAndSlotCount :: Property
golden_EpochAndSlotCount =
forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR
EpochAndSlotCount
exampleEpochAndSlotCount
(FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/cbor/slotting/EpochAndSlotCount"
ts_roundTripEpochAndSlotCountCBOR :: TSProperty
ts_roundTripEpochAndSlotCountCBOR :: TSProperty
ts_roundTripEpochAndSlotCountCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 Gen EpochAndSlotCount
gen forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
where
gen :: Gen EpochAndSlotCount
gen = forall a. (ProtocolMagicId -> EpochSlots -> Gen a) -> Gen a
feedPMEpochSlots (\ProtocolMagicId
_pm EpochSlots
es -> EpochSlots -> Gen EpochAndSlotCount
genEpochAndSlotCount EpochSlots
es)
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
golden_EpochAndSlotCount :: Property
golden_EpochSlots :: Property
golden_SlotNumber :: Property
golden_EpochNumber :: Property
discoverGolden, $$discoverRoundTripArg]