Skip to content

Commit

Permalink
Rename our SlotNo to SlotInEpoch
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
Anviking committed Jul 9, 2020
1 parent 368c038 commit 8a85564
Show file tree
Hide file tree
Showing 18 changed files with 80 additions and 75 deletions.
8 changes: 4 additions & 4 deletions lib/byron/src/Cardano/Wallet/Byron/Compatibility.hs
Expand Up @@ -39,7 +39,7 @@ module Cardano.Wallet.Byron.Compatibility
, toByronHash
, toGenTx
, toPoint
, toSlotNo
, toSlotInEpoch

, fromBlockNo
, fromByronBlock
Expand Down Expand Up @@ -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
Expand Down
8 changes: 4 additions & 4 deletions lib/core/src/Cardano/Byron/Codec/Cbor.hs
Expand Up @@ -66,7 +66,7 @@ import Cardano.Wallet.Primitive.Types
, Hash (..)
, ProtocolMagic (..)
, SlotId (..)
, SlotNo (..)
, SlotInEpoch (..)
, TxIn (..)
, TxOut (..)
, unsafeEpochNo
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
14 changes: 7 additions & 7 deletions lib/core/src/Cardano/Wallet/Api/Types.hs
Expand Up @@ -160,8 +160,8 @@ import Cardano.Wallet.Primitive.Types
, NetworkParameters (..)
, PoolId (..)
, ShowFmt (..)
, SlotInEpoch (..)
, SlotLength (..)
, SlotNo (..)
, StakePoolMetadata
, StartTime (..)
, TxIn (..)
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
10 changes: 5 additions & 5 deletions lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs
Expand Up @@ -35,7 +35,7 @@ import Cardano.Wallet.Primitive.Types
, PoolId
, PoolOwner (..)
, SlotId (..)
, SlotNo (..)
, SlotInEpoch (..)
, StakeKeyCertificate (..)
, StakePoolMetadataHash (..)
, StakePoolMetadataUrl (..)
Expand Down Expand Up @@ -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)
Expand Down
20 changes: 10 additions & 10 deletions lib/core/src/Cardano/Wallet/Primitive/Types.hs
Expand Up @@ -97,7 +97,7 @@ module Cardano.Wallet.Primitive.Types
, FeePolicy (..)
, SlotId (..)
, SlotLength (..)
, SlotNo (..)
, SlotInEpoch (..)
, StartTime (..)
, slotParams

Expand Down Expand Up @@ -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)

Expand Down Expand Up @@ -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.
Expand All @@ -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'.
Expand All @@ -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.
Expand All @@ -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.
Expand Down Expand Up @@ -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.
Expand Down
4 changes: 2 additions & 2 deletions lib/core/test/bench/db/Main.hs
Expand Up @@ -83,7 +83,7 @@ import Cardano.Wallet.Primitive.Types
, Hash (..)
, Range (..)
, SlotId (..)
, SlotNo (unSlotNo)
, SlotInEpoch (unSlotInEpoch)
, SortOrder (..)
, TransactionInfo
, Tx (..)
Expand Down Expand Up @@ -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)
}
)
Expand Down
8 changes: 4 additions & 4 deletions lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs
Expand Up @@ -25,7 +25,7 @@ import Cardano.Wallet.Primitive.Types
, PoolOwner (..)
, PoolRegistrationCertificate (..)
, SlotId (..)
, SlotNo (..)
, SlotInEpoch (..)
, SlotParameters (..)
, StakePoolMetadata (..)
, StakePoolMetadataHash (..)
Expand Down Expand Up @@ -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
Expand Down
8 changes: 4 additions & 4 deletions lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs
Expand Up @@ -123,7 +123,7 @@ import Cardano.Wallet.Primitive.Types
, PoolId (..)
, PoolOwner (..)
, SlotId (..)
, SlotNo (..)
, SlotInEpoch (..)
, SortOrder (..)
, StakePoolMetadata (..)
, StakePoolTicker
Expand Down Expand Up @@ -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
Expand Down
14 changes: 7 additions & 7 deletions lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs
Expand Up @@ -89,7 +89,7 @@ import Cardano.Wallet.Primitive.Types
, Range (..)
, ShowFmt (..)
, SlotId (..)
, SlotNo (..)
, SlotInEpoch (..)
, SlotParameters (..)
, SortOrder (..)
, Tx (..)
Expand Down Expand Up @@ -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
Expand Down
8 changes: 4 additions & 4 deletions lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions lib/core/test/unit/Cardano/Wallet/DB/StateMachine.hs
Expand Up @@ -123,7 +123,7 @@ import Cardano.Wallet.Primitive.Types
, ProtocolParameters (..)
, Range (..)
, SlotId (..)
, SlotNo (..)
, SlotInEpoch (..)
, SortOrder (..)
, StakeKeyCertificate
, TransactionInfo (..)
Expand Down Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions lib/core/test/unit/Cardano/Wallet/Gen.hs
Expand Up @@ -32,7 +32,7 @@ import Cardano.Wallet.Primitive.Types
, Hash (..)
, ProtocolMagic (..)
, SlotId (..)
, SlotNo (..)
, SlotInEpoch (..)
, flatSlot
, unsafeEpochNo
)
Expand Down Expand Up @@ -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
Expand Down
9 changes: 7 additions & 2 deletions lib/core/test/unit/Cardano/Wallet/Network/BlockHeadersSpec.hs
Expand Up @@ -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
Expand Down Expand Up @@ -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)
Expand Down
Expand Up @@ -20,8 +20,8 @@ import Cardano.Wallet.Primitive.Types
, EpochLength (..)
, Hash (..)
, SlotId (..)
, SlotInEpoch (..)
, SlotLength (..)
, SlotNo (..)
, SlotParameters (..)
, StartTime (..)
, unsafeEpochNo
Expand Down Expand Up @@ -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
Expand Down

0 comments on commit 8a85564

Please sign in to comment.