From 8a855640ab52ffbaf35a8e47d9517d862bf69e95 Mon Sep 17 00:00:00 2001 From: Johannes Lund Date: Wed, 8 Jul 2020 11:32:30 +0200 Subject: [PATCH] Rename our SlotNo to SlotInEpoch The SlotNo we use is different from the one in consensus. By renaming it to SlotInEpoch it will be less confusing, and easier for us to start adoping the actual SlotNo. With an epoch length of 2, this is how they differ: ``` Epoch 0 1 2 3 4 SlotNo* 0 1 2 3 4 5 6 7 8 9 SlotInEpoch 0 1 0 1 0 1 0 1 0 1 ``` *) I.e. the one defined in cardano-base and used in ourobouros-consensus. --- .../src/Cardano/Wallet/Byron/Compatibility.hs | 8 ++++---- lib/core/src/Cardano/Byron/Codec/Cbor.hs | 8 ++++---- lib/core/src/Cardano/Wallet/Api/Types.hs | 14 ++++++------- .../src/Cardano/Wallet/DB/Sqlite/Types.hs | 10 +++++----- .../src/Cardano/Wallet/Primitive/Types.hs | 20 +++++++++---------- lib/core/test/bench/db/Main.hs | 4 ++-- .../test/unit/Cardano/Pool/DB/Arbitrary.hs | 8 ++++---- .../test/unit/Cardano/Wallet/Api/TypesSpec.hs | 8 ++++---- .../test/unit/Cardano/Wallet/DB/Arbitrary.hs | 14 ++++++------- .../Cardano/Wallet/DB/Sqlite/TypesSpec.hs | 8 ++++---- .../unit/Cardano/Wallet/DB/StateMachine.hs | 4 ++-- lib/core/test/unit/Cardano/Wallet/Gen.hs | 4 ++-- .../Wallet/Network/BlockHeadersSpec.hs | 9 +++++++-- .../Wallet/Primitive/SyncProgressSpec.hs | 4 ++-- .../Cardano/Wallet/Primitive/TypesSpec.hs | 12 +++++------ lib/core/test/unit/Cardano/WalletSpec.hs | 10 +++++----- .../src/Cardano/Wallet/Jormungandr/Binary.hs | 4 ++-- .../Cardano/Wallet/Jormungandr/NetworkSpec.hs | 6 +++--- 18 files changed, 80 insertions(+), 75 deletions(-) diff --git a/lib/byron/src/Cardano/Wallet/Byron/Compatibility.hs b/lib/byron/src/Cardano/Wallet/Byron/Compatibility.hs index 7348a8b78e0..170289a33fe 100644 --- a/lib/byron/src/Cardano/Wallet/Byron/Compatibility.hs +++ b/lib/byron/src/Cardano/Wallet/Byron/Compatibility.hs @@ -39,7 +39,7 @@ module Cardano.Wallet.Byron.Compatibility , toByronHash , toGenTx , toPoint - , toSlotNo + , toSlotInEpoch , fromBlockNo , fromByronBlock @@ -296,10 +296,10 @@ toPoint -> Point ByronBlock toPoint genesisH epLength (W.BlockHeader sid _ h _) | h == (coerce genesisH) = O.GenesisPoint - | otherwise = O.Point $ Point.block (toSlotNo epLength sid) (toByronHash h) + | otherwise = O.Point $ Point.block (toSlotInEpoch epLength sid) (toByronHash h) -toSlotNo :: W.EpochLength -> W.SlotId -> SlotNo -toSlotNo epLength = +toSlotInEpoch :: W.EpochLength -> W.SlotId -> SlotNo +toSlotInEpoch epLength = SlotNo . W.flatSlot epLength -- | SealedTx are the result of rightfully constructed byron transactions so, it diff --git a/lib/core/src/Cardano/Byron/Codec/Cbor.hs b/lib/core/src/Cardano/Byron/Codec/Cbor.hs index eee1d14554b..cf7eafc4604 100644 --- a/lib/core/src/Cardano/Byron/Codec/Cbor.hs +++ b/lib/core/src/Cardano/Byron/Codec/Cbor.hs @@ -66,7 +66,7 @@ import Cardano.Wallet.Primitive.Types , Hash (..) , ProtocolMagic (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , TxIn (..) , TxOut (..) , unsafeEpochNo @@ -316,8 +316,8 @@ decodeEpochNo :: HasCallStack => CBOR.Decoder s EpochNo decodeEpochNo = unsafeEpochNo . fromIntegral @Word64 @Word32 <$> CBOR.decodeWord64 -decodeSlotNo :: CBOR.Decoder s SlotNo -decodeSlotNo = SlotNo . fromIntegral <$> CBOR.decodeWord16 +decodeSlotInEpoch :: CBOR.Decoder s SlotInEpoch +decodeSlotInEpoch = SlotInEpoch . fromIntegral <$> CBOR.decodeWord16 decodeGenesisBlockHeader :: CBOR.Decoder s BlockHeader decodeGenesisBlockHeader = do @@ -491,7 +491,7 @@ decodeSlotId :: CBOR.Decoder s SlotId decodeSlotId = do _ <- CBOR.decodeListLenCanonicalOf 2 epoch <- decodeEpochNo - SlotId epoch <$> decodeSlotNo + SlotId epoch <$> decodeSlotInEpoch decodeSoftwareVersion :: CBOR.Decoder s () decodeSoftwareVersion = do diff --git a/lib/core/src/Cardano/Wallet/Api/Types.hs b/lib/core/src/Cardano/Wallet/Api/Types.hs index 4cafc365095..30bcc242502 100644 --- a/lib/core/src/Cardano/Wallet/Api/Types.hs +++ b/lib/core/src/Cardano/Wallet/Api/Types.hs @@ -160,8 +160,8 @@ import Cardano.Wallet.Primitive.Types , NetworkParameters (..) , PoolId (..) , ShowFmt (..) + , SlotInEpoch (..) , SlotLength (..) - , SlotNo (..) , StakePoolMetadata , StartTime (..) , TxIn (..) @@ -554,13 +554,13 @@ data ApiTimeReference = ApiTimeReference data ApiBlockReference = ApiBlockReference { epochNumber :: !(ApiT EpochNo) - , slotNumber :: !(ApiT SlotNo) + , slotNumber :: !(ApiT SlotInEpoch) , height :: !(Quantity "block" Natural) } deriving (Eq, Generic, Show) data ApiNetworkTip = ApiNetworkTip { epochNumber :: !(ApiT EpochNo) - , slotNumber :: !(ApiT SlotNo) + , slotNumber :: !(ApiT SlotInEpoch) } deriving (Eq, Generic, Show) data ApiNetworkInformation = ApiNetworkInformation @@ -1124,10 +1124,10 @@ instance FromJSON (ApiT EpochNo) where instance ToJSON (ApiT EpochNo) where toJSON (ApiT (EpochNo en)) = toJSON $ fromIntegral @Word31 @Word32 en -instance FromJSON (ApiT SlotNo) where - parseJSON = fmap (ApiT . SlotNo) . parseJSON -instance ToJSON (ApiT SlotNo) where - toJSON (ApiT (SlotNo sn)) = toJSON sn +instance FromJSON (ApiT SlotInEpoch) where + parseJSON = fmap (ApiT . SlotInEpoch) . parseJSON +instance ToJSON (ApiT SlotInEpoch) where + toJSON (ApiT (SlotInEpoch sn)) = toJSON sn instance FromJSON ApiNetworkTip where parseJSON = genericParseJSON defaultRecordTypeOptions diff --git a/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs b/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs index 7e416de1618..63854a08f35 100644 --- a/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs +++ b/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs @@ -35,7 +35,7 @@ import Cardano.Wallet.Primitive.Types , PoolId , PoolOwner (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , StakeKeyCertificate (..) , StakePoolMetadataHash (..) , StakePoolMetadataUrl (..) @@ -307,11 +307,11 @@ instance ToJSON SlotId where instance FromJSON SlotId where parseJSON = genericParseJSON defaultOptions -instance ToJSON SlotNo where - toJSON (SlotNo n) = toJSON n +instance ToJSON SlotInEpoch where + toJSON (SlotInEpoch n) = toJSON n -instance FromJSON SlotNo where - parseJSON = fmap SlotNo . parseJSON +instance FromJSON SlotInEpoch where + parseJSON = fmap SlotInEpoch . parseJSON instance ToJSON EpochNo where toJSON (EpochNo n) = toJSON (fromIntegral @Word31 @Word32 n) diff --git a/lib/core/src/Cardano/Wallet/Primitive/Types.hs b/lib/core/src/Cardano/Wallet/Primitive/Types.hs index 02c3b2afbdb..761bf70d20c 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/Types.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/Types.hs @@ -97,7 +97,7 @@ module Cardano.Wallet.Primitive.Types , FeePolicy (..) , SlotId (..) , SlotLength (..) - , SlotNo (..) + , SlotInEpoch (..) , StartTime (..) , slotParams @@ -1459,10 +1459,10 @@ instance Buildable TxParameters where -- | A slot identifier is the combination of an epoch and slot. data SlotId = SlotId { epochNumber :: !EpochNo - , slotNumber :: !SlotNo + , slotNumber :: !SlotInEpoch } deriving stock (Show, Read, Eq, Ord, Generic) -newtype SlotNo = SlotNo { unSlotNo :: Word32 } +newtype SlotInEpoch = SlotInEpoch { unSlotInEpoch :: Word32 } deriving stock (Show, Read, Eq, Ord, Generic) deriving newtype (Num, Buildable, NFData, Enum) @@ -1520,7 +1520,7 @@ epochSucc (EpochNo e) instance NFData SlotId instance Buildable SlotId where - build (SlotId (EpochNo e) (SlotNo s)) = + build (SlotId (EpochNo e) (SlotInEpoch s)) = fromString (show e) <> "." <> fromString (show s) -- | The essential parameters necessary for performing slot arithmetic. @@ -1537,7 +1537,7 @@ data SlotParameters = SlotParameters -- | Convert a 'SlotId' to the number of slots since genesis. flatSlot :: EpochLength -> SlotId -> Word64 -flatSlot (EpochLength epochLength) (SlotId (EpochNo e) (SlotNo s)) = +flatSlot (EpochLength epochLength) (SlotId (EpochNo e) (SlotInEpoch s)) = fromIntegral epochLength * fromIntegral e + fromIntegral s -- | Convert a 'flatSlot' index to 'SlotId'. @@ -1563,7 +1563,7 @@ fromFlatSlot el@(EpochLength epochLength) n e = n `div` fromIntegral epochLength s = n `mod` fromIntegral epochLength maxFlatSlot = - flatSlot el (SlotId (EpochNo maxBound) (SlotNo $ epochLength - 1)) + flatSlot el (SlotId (EpochNo maxBound) (SlotInEpoch $ epochLength - 1)) -- | @slotDifference a b@ is how many slots @a@ is after @b@. The result is -- non-negative, and if @b > a@ then this function returns zero. @@ -1580,12 +1580,12 @@ slotPred :: SlotParameters -> SlotId -> Maybe SlotId slotPred (SlotParameters (EpochLength el) _ _ _) (SlotId en sn) | en == 0 && sn == 0 = Nothing | sn > 0 = Just $ SlotId en (sn - 1) - | otherwise = Just $ SlotId (en - 1) (SlotNo $ el - 1) + | otherwise = Just $ SlotId (en - 1) (SlotInEpoch $ el - 1) -- | Return the slot immediately after the given slot. slotSucc :: SlotParameters -> SlotId -> SlotId -slotSucc (SlotParameters (EpochLength el) _ _ _) (SlotId en (SlotNo sn)) - | sn < el - 1 = SlotId en (SlotNo $ sn + 1) +slotSucc (SlotParameters (EpochLength el) _ _ _) (SlotId en (SlotInEpoch sn)) + | sn < el - 1 = SlotId en (SlotInEpoch $ sn + 1) | otherwise = SlotId (en + 1) 0 -- | The time when a slot begins. @@ -1626,7 +1626,7 @@ slotAt (SlotParameters (EpochLength el) (SlotLength sl) (StartTime st) _) t epochNumber = EpochNo $ floor (diff / epochLength) - slotNumber = SlotNo $ + slotNumber = SlotInEpoch $ floor ((diff - fromIntegral (unEpochNo epochNumber) * epochLength) / sl) -- | Transforms the given inclusive time range into an inclusive slot range. diff --git a/lib/core/test/bench/db/Main.hs b/lib/core/test/bench/db/Main.hs index 324a50a2040..e8db129cb74 100644 --- a/lib/core/test/bench/db/Main.hs +++ b/lib/core/test/bench/db/Main.hs @@ -83,7 +83,7 @@ import Cardano.Wallet.Primitive.Types , Hash (..) , Range (..) , SlotId (..) - , SlotNo (unSlotNo) + , SlotInEpoch (unSlotInEpoch) , SortOrder (..) , TransactionInfo , Tx (..) @@ -411,7 +411,7 @@ mkTxHistory numTx numInputs numOutputs range = { status = [InLedger, Pending] !! (i `mod` 2) , direction = Incoming , slotId = sl i - , blockHeight = Quantity $ fromIntegral $ unSlotNo $ slotNumber $ sl i + , blockHeight = Quantity $ fromIntegral $ unSlotInEpoch $ slotNumber $ sl i , amount = Quantity (fromIntegral numOutputs) } ) diff --git a/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs b/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs index 04c914bea0a..cbe32f3c7ff 100644 --- a/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs +++ b/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs @@ -25,7 +25,7 @@ import Cardano.Wallet.Primitive.Types , PoolOwner (..) , PoolRegistrationCertificate (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , SlotParameters (..) , StakePoolMetadata (..) , StakePoolMetadataHash (..) @@ -94,9 +94,9 @@ instance Arbitrary SlotId where uncurry SlotId <$> shrink (ep, sl) arbitrary = applyArbitrary2 SlotId -instance Arbitrary SlotNo where - shrink (SlotNo x) = SlotNo <$> shrink x - arbitrary = SlotNo <$> choose (0, fromIntegral arbitraryChainLength) +instance Arbitrary SlotInEpoch where + shrink (SlotInEpoch x) = SlotInEpoch <$> shrink x + arbitrary = SlotInEpoch <$> choose (0, fromIntegral arbitraryChainLength) instance Arbitrary EpochNo where shrink (EpochNo x) = EpochNo <$> shrink x diff --git a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs index d0f1d3c8779..795ab46cd92 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -123,7 +123,7 @@ import Cardano.Wallet.Primitive.Types , PoolId (..) , PoolOwner (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , SortOrder (..) , StakePoolMetadata (..) , StakePoolTicker @@ -1183,9 +1183,9 @@ instance Arbitrary SlotId where arbitrary = applyArbitrary2 SlotId shrink = genericShrink -instance Arbitrary SlotNo where - shrink (SlotNo x) = SlotNo <$> shrink x - arbitrary = SlotNo <$> arbitrary +instance Arbitrary SlotInEpoch where + shrink (SlotInEpoch x) = SlotInEpoch <$> shrink x + arbitrary = SlotInEpoch <$> arbitrary instance Arbitrary EpochNo where shrink (EpochNo x) = EpochNo <$> shrink x diff --git a/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs b/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs index 6f1a94aa9ce..51a6716a818 100644 --- a/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs +++ b/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs @@ -89,7 +89,7 @@ import Cardano.Wallet.Primitive.Types , Range (..) , ShowFmt (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , SlotParameters (..) , SortOrder (..) , Tx (..) @@ -347,19 +347,19 @@ instance Arbitrary PassphraseScheme where instance Arbitrary BlockHeader where arbitrary = do - sid@(SlotId (EpochNo ep) (SlotNo sl)) <- arbitrary + sid@(SlotId (EpochNo ep) (SlotInEpoch sl)) <- arbitrary let h = fromIntegral sl + fromIntegral ep * arbitraryEpochLength blockH <- arbitrary pure $ BlockHeader sid (Quantity h) blockH (coerce blockH) instance Arbitrary SlotId where - shrink (SlotId (EpochNo ep) (SlotNo sl)) = - uncurry SlotId <$> shrink (EpochNo ep, SlotNo sl) + shrink (SlotId (EpochNo ep) (SlotInEpoch sl)) = + uncurry SlotId <$> shrink (EpochNo ep, SlotInEpoch sl) arbitrary = applyArbitrary2 SlotId -instance Arbitrary SlotNo where - shrink (SlotNo x) = SlotNo <$> shrink x - arbitrary = SlotNo <$> choose (0, fromIntegral arbitraryChainLength) +instance Arbitrary SlotInEpoch where + shrink (SlotInEpoch x) = SlotInEpoch <$> shrink x + arbitrary = SlotInEpoch <$> choose (0, fromIntegral arbitraryChainLength) instance Arbitrary EpochNo where shrink (EpochNo x) = EpochNo <$> shrink x diff --git a/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs index d8527a35170..c248956bc6f 100644 --- a/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs @@ -14,7 +14,7 @@ import Prelude import Cardano.Wallet.DB.Sqlite.Types () import Cardano.Wallet.Primitive.Types - ( EpochNo (..), SlotId (..), SlotNo (..) ) + ( EpochNo (..), SlotId (..), SlotInEpoch (..) ) import Data.Proxy ( Proxy (..) ) import Data.Typeable @@ -64,9 +64,9 @@ instance Arbitrary EpochNo where arbitrary = EpochNo <$> arbitrary shrink (EpochNo n) = EpochNo <$> shrink n -instance Arbitrary SlotNo where - arbitrary = SlotNo <$> arbitrary - shrink (SlotNo n) = SlotNo <$> shrink n +instance Arbitrary SlotInEpoch where + arbitrary = SlotInEpoch <$> arbitrary + shrink (SlotInEpoch n) = SlotInEpoch <$> shrink n instance Arbitrary Word31 where arbitrary = arbitrarySizedBoundedIntegral diff --git a/lib/core/test/unit/Cardano/Wallet/DB/StateMachine.hs b/lib/core/test/unit/Cardano/Wallet/DB/StateMachine.hs index 9beb16d564d..2ea95da210d 100644 --- a/lib/core/test/unit/Cardano/Wallet/DB/StateMachine.hs +++ b/lib/core/test/unit/Cardano/Wallet/DB/StateMachine.hs @@ -123,7 +123,7 @@ import Cardano.Wallet.Primitive.Types , ProtocolParameters (..) , Range (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , SortOrder (..) , StakeKeyCertificate , TransactionInfo (..) @@ -784,7 +784,7 @@ instance ToExpr SlotId where instance ToExpr EpochNo where toExpr = defaultExprViaShow -instance ToExpr SlotNo where +instance ToExpr SlotInEpoch where toExpr = genericToExpr instance ToExpr TxStatus where diff --git a/lib/core/test/unit/Cardano/Wallet/Gen.hs b/lib/core/test/unit/Cardano/Wallet/Gen.hs index d55600f5751..cf0e73d4e12 100644 --- a/lib/core/test/unit/Cardano/Wallet/Gen.hs +++ b/lib/core/test/unit/Cardano/Wallet/Gen.hs @@ -32,7 +32,7 @@ import Cardano.Wallet.Primitive.Types , Hash (..) , ProtocolMagic (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , flatSlot , unsafeEpochNo ) @@ -104,7 +104,7 @@ genSlotId :: EpochLength -> Gen SlotId genSlotId (EpochLength el) | el > 0 = do ep <- choose (0, 10) sl <- choose (0, el - 1) - return (SlotId (unsafeEpochNo ep) (SlotNo sl)) + return (SlotId (unsafeEpochNo ep) (SlotInEpoch sl)) genSlotId _ = error "genSlotId: epochLength must > 0" genBlockHeader :: SlotId -> Gen BlockHeader diff --git a/lib/core/test/unit/Cardano/Wallet/Network/BlockHeadersSpec.hs b/lib/core/test/unit/Cardano/Wallet/Network/BlockHeadersSpec.hs index 5589af64715..81da20f3e31 100644 --- a/lib/core/test/unit/Cardano/Wallet/Network/BlockHeadersSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Network/BlockHeadersSpec.hs @@ -20,7 +20,12 @@ import Cardano.Wallet.Network.BlockHeaders , updateUnstableBlocks ) import Cardano.Wallet.Primitive.Types - ( BlockHeader (..), EpochNo (..), Hash (..), SlotId (..), SlotNo (..) ) + ( BlockHeader (..) + , EpochNo (..) + , Hash (..) + , SlotId (..) + , SlotInEpoch (..) + ) import Control.Monad.Trans.Class ( lift ) import Control.Monad.Trans.Writer @@ -419,7 +424,7 @@ instance Arbitrary TestCase where , localChain = [genesis] <> base <> startFrom baseTip local } where - startFrom (SlotId (EpochNo ep) (SlotNo n)) xs = + startFrom (SlotId (EpochNo ep) (SlotInEpoch n)) xs = [ BlockHeader (SlotId (EpochNo ep) (sl+fromIntegral n)) bh' hh prev | BlockHeader (SlotId _ sl) (Quantity bh) hh prev <- xs , let bh' = Quantity (bh+fromIntegral n+1) diff --git a/lib/core/test/unit/Cardano/Wallet/Primitive/SyncProgressSpec.hs b/lib/core/test/unit/Cardano/Wallet/Primitive/SyncProgressSpec.hs index 524c3a74d6c..ca75817da2b 100644 --- a/lib/core/test/unit/Cardano/Wallet/Primitive/SyncProgressSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Primitive/SyncProgressSpec.hs @@ -20,8 +20,8 @@ import Cardano.Wallet.Primitive.Types , EpochLength (..) , Hash (..) , SlotId (..) + , SlotInEpoch (..) , SlotLength (..) - , SlotNo (..) , SlotParameters (..) , StartTime (..) , unsafeEpochNo @@ -192,7 +192,7 @@ instance Arbitrary SlotId where arbitrary = do ep <- choose (0, 10) sl <- choose (0, 100) - return (SlotId (unsafeEpochNo ep) (SlotNo sl)) + return (SlotId (unsafeEpochNo ep) (SlotInEpoch sl)) instance Arbitrary ActiveSlotCoefficient where shrink = shrinkActiveSlotCoefficient diff --git a/lib/core/test/unit/Cardano/Wallet/Primitive/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/Primitive/TypesSpec.hs index 24c9616cfb0..5ff3c258adf 100644 --- a/lib/core/test/unit/Cardano/Wallet/Primitive/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Primitive/TypesSpec.hs @@ -45,8 +45,8 @@ import Cardano.Wallet.Primitive.Types , RangeBound (..) , ShowFmt (..) , SlotId (..) + , SlotInEpoch (..) , SlotLength (..) - , SlotNo (..) , SlotParameters (..) , StartTime (..) , Tx (..) @@ -299,8 +299,8 @@ spec = do -- -- For flat slot values that are higher than this maximum, we expect -- the 'fromFlatSlot' function to fail with an error. - let maxSlotNo = SlotNo $ unEpochLength slotsPerEpoch - 1 - let maxSlotId = SlotId (EpochNo maxBound) maxSlotNo + let maxSlotInEpoch = SlotInEpoch $ unEpochLength slotsPerEpoch - 1 + let maxSlotId = SlotId (EpochNo maxBound) maxSlotInEpoch let maxFlatSlot = flatSlot slotsPerEpoch maxSlotId let result = flatSlot slotsPerEpoch $ fromFlatSlot slotsPerEpoch n checkCoverage $ @@ -1220,7 +1220,7 @@ instance Arbitrary SlotId where arbitrary = do ep <- choose (0, 10) sl <- choose (0, 100) - return (SlotId (unsafeEpochNo ep) (SlotNo sl)) + return (SlotId (unsafeEpochNo ep) (SlotInEpoch sl)) instance Arbitrary Block where shrink (Block h txs _) = Block h <$> shrink txs <*> pure [] @@ -1319,12 +1319,12 @@ instance {-# OVERLAPS #-} Arbitrary (EpochLength, SlotId) where shrink (a,b) = filter validSlotConfig $ zip (shrink a) (shrink b) where - validSlotConfig (EpochLength ep, SlotId _ (SlotNo sl)) = sl < ep + validSlotConfig (EpochLength ep, SlotId _ (SlotInEpoch sl)) = sl < ep arbitrary = do (EpochLength epochLength) <- arbitrary ep <- unsafeEpochNo <$> choose (0, 1000) - sl <- SlotNo <$> choose (0, fromIntegral epochLength - 1) + sl <- SlotInEpoch <$> choose (0, fromIntegral epochLength - 1) return (EpochLength epochLength, SlotId ep sl) instance Arbitrary Word31 where diff --git a/lib/core/test/unit/Cardano/WalletSpec.hs b/lib/core/test/unit/Cardano/WalletSpec.hs index c0957ea6358..7fd61da8d52 100644 --- a/lib/core/test/unit/Cardano/WalletSpec.hs +++ b/lib/core/test/unit/Cardano/WalletSpec.hs @@ -79,7 +79,7 @@ import Cardano.Wallet.Primitive.Types , PoolId (..) , SealedTx (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , SortOrder (..) , TransactionInfo (txInfoMeta) , TransactionInfo (..) @@ -759,9 +759,9 @@ instance Arbitrary SlotId where shrink _ = [] arbitrary = applyArbitrary2 SlotId -instance Arbitrary SlotNo where - shrink (SlotNo x) = SlotNo <$> shrink x - arbitrary = SlotNo <$> arbitrary +instance Arbitrary SlotInEpoch where + shrink (SlotInEpoch x) = SlotInEpoch <$> shrink x + arbitrary = SlotInEpoch <$> arbitrary instance Arbitrary EpochNo where shrink (EpochNo x) = EpochNo <$> shrink x @@ -814,6 +814,6 @@ instance Arbitrary TxMeta where <*> elements [Incoming, Outgoing] <*> (SlotId <$> (unsafeEpochNo <$> choose (0, 1000)) - <*> (SlotNo <$> choose (0, 21599))) + <*> (SlotInEpoch <$> choose (0, 21599))) <*> fmap Quantity arbitrary <*> fmap (Quantity . fromIntegral) (arbitrary @Word32) diff --git a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs index 121acef7d64..ebf6a2721c3 100644 --- a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs +++ b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs @@ -105,7 +105,7 @@ import Cardano.Wallet.Primitive.Types , PoolOwner (..) , SealedTx (..) , SlotId (..) - , SlotNo (..) + , SlotInEpoch (..) , Tx (..) , TxIn (..) , TxOut (..) @@ -227,7 +227,7 @@ getBlockHeader = label "getBlockHeader" $ do version <- getWord16be contentSize <- getWord32be slotEpoch <- getEpochNo - slotNo <- SlotNo <$> getWord32be + slotNo <- SlotInEpoch <$> getWord32be chainLength <- getWord32be contentHash <- Hash <$> getByteString 32 parentHeaderHash <- Hash <$> getByteString 32 diff --git a/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/NetworkSpec.hs b/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/NetworkSpec.hs index 6c52ffcc5ca..016096551e9 100644 --- a/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/NetworkSpec.hs +++ b/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/NetworkSpec.hs @@ -34,7 +34,7 @@ import Cardano.Wallet.Primitive.Types , NetworkParameters (..) , ProtocolParameters (..) , SlotId (..) - , SlotNo (unSlotNo) + , SlotInEpoch (unSlotInEpoch) , TxParameters (..) ) import Control.Concurrent.MVar.Lifted @@ -249,7 +249,7 @@ addGaps getSlot (b1:b2:bs) = [Just b1] ++ replicate gap Nothing ++ addGaps getSlot (b2:bs) where gap = slotNum b2 - slotNum b1 - 1 - slotNum = fromIntegral . unSlotNo . slotNumber . getSlot + slotNum = fromIntegral . unSlotInEpoch . slotNumber . getSlot -- | Test Genesis block block0 :: J.Block @@ -693,7 +693,7 @@ genBlocksWith n empty count = tip = getNodeTip n tipSlot = maybe (-1) - (fromIntegral . unSlotNo . slotNumber . mockBlockSlot) + (fromIntegral . unSlotInEpoch . slotNumber . mockBlockSlot) tip slots = [ SlotId 0 (fromIntegral $ tipSlot + i)