Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
<!--
A new scriv changelog fragment.

Uncomment the section that is right (remove the HTML comment wrapper).
For top level release notes, leave all the headers commented out.
-->

<!--
### Patch

- A bullet item for the Patch category.

-->

### Non-Breaking

- Add plumbing to provide a SystemTime to the PerasCertDB in ordert to record
certificate arrival times.

<!--
### Breaking

- A bullet item for the Breaking category.

-->
Original file line number Diff line number Diff line change
Expand Up @@ -263,6 +263,7 @@ mkHandlers
, keepAliveRng
, miniProtocolParameters
, getDiffusionPipeliningSupport
, systemTime
}
NodeKernel
{ getChainDB
Expand Down Expand Up @@ -322,7 +323,7 @@ mkHandlers
, 10 -- TODO: see https://github.com/tweag/cardano-peras/issues/97
, 10 -- TODO: see https://github.com/tweag/cardano-peras/issues/97
)
(makePerasCertPoolWriterFromChainDB $ getChainDB)
(makePerasCertPoolWriterFromChainDB systemTime getChainDB)
version
controlMessageSTM
, hPerasCertDiffusionServer = \version peer ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -578,6 +578,7 @@ runWith RunNodeArgs{..} encAddrNtN decAddrNtN LowLevelRunNodeArgs{..} =
cfg
rnTraceConsensus
btime
systemTime
(InFutureCheck.realHeaderInFutureCheck llrnMaxClockSkew systemTime)
historicityCheck
chainDB
Expand Down Expand Up @@ -855,6 +856,7 @@ mkNodeKernelArgs ::
TopLevelConfig blk ->
Tracers m (ConnectionId addrNTN) (ConnectionId addrNTC) blk ->
BlockchainTime m ->
SystemTime m ->
InFutureCheck.SomeHeaderInFutureCheck m blk ->
(m GSM.GsmState -> HistoricityCheck m blk) ->
ChainDB m blk ->
Expand All @@ -874,6 +876,7 @@ mkNodeKernelArgs
cfg
tracers
btime
systemTime
chainSyncFutureCheck
chainSyncHistoricityCheck
chainDB
Expand All @@ -892,6 +895,7 @@ mkNodeKernelArgs
, registry
, cfg
, btime
, systemTime
, chainDB
, initChainDB = nodeInitChainDB
, chainSyncFutureCheck
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -196,6 +196,7 @@ data NodeKernelArgs m addrNTN addrNTC blk = NodeKernelArgs
, registry :: ResourceRegistry m
, cfg :: TopLevelConfig blk
, btime :: BlockchainTime m
, systemTime :: SystemTime m
, chainDB :: ChainDB m blk
, initChainDB :: StorageConfig blk -> InitChainDB m blk -> m ()
, chainSyncFutureCheck :: SomeHeaderInFutureCheck m blk
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1046,6 +1046,7 @@ runThreadNetwork
, registry
, cfg = pInfoConfig
, btime
, systemTime
, chainDB
, initChainDB = nodeInitChainDB
, chainSyncFutureCheck =
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
<!--
A new scriv changelog fragment.

Uncomment the section that is right (remove the HTML comment wrapper).
For top level release notes, leave all the headers commented out.
-->

<!--
### Patch

- A bullet item for the Patch category.

-->
### Non-Breaking

- Introduce `Ouroboros.Consensus.Peras.Params` module.
- Introduce `WithArrivalTime` combinator.
- Refactor `HasPerasCertX` field projection typeclasses.
- Add `getLatestCertSeen` method to the PerasCertDB API.

<!--
### Breaking

- A bullet item for the Breaking category.

-->
1 change: 1 addition & 0 deletions ouroboros-consensus/ouroboros-consensus.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -203,6 +203,7 @@ library
Ouroboros.Consensus.Node.Run
Ouroboros.Consensus.Node.Serialisation
Ouroboros.Consensus.NodeId
Ouroboros.Consensus.Peras.Params
Ouroboros.Consensus.Peras.SelectView
Ouroboros.Consensus.Peras.Weight
Ouroboros.Consensus.Protocol.Abstract
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
Expand All @@ -13,59 +13,49 @@

module Ouroboros.Consensus.Block.SupportsPeras
( PerasRoundNo (..)
, PerasWeight (..)
, onPerasRoundNo
, BlockSupportsPeras (..)
, PerasCert (..)
, PerasCfg (..)
, ValidatedPerasCert (..)
, makePerasCfg
, HasPerasCert (..)
, getPerasCertRound
, getPerasCertBoostedBlock
, getPerasCertBoost

-- * Ouroboros Peras round length
, PerasRoundLength (..)
, defaultPerasRoundLength
, HasPerasCertRound (..)
, HasPerasCertBoostedBlock (..)
, HasPerasCertBoost (..)

-- * Convenience re-exports
, module Ouroboros.Consensus.Peras.Params
) where

import Codec.Serialise (Serialise (..))
import Codec.Serialise.Decoding (decodeListLenOf)
import Codec.Serialise.Encoding (encodeListLen)
import Data.Monoid (Sum (..))
import Data.Coerce (coerce)
import Data.Proxy (Proxy (..))
import Data.Word (Word64)
import GHC.Generics (Generic)
import NoThunks.Class
import Ouroboros.Consensus.Block.Abstract
import Ouroboros.Consensus.BlockchainTime.WallClock.Types (WithArrivalTime (..))
import Ouroboros.Consensus.Peras.Params
import Ouroboros.Consensus.Util
import Ouroboros.Consensus.Util.Condense
import Quiet (Quiet (..))

newtype PerasRoundNo = PerasRoundNo {unPerasRoundNo :: Word64}
deriving Show via Quiet PerasRoundNo
deriving stock Generic
deriving newtype (Enum, Eq, Ord, NoThunks, Serialise)
deriving newtype (Enum, Eq, Ord, Num, Bounded, NoThunks, Serialise)

instance Condense PerasRoundNo where
condense = show . unPerasRoundNo

instance ShowProxy PerasRoundNo where
showProxy _ = "PerasRoundNo"

newtype PerasWeight = PerasWeight {unPerasWeight :: Word64}
deriving Show via Quiet PerasWeight
deriving stock Generic
deriving newtype (Eq, Ord, NoThunks)
deriving (Semigroup, Monoid) via Sum Word64

instance Condense PerasWeight where
condense = show . unPerasWeight

-- | TODO: this will become a Ledger protocol parameter
-- see https://github.com/tweag/cardano-peras/issues/119
boostPerCert :: PerasWeight
boostPerCert = PerasWeight 15
-- | Lift a binary operation on 'Word64' to 'PerasRoundNo'
onPerasRoundNo ::
(Word64 -> Word64 -> Word64) ->
(PerasRoundNo -> PerasRoundNo -> PerasRoundNo)
onPerasRoundNo = coerce

-- TODO using 'Validated' for extra safety? Or some @.Unsafe@ module?
data ValidatedPerasCert blk = ValidatedPerasCert
Expand All @@ -76,27 +66,16 @@ data ValidatedPerasCert blk = ValidatedPerasCert
deriving anyclass NoThunks

{-------------------------------------------------------------------------------
Ouroboros Peras round length
-- * BlockSupportsPeras class
-------------------------------------------------------------------------------}

newtype PerasRoundLength = PerasRoundLength {unPerasRoundLength :: Word64}
deriving stock (Show, Eq, Ord)
deriving newtype (NoThunks, Num)

-- | See the Protocol parameters section of the Peras design report:
-- https://tweag.github.io/cardano-peras/peras-design.pdf#section.2.1
-- TODO: this will become a Ledger protocol parameter
-- see https://github.com/tweag/cardano-peras/issues/119
defaultPerasRoundLength :: PerasRoundLength
defaultPerasRoundLength = 90

class
( Show (PerasCfg blk)
, NoThunks (PerasCert blk)
) =>
BlockSupportsPeras blk
where
data PerasCfg blk
type PerasCfg blk

data PerasCert blk

Expand All @@ -110,13 +89,7 @@ class
-- TODO: degenerate instance for all blks to get things to compile
-- see https://github.com/tweag/cardano-peras/issues/73
instance StandardHash blk => BlockSupportsPeras blk where
newtype PerasCfg blk = PerasCfg
{ -- TODO: eventually, this will come from the
-- protocol parameters from the ledger state
-- see https://github.com/tweag/cardano-peras/issues/119
perasCfgWeightBoost :: PerasWeight
}
deriving stock (Show, Eq)
type PerasCfg blk = PerasParams

data PerasCert blk = PerasCert
{ pcCertRound :: PerasRoundNo
Expand All @@ -134,11 +107,11 @@ instance StandardHash blk => BlockSupportsPeras blk where
-- TODO: perform actual validation against all
-- possible 'PerasValidationErr' variants
-- see https://github.com/tweag/cardano-peras/issues/120
validatePerasCert cfg cert =
validatePerasCert params cert =
Right
ValidatedPerasCert
{ vpcCert = cert
, vpcCertBoost = perasCfgWeightBoost cfg
, vpcCertBoost = perasWeight params
}

instance ShowProxy blk => ShowProxy (PerasCert blk) where
Expand All @@ -155,31 +128,47 @@ instance Serialise (HeaderHash blk) => Serialise (PerasCert blk) where
pcCertBoostedBlock <- decode
pure $ PerasCert{pcCertRound, pcCertBoostedBlock}

-- | Derive a 'PerasCfg' from a 'BlockConfig'
--
-- TODO: this currently doesn't depend on 'BlockConfig' at all, but likely will
-- depend on it in the future
-- see https://github.com/tweag/cardano-peras/issues/73
makePerasCfg :: Maybe (BlockConfig blk) -> PerasCfg blk
makePerasCfg _ =
PerasCfg
{ perasCfgWeightBoost = boostPerCert
}
-- | Extract the certificate round from a Peras certificate container
class HasPerasCertRound cert where
getPerasCertRound :: cert -> PerasRoundNo

instance HasPerasCertRound (PerasCert blk) where
getPerasCertRound = pcCertRound

instance HasPerasCertRound (ValidatedPerasCert blk) where
getPerasCertRound = getPerasCertRound . vpcCert

instance
HasPerasCertRound cert =>
HasPerasCertRound (WithArrivalTime cert)
where
getPerasCertRound = getPerasCertRound . forgetArrivalTime

-- | Extract the boosted block point from a Peras certificate container
class HasPerasCertBoostedBlock cert blk | cert -> blk where
getPerasCertBoostedBlock :: cert -> Point blk

class StandardHash blk => HasPerasCert cert blk where
getPerasCert :: cert blk -> PerasCert blk
instance HasPerasCertBoostedBlock (PerasCert blk) blk where
getPerasCertBoostedBlock = pcCertBoostedBlock

instance StandardHash blk => HasPerasCert PerasCert blk where
getPerasCert = id
instance HasPerasCertBoostedBlock (ValidatedPerasCert blk) blk where
getPerasCertBoostedBlock = getPerasCertBoostedBlock . vpcCert

instance StandardHash blk => HasPerasCert ValidatedPerasCert blk where
getPerasCert = vpcCert
instance
HasPerasCertBoostedBlock cert blk =>
HasPerasCertBoostedBlock (WithArrivalTime cert) blk
where
getPerasCertBoostedBlock = getPerasCertBoostedBlock . forgetArrivalTime

getPerasCertRound :: HasPerasCert cert blk => cert blk -> PerasRoundNo
getPerasCertRound = pcCertRound . getPerasCert
-- | Extract the certificate boost from a Peras certificate container
class HasPerasCertBoost cert where
getPerasCertBoost :: cert -> PerasWeight

getPerasCertBoostedBlock :: HasPerasCert cert blk => cert blk -> Point blk
getPerasCertBoostedBlock = pcCertBoostedBlock . getPerasCert
instance HasPerasCertBoost (ValidatedPerasCert blk) where
getPerasCertBoost = vpcCertBoost

getPerasCertBoost :: ValidatedPerasCert blk -> PerasWeight
getPerasCertBoost = vpcCertBoost
instance
HasPerasCertBoost cert =>
HasPerasCertBoost (WithArrivalTime cert)
where
getPerasCertBoost = getPerasCertBoost . forgetArrivalTime
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}

module Ouroboros.Consensus.BlockchainTime.WallClock.Types
Expand All @@ -15,6 +17,10 @@ module Ouroboros.Consensus.BlockchainTime.WallClock.Types
-- * Get current time (as 'RelativeTime')
, SystemTime (..)

-- * Attach an arrival time (as 'RelativeTime') to an object
, WithArrivalTime (..)
, addArrivalTime

-- * Slot length
, getSlotLength
, mkSlotLength
Expand All @@ -31,6 +37,7 @@ module Ouroboros.Consensus.BlockchainTime.WallClock.Types

import Cardano.Slotting.Time
import Data.Time.Clock (NominalDiffTime)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks, OnlyCheckWhnfNamed (..))

addRelTime :: NominalDiffTime -> RelativeTime -> RelativeTime
Expand Down Expand Up @@ -60,3 +67,22 @@ data SystemTime m = SystemTime
-- to reach 'SystemStart'. In tests this does nothing.
}
deriving NoThunks via OnlyCheckWhnfNamed "SystemTime" (SystemTime m)

{-------------------------------------------------------------------------------
Attach an arrival time (as RelativeTime) to an object
-------------------------------------------------------------------------------}

-- | WithArrivalTime
data WithArrivalTime a = WithArrivalTime
{ getArrivalTime :: !RelativeTime
-- ^ The time at which the object arrived
, forgetArrivalTime :: !a
-- ^ The object without its arrival time
}
deriving (Show, Eq, Ord, Generic, NoThunks)

-- | Add an arrival time to an object
addArrivalTime :: Monad m => SystemTime m -> a -> m (WithArrivalTime a)
addArrivalTime systemTime a = do
t <- systemTimeCurrent systemTime
return (WithArrivalTime t a)
Loading
Loading