{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Ouroboros.Consensus.HeaderValidation (
revalidateHeader
, validateHeader
, AnnTip (..)
, HasAnnTip (..)
, annTipHash
, annTipPoint
, annTipRealPoint
, castAnnTip
, getAnnTip
, mapAnnTip
, HeaderState (..)
, castHeaderState
, genesisHeaderState
, headerStateBlockNo
, headerStatePoint
, tickHeaderState
, BasicEnvelopeValidation (..)
, HeaderEnvelopeError (..)
, ValidateEnvelope (..)
, castHeaderEnvelopeError
, HeaderError (..)
, castHeaderError
, TipInfoIsEBB (..)
, decodeAnnTipIsEBB
, decodeHeaderState
, defaultDecodeAnnTip
, defaultEncodeAnnTip
, encodeAnnTipIsEBB
, encodeHeaderState
, Ticked (..)
) where
import Cardano.Binary (enforceSize)
import Codec.CBOR.Decoding (Decoder)
import Codec.CBOR.Encoding (Encoding, encodeListLen)
import Codec.Serialise (decode, encode)
import Control.Monad (unless, when)
import Control.Monad.Except (Except, runExcept, throwError,
withExcept)
import Data.Coerce
import Data.Kind (Type)
import qualified Data.Map.Strict as Map
import Data.Proxy
import Data.Void (Void)
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack)
import NoThunks.Class (NoThunks)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Config
import Ouroboros.Consensus.Protocol.Abstract
import Ouroboros.Consensus.Ticked
import Ouroboros.Consensus.Util (whenJust)
import Ouroboros.Consensus.Util.Assert
import qualified Ouroboros.Consensus.Util.CBOR as Util.CBOR
data AnnTip blk = AnnTip {
forall blk. AnnTip blk -> SlotNo
annTipSlotNo :: !SlotNo
, forall blk. AnnTip blk -> BlockNo
annTipBlockNo :: !BlockNo
, forall blk. AnnTip blk -> TipInfo blk
annTipInfo :: !(TipInfo blk)
}
deriving ((forall x. AnnTip blk -> Rep (AnnTip blk) x)
-> (forall x. Rep (AnnTip blk) x -> AnnTip blk)
-> Generic (AnnTip blk)
forall x. Rep (AnnTip blk) x -> AnnTip blk
forall x. AnnTip blk -> Rep (AnnTip blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (AnnTip blk) x -> AnnTip blk
forall blk x. AnnTip blk -> Rep (AnnTip blk) x
$cfrom :: forall blk x. AnnTip blk -> Rep (AnnTip blk) x
from :: forall x. AnnTip blk -> Rep (AnnTip blk) x
$cto :: forall blk x. Rep (AnnTip blk) x -> AnnTip blk
to :: forall x. Rep (AnnTip blk) x -> AnnTip blk
Generic)
deriving instance HasAnnTip blk => Show (AnnTip blk)
deriving instance HasAnnTip blk => Eq (AnnTip blk)
deriving instance HasAnnTip blk => NoThunks (AnnTip blk)
annTipHash :: forall blk. HasAnnTip blk => AnnTip blk -> HeaderHash blk
annTipHash :: forall blk. HasAnnTip blk => AnnTip blk -> HeaderHash blk
annTipHash = Proxy blk -> TipInfo blk -> HeaderHash blk
forall blk (proxy :: * -> *).
HasAnnTip blk =>
proxy blk -> TipInfo blk -> HeaderHash blk
forall (proxy :: * -> *).
proxy blk -> TipInfo blk -> HeaderHash blk
tipInfoHash (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @blk) (TipInfo blk -> HeaderHash blk)
-> (AnnTip blk -> TipInfo blk) -> AnnTip blk -> HeaderHash blk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnTip blk -> TipInfo blk
forall blk. AnnTip blk -> TipInfo blk
annTipInfo
annTipPoint :: forall blk. HasAnnTip blk => AnnTip blk -> Point blk
annTipPoint :: forall blk. HasAnnTip blk => AnnTip blk -> Point blk
annTipPoint annTip :: AnnTip blk
annTip@AnnTip{BlockNo
SlotNo
TipInfo blk
annTipSlotNo :: forall blk. AnnTip blk -> SlotNo
annTipBlockNo :: forall blk. AnnTip blk -> BlockNo
annTipInfo :: forall blk. AnnTip blk -> TipInfo blk
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk
..} = SlotNo -> HeaderHash blk -> Point blk
forall {k} (block :: k). SlotNo -> HeaderHash block -> Point block
BlockPoint SlotNo
annTipSlotNo (AnnTip blk -> HeaderHash blk
forall blk. HasAnnTip blk => AnnTip blk -> HeaderHash blk
annTipHash AnnTip blk
annTip)
annTipRealPoint :: forall blk. HasAnnTip blk => AnnTip blk -> RealPoint blk
annTipRealPoint :: forall blk. HasAnnTip blk => AnnTip blk -> RealPoint blk
annTipRealPoint annTip :: AnnTip blk
annTip@AnnTip{BlockNo
SlotNo
TipInfo blk
annTipSlotNo :: forall blk. AnnTip blk -> SlotNo
annTipBlockNo :: forall blk. AnnTip blk -> BlockNo
annTipInfo :: forall blk. AnnTip blk -> TipInfo blk
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk
..} = SlotNo -> HeaderHash blk -> RealPoint blk
forall blk. SlotNo -> HeaderHash blk -> RealPoint blk
RealPoint SlotNo
annTipSlotNo (AnnTip blk -> HeaderHash blk
forall blk. HasAnnTip blk => AnnTip blk -> HeaderHash blk
annTipHash AnnTip blk
annTip)
castAnnTip :: TipInfo blk ~ TipInfo blk' => AnnTip blk -> AnnTip blk'
castAnnTip :: forall blk blk'.
(TipInfo blk ~ TipInfo blk') =>
AnnTip blk -> AnnTip blk'
castAnnTip AnnTip{BlockNo
SlotNo
TipInfo blk
annTipSlotNo :: forall blk. AnnTip blk -> SlotNo
annTipBlockNo :: forall blk. AnnTip blk -> BlockNo
annTipInfo :: forall blk. AnnTip blk -> TipInfo blk
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk
..} = AnnTip{BlockNo
SlotNo
TipInfo blk
TipInfo blk'
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk'
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk
..}
mapAnnTip :: (TipInfo blk -> TipInfo blk') -> AnnTip blk -> AnnTip blk'
mapAnnTip :: forall blk blk'.
(TipInfo blk -> TipInfo blk') -> AnnTip blk -> AnnTip blk'
mapAnnTip TipInfo blk -> TipInfo blk'
f AnnTip { TipInfo blk
annTipInfo :: forall blk. AnnTip blk -> TipInfo blk
annTipInfo :: TipInfo blk
annTipInfo, BlockNo
SlotNo
annTipSlotNo :: forall blk. AnnTip blk -> SlotNo
annTipBlockNo :: forall blk. AnnTip blk -> BlockNo
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
.. } = AnnTip { annTipInfo :: TipInfo blk'
annTipInfo = TipInfo blk -> TipInfo blk'
f TipInfo blk
annTipInfo, BlockNo
SlotNo
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
.. }
class ( StandardHash blk
, Show (TipInfo blk)
, Eq (TipInfo blk)
, NoThunks (TipInfo blk)
) => HasAnnTip blk where
type TipInfo blk :: Type
type TipInfo blk = HeaderHash blk
getTipInfo :: Header blk -> TipInfo blk
tipInfoHash :: proxy blk -> TipInfo blk -> HeaderHash blk
default tipInfoHash :: (TipInfo blk ~ HeaderHash blk)
=> proxy blk -> TipInfo blk -> HeaderHash blk
tipInfoHash proxy blk
_ = HeaderHash blk -> HeaderHash blk
TipInfo blk -> HeaderHash blk
forall a. a -> a
id
default getTipInfo :: (TipInfo blk ~ HeaderHash blk, HasHeader (Header blk))
=> Header blk -> TipInfo blk
getTipInfo = Header blk -> HeaderHash (Header blk)
Header blk -> TipInfo blk
forall b. HasHeader b => b -> HeaderHash b
blockHash
getAnnTip :: (HasHeader (Header blk), HasAnnTip blk)
=> Header blk -> AnnTip blk
getAnnTip :: forall blk.
(HasHeader (Header blk), HasAnnTip blk) =>
Header blk -> AnnTip blk
getAnnTip Header blk
hdr = AnnTip {
annTipSlotNo :: SlotNo
annTipSlotNo = Header blk -> SlotNo
forall b. HasHeader b => b -> SlotNo
blockSlot Header blk
hdr
, annTipBlockNo :: BlockNo
annTipBlockNo = Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr
, annTipInfo :: TipInfo blk
annTipInfo = Header blk -> TipInfo blk
forall blk. HasAnnTip blk => Header blk -> TipInfo blk
getTipInfo Header blk
hdr
}
data blk = {
:: !(WithOrigin (AnnTip blk))
, :: !(ChainDepState (BlockProtocol blk))
}
deriving ((forall x. HeaderState blk -> Rep (HeaderState blk) x)
-> (forall x. Rep (HeaderState blk) x -> HeaderState blk)
-> Generic (HeaderState blk)
forall x. Rep (HeaderState blk) x -> HeaderState blk
forall x. HeaderState blk -> Rep (HeaderState blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (HeaderState blk) x -> HeaderState blk
forall blk x. HeaderState blk -> Rep (HeaderState blk) x
$cfrom :: forall blk x. HeaderState blk -> Rep (HeaderState blk) x
from :: forall x. HeaderState blk -> Rep (HeaderState blk) x
$cto :: forall blk x. Rep (HeaderState blk) x -> HeaderState blk
to :: forall x. Rep (HeaderState blk) x -> HeaderState blk
Generic)
castHeaderState ::
( Coercible (ChainDepState (BlockProtocol blk ))
(ChainDepState (BlockProtocol blk'))
, TipInfo blk ~ TipInfo blk'
)
=> HeaderState blk -> HeaderState blk'
HeaderState {WithOrigin (AnnTip blk)
ChainDepState (BlockProtocol blk)
headerStateTip :: forall blk. HeaderState blk -> WithOrigin (AnnTip blk)
headerStateChainDep :: forall blk. HeaderState blk -> ChainDepState (BlockProtocol blk)
headerStateTip :: WithOrigin (AnnTip blk)
headerStateChainDep :: ChainDepState (BlockProtocol blk)
..} = HeaderState {
headerStateTip :: WithOrigin (AnnTip blk')
headerStateTip = AnnTip blk -> AnnTip blk'
forall blk blk'.
(TipInfo blk ~ TipInfo blk') =>
AnnTip blk -> AnnTip blk'
castAnnTip (AnnTip blk -> AnnTip blk')
-> WithOrigin (AnnTip blk) -> WithOrigin (AnnTip blk')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WithOrigin (AnnTip blk)
headerStateTip
, headerStateChainDep :: ChainDepState (BlockProtocol blk')
headerStateChainDep = ChainDepState (BlockProtocol blk)
-> ChainDepState (BlockProtocol blk')
forall a b. Coercible a b => a -> b
coerce ChainDepState (BlockProtocol blk)
headerStateChainDep
}
deriving instance (BlockSupportsProtocol blk, HasAnnTip blk)
=> Eq (HeaderState blk)
deriving instance (BlockSupportsProtocol blk, HasAnnTip blk)
=> Show (HeaderState blk)
deriving instance (BlockSupportsProtocol blk, HasAnnTip blk)
=> NoThunks (HeaderState blk)
data instance Ticked (HeaderState blk) = {
:: WithOrigin (AnnTip blk)
, :: Ticked (ChainDepState (BlockProtocol blk))
}
tickHeaderState :: ConsensusProtocol (BlockProtocol blk)
=> ConsensusConfig (BlockProtocol blk)
-> LedgerView (BlockProtocol blk)
-> SlotNo
-> HeaderState blk -> Ticked (HeaderState blk)
ConsensusConfig (BlockProtocol blk)
cfg LedgerView (BlockProtocol blk)
ledgerView SlotNo
slot HeaderState {WithOrigin (AnnTip blk)
ChainDepState (BlockProtocol blk)
headerStateTip :: forall blk. HeaderState blk -> WithOrigin (AnnTip blk)
headerStateChainDep :: forall blk. HeaderState blk -> ChainDepState (BlockProtocol blk)
headerStateTip :: WithOrigin (AnnTip blk)
headerStateChainDep :: ChainDepState (BlockProtocol blk)
..} = TickedHeaderState {
untickedHeaderStateTip :: WithOrigin (AnnTip blk)
untickedHeaderStateTip = WithOrigin (AnnTip blk)
headerStateTip
, tickedHeaderStateChainDep :: Ticked (ChainDepState (BlockProtocol blk))
tickedHeaderStateChainDep =
ConsensusConfig (BlockProtocol blk)
-> LedgerView (BlockProtocol blk)
-> SlotNo
-> ChainDepState (BlockProtocol blk)
-> Ticked (ChainDepState (BlockProtocol blk))
forall p.
ConsensusProtocol p =>
ConsensusConfig p
-> LedgerView p
-> SlotNo
-> ChainDepState p
-> Ticked (ChainDepState p)
tickChainDepState ConsensusConfig (BlockProtocol blk)
cfg LedgerView (BlockProtocol blk)
ledgerView SlotNo
slot ChainDepState (BlockProtocol blk)
headerStateChainDep
}
genesisHeaderState :: ChainDepState (BlockProtocol blk) -> HeaderState blk
= WithOrigin (AnnTip blk)
-> ChainDepState (BlockProtocol blk) -> HeaderState blk
forall blk.
WithOrigin (AnnTip blk)
-> ChainDepState (BlockProtocol blk) -> HeaderState blk
HeaderState WithOrigin (AnnTip blk)
forall t. WithOrigin t
Origin
headerStateBlockNo :: HeaderState blk -> WithOrigin BlockNo
= (AnnTip blk -> BlockNo)
-> WithOrigin (AnnTip blk) -> WithOrigin BlockNo
forall a b. (a -> b) -> WithOrigin a -> WithOrigin b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AnnTip blk -> BlockNo
forall blk. AnnTip blk -> BlockNo
annTipBlockNo (WithOrigin (AnnTip blk) -> WithOrigin BlockNo)
-> (HeaderState blk -> WithOrigin (AnnTip blk))
-> HeaderState blk
-> WithOrigin BlockNo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HeaderState blk -> WithOrigin (AnnTip blk)
forall blk. HeaderState blk -> WithOrigin (AnnTip blk)
headerStateTip
headerStatePoint :: HasAnnTip blk => HeaderState blk -> Point blk
=
WithOrigin (RealPoint blk) -> Point blk
forall blk. WithOrigin (RealPoint blk) -> Point blk
withOriginRealPointToPoint
(WithOrigin (RealPoint blk) -> Point blk)
-> (HeaderState blk -> WithOrigin (RealPoint blk))
-> HeaderState blk
-> Point blk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnnTip blk -> RealPoint blk)
-> WithOrigin (AnnTip blk) -> WithOrigin (RealPoint blk)
forall a b. (a -> b) -> WithOrigin a -> WithOrigin b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AnnTip blk -> RealPoint blk
forall blk. HasAnnTip blk => AnnTip blk -> RealPoint blk
annTipRealPoint
(WithOrigin (AnnTip blk) -> WithOrigin (RealPoint blk))
-> (HeaderState blk -> WithOrigin (AnnTip blk))
-> HeaderState blk
-> WithOrigin (RealPoint blk)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HeaderState blk -> WithOrigin (AnnTip blk)
forall blk. HeaderState blk -> WithOrigin (AnnTip blk)
headerStateTip
data blk =
UnexpectedBlockNo !BlockNo !BlockNo
| UnexpectedSlotNo !SlotNo !SlotNo
| UnexpectedPrevHash !(WithOrigin (HeaderHash blk)) !(ChainHash blk)
| CheckpointMismatch !BlockNo !(HeaderHash blk) !(HeaderHash blk)
| !(OtherHeaderEnvelopeError blk)
deriving ((forall x.
HeaderEnvelopeError blk -> Rep (HeaderEnvelopeError blk) x)
-> (forall x.
Rep (HeaderEnvelopeError blk) x -> HeaderEnvelopeError blk)
-> Generic (HeaderEnvelopeError blk)
forall x.
Rep (HeaderEnvelopeError blk) x -> HeaderEnvelopeError blk
forall x.
HeaderEnvelopeError blk -> Rep (HeaderEnvelopeError blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (HeaderEnvelopeError blk) x -> HeaderEnvelopeError blk
forall blk x.
HeaderEnvelopeError blk -> Rep (HeaderEnvelopeError blk) x
$cfrom :: forall blk x.
HeaderEnvelopeError blk -> Rep (HeaderEnvelopeError blk) x
from :: forall x.
HeaderEnvelopeError blk -> Rep (HeaderEnvelopeError blk) x
$cto :: forall blk x.
Rep (HeaderEnvelopeError blk) x -> HeaderEnvelopeError blk
to :: forall x.
Rep (HeaderEnvelopeError blk) x -> HeaderEnvelopeError blk
Generic)
deriving instance (ValidateEnvelope blk) => Eq (HeaderEnvelopeError blk)
deriving instance (ValidateEnvelope blk) => Show (HeaderEnvelopeError blk)
deriving instance (ValidateEnvelope blk)
=> NoThunks (HeaderEnvelopeError blk)
castHeaderEnvelopeError :: ( HeaderHash blk ~ HeaderHash blk'
, OtherHeaderEnvelopeError blk ~ OtherHeaderEnvelopeError blk'
)
=> HeaderEnvelopeError blk -> HeaderEnvelopeError blk'
= \case
OtherHeaderEnvelopeError OtherHeaderEnvelopeError blk
err -> OtherHeaderEnvelopeError blk' -> HeaderEnvelopeError blk'
forall blk. OtherHeaderEnvelopeError blk -> HeaderEnvelopeError blk
OtherHeaderEnvelopeError OtherHeaderEnvelopeError blk
OtherHeaderEnvelopeError blk'
err
UnexpectedBlockNo BlockNo
expected BlockNo
actual -> BlockNo -> BlockNo -> HeaderEnvelopeError blk'
forall blk. BlockNo -> BlockNo -> HeaderEnvelopeError blk
UnexpectedBlockNo BlockNo
expected BlockNo
actual
UnexpectedSlotNo SlotNo
expected SlotNo
actual -> SlotNo -> SlotNo -> HeaderEnvelopeError blk'
forall blk. SlotNo -> SlotNo -> HeaderEnvelopeError blk
UnexpectedSlotNo SlotNo
expected SlotNo
actual
UnexpectedPrevHash WithOrigin (HeaderHash blk)
oldTip ChainHash blk
prevHash -> WithOrigin (HeaderHash blk')
-> ChainHash blk' -> HeaderEnvelopeError blk'
forall blk.
WithOrigin (HeaderHash blk)
-> ChainHash blk -> HeaderEnvelopeError blk
UnexpectedPrevHash WithOrigin (HeaderHash blk)
WithOrigin (HeaderHash blk')
oldTip (ChainHash blk -> ChainHash blk'
forall {k1} {k2} (b :: k1) (b' :: k2).
Coercible (HeaderHash b) (HeaderHash b') =>
ChainHash b -> ChainHash b'
castHash ChainHash blk
prevHash)
CheckpointMismatch BlockNo
bNo HeaderHash blk
expected HeaderHash blk
actual -> BlockNo
-> HeaderHash blk' -> HeaderHash blk' -> HeaderEnvelopeError blk'
forall blk.
BlockNo
-> HeaderHash blk -> HeaderHash blk -> HeaderEnvelopeError blk
CheckpointMismatch BlockNo
bNo HeaderHash blk
HeaderHash blk'
expected HeaderHash blk
HeaderHash blk'
actual
class ( HasHeader (Header blk)
, HasAnnTip blk
) => BasicEnvelopeValidation blk where
expectedFirstBlockNo :: proxy blk -> BlockNo
expectedFirstBlockNo proxy blk
_ = Word64 -> BlockNo
BlockNo Word64
0
expectedNextBlockNo :: proxy blk
-> TipInfo blk
-> TipInfo blk
-> BlockNo -> BlockNo
expectedNextBlockNo proxy blk
_ TipInfo blk
_ TipInfo blk
_ = BlockNo -> BlockNo
forall a. Enum a => a -> a
succ
minimumPossibleSlotNo :: Proxy blk -> SlotNo
minimumPossibleSlotNo Proxy blk
_ = Word64 -> SlotNo
SlotNo Word64
0
minimumNextSlotNo :: proxy blk
-> TipInfo blk
-> TipInfo blk
-> SlotNo -> SlotNo
minimumNextSlotNo proxy blk
_ TipInfo blk
_ TipInfo blk
_ = SlotNo -> SlotNo
forall a. Enum a => a -> a
succ
class ( BasicEnvelopeValidation blk
, GetPrevHash blk
, Eq (OtherHeaderEnvelopeError blk)
, Show (OtherHeaderEnvelopeError blk)
, NoThunks (OtherHeaderEnvelopeError blk)
) => ValidateEnvelope blk where
type blk :: Type
type blk = Void
additionalEnvelopeChecks :: TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> Header blk
-> Except (OtherHeaderEnvelopeError blk) ()
additionalEnvelopeChecks TopLevelConfig blk
_ LedgerView (BlockProtocol blk)
_ Header blk
_ = () -> Except (OtherHeaderEnvelopeError blk) ()
forall a. a -> ExceptT (OtherHeaderEnvelopeError blk) Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
validateEnvelope :: forall blk. (ValidateEnvelope blk)
=> TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> WithOrigin (AnnTip blk)
-> Header blk
-> Except (HeaderEnvelopeError blk) ()
validateEnvelope :: forall blk.
ValidateEnvelope blk =>
TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> WithOrigin (AnnTip blk)
-> Header blk
-> Except (HeaderEnvelopeError blk) ()
validateEnvelope TopLevelConfig blk
cfg LedgerView (BlockProtocol blk)
ledgerView WithOrigin (AnnTip blk)
oldTip Header blk
hdr = do
Bool
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (BlockNo
actualBlockNo BlockNo -> BlockNo -> Bool
forall a. Eq a => a -> a -> Bool
== BlockNo
expectedBlockNo) (Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ())
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall a b. (a -> b) -> a -> b
$
HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ()
forall a.
HeaderEnvelopeError blk
-> ExceptT (HeaderEnvelopeError blk) Identity a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ())
-> HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ()
forall a b. (a -> b) -> a -> b
$ BlockNo -> BlockNo -> HeaderEnvelopeError blk
forall blk. BlockNo -> BlockNo -> HeaderEnvelopeError blk
UnexpectedBlockNo BlockNo
expectedBlockNo BlockNo
actualBlockNo
Bool
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (SlotNo
actualSlotNo SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
>= SlotNo
expectedSlotNo) (Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ())
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall a b. (a -> b) -> a -> b
$
HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ()
forall a.
HeaderEnvelopeError blk
-> ExceptT (HeaderEnvelopeError blk) Identity a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ())
-> HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ()
forall a b. (a -> b) -> a -> b
$ SlotNo -> SlotNo -> HeaderEnvelopeError blk
forall blk. SlotNo -> SlotNo -> HeaderEnvelopeError blk
UnexpectedSlotNo SlotNo
expectedSlotNo SlotNo
actualSlotNo
Bool
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (WithOrigin (HeaderHash blk) -> ChainHash blk -> Bool
checkPrevHash' (AnnTip blk -> HeaderHash blk
forall blk. HasAnnTip blk => AnnTip blk -> HeaderHash blk
annTipHash (AnnTip blk -> HeaderHash blk)
-> WithOrigin (AnnTip blk) -> WithOrigin (HeaderHash blk)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WithOrigin (AnnTip blk)
oldTip) ChainHash blk
actualPrevHash) (Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ())
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall a b. (a -> b) -> a -> b
$
HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ()
forall a.
HeaderEnvelopeError blk
-> ExceptT (HeaderEnvelopeError blk) Identity a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ())
-> HeaderEnvelopeError blk -> Except (HeaderEnvelopeError blk) ()
forall a b. (a -> b) -> a -> b
$ WithOrigin (HeaderHash blk)
-> ChainHash blk -> HeaderEnvelopeError blk
forall blk.
WithOrigin (HeaderHash blk)
-> ChainHash blk -> HeaderEnvelopeError blk
UnexpectedPrevHash (AnnTip blk -> HeaderHash blk
forall blk. HasAnnTip blk => AnnTip blk -> HeaderHash blk
annTipHash (AnnTip blk -> HeaderHash blk)
-> WithOrigin (AnnTip blk) -> WithOrigin (HeaderHash blk)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WithOrigin (AnnTip blk)
oldTip) ChainHash blk
actualPrevHash
CheckpointsMap blk
-> Header blk -> Except (HeaderEnvelopeError blk) ()
forall blk.
HasHeader (Header blk) =>
CheckpointsMap blk
-> Header blk -> Except (HeaderEnvelopeError blk) ()
validateIfCheckpoint (TopLevelConfig blk -> CheckpointsMap blk
forall blk. TopLevelConfig blk -> CheckpointsMap blk
topLevelConfigCheckpoints TopLevelConfig blk
cfg) Header blk
hdr
(OtherHeaderEnvelopeError blk -> HeaderEnvelopeError blk)
-> Except (OtherHeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall e e' a. (e -> e') -> Except e a -> Except e' a
withExcept OtherHeaderEnvelopeError blk -> HeaderEnvelopeError blk
forall blk. OtherHeaderEnvelopeError blk -> HeaderEnvelopeError blk
OtherHeaderEnvelopeError (Except (OtherHeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ())
-> Except (OtherHeaderEnvelopeError blk) ()
-> Except (HeaderEnvelopeError blk) ()
forall a b. (a -> b) -> a -> b
$
TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> Header blk
-> Except (OtherHeaderEnvelopeError blk) ()
forall blk.
ValidateEnvelope blk =>
TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> Header blk
-> Except (OtherHeaderEnvelopeError blk) ()
additionalEnvelopeChecks TopLevelConfig blk
cfg LedgerView (BlockProtocol blk)
ledgerView Header blk
hdr
where
checkPrevHash' :: WithOrigin (HeaderHash blk)
-> ChainHash blk
-> Bool
checkPrevHash' :: WithOrigin (HeaderHash blk) -> ChainHash blk -> Bool
checkPrevHash' WithOrigin (HeaderHash blk)
Origin ChainHash blk
GenesisHash = Bool
True
checkPrevHash' (NotOrigin HeaderHash blk
h) (BlockHash HeaderHash blk
h') = HeaderHash blk
h HeaderHash blk -> HeaderHash blk -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderHash blk
h'
checkPrevHash' WithOrigin (HeaderHash blk)
_ ChainHash blk
_ = Bool
False
actualSlotNo :: SlotNo
actualBlockNo :: BlockNo
actualPrevHash :: ChainHash blk
actualSlotNo :: SlotNo
actualSlotNo = Header blk -> SlotNo
forall b. HasHeader b => b -> SlotNo
blockSlot Header blk
hdr
actualBlockNo :: BlockNo
actualBlockNo = Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr
actualPrevHash :: ChainHash blk
actualPrevHash = Header blk -> ChainHash blk
forall blk. GetPrevHash blk => Header blk -> ChainHash blk
headerPrevHash Header blk
hdr
expectedSlotNo :: SlotNo
expectedSlotNo :: SlotNo
expectedSlotNo =
case WithOrigin (AnnTip blk)
oldTip of
WithOrigin (AnnTip blk)
Origin -> Proxy blk -> SlotNo
forall blk. BasicEnvelopeValidation blk => Proxy blk -> SlotNo
minimumPossibleSlotNo Proxy blk
p
NotOrigin AnnTip blk
tip -> Proxy blk -> TipInfo blk -> TipInfo blk -> SlotNo -> SlotNo
forall blk (proxy :: * -> *).
BasicEnvelopeValidation blk =>
proxy blk -> TipInfo blk -> TipInfo blk -> SlotNo -> SlotNo
forall (proxy :: * -> *).
proxy blk -> TipInfo blk -> TipInfo blk -> SlotNo -> SlotNo
minimumNextSlotNo Proxy blk
p (AnnTip blk -> TipInfo blk
forall blk. AnnTip blk -> TipInfo blk
annTipInfo AnnTip blk
tip)
(Header blk -> TipInfo blk
forall blk. HasAnnTip blk => Header blk -> TipInfo blk
getTipInfo Header blk
hdr)
(AnnTip blk -> SlotNo
forall blk. AnnTip blk -> SlotNo
annTipSlotNo AnnTip blk
tip)
expectedBlockNo :: BlockNo
expectedBlockNo :: BlockNo
expectedBlockNo =
case WithOrigin (AnnTip blk)
oldTip of
WithOrigin (AnnTip blk)
Origin -> Proxy blk -> BlockNo
forall blk (proxy :: * -> *).
BasicEnvelopeValidation blk =>
proxy blk -> BlockNo
forall (proxy :: * -> *). proxy blk -> BlockNo
expectedFirstBlockNo Proxy blk
p
NotOrigin AnnTip blk
tip -> Proxy blk -> TipInfo blk -> TipInfo blk -> BlockNo -> BlockNo
forall blk (proxy :: * -> *).
BasicEnvelopeValidation blk =>
proxy blk -> TipInfo blk -> TipInfo blk -> BlockNo -> BlockNo
forall (proxy :: * -> *).
proxy blk -> TipInfo blk -> TipInfo blk -> BlockNo -> BlockNo
expectedNextBlockNo Proxy blk
p (AnnTip blk -> TipInfo blk
forall blk. AnnTip blk -> TipInfo blk
annTipInfo AnnTip blk
tip)
(Header blk -> TipInfo blk
forall blk. HasAnnTip blk => Header blk -> TipInfo blk
getTipInfo Header blk
hdr)
(AnnTip blk -> BlockNo
forall blk. AnnTip blk -> BlockNo
annTipBlockNo AnnTip blk
tip)
p :: Proxy blk
p = forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @blk
validateIfCheckpoint ::
HasHeader (Header blk)
=> CheckpointsMap blk
-> Header blk
-> Except (HeaderEnvelopeError blk) ()
validateIfCheckpoint :: forall blk.
HasHeader (Header blk) =>
CheckpointsMap blk
-> Header blk -> Except (HeaderEnvelopeError blk) ()
validateIfCheckpoint CheckpointsMap blk
checkpointsMap Header blk
hdr =
Maybe (HeaderHash blk)
-> (HeaderHash blk
-> ExceptT (HeaderEnvelopeError blk) Identity ())
-> ExceptT (HeaderEnvelopeError blk) Identity ()
forall (f :: * -> *) a.
Applicative f =>
Maybe a -> (a -> f ()) -> f ()
whenJust (BlockNo -> Map BlockNo (HeaderHash blk) -> Maybe (HeaderHash blk)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr) (Map BlockNo (HeaderHash blk) -> Maybe (HeaderHash blk))
-> Map BlockNo (HeaderHash blk) -> Maybe (HeaderHash blk)
forall a b. (a -> b) -> a -> b
$ CheckpointsMap blk -> Map BlockNo (HeaderHash blk)
forall blk. CheckpointsMap blk -> Map BlockNo (HeaderHash blk)
unCheckpointsMap CheckpointsMap blk
checkpointsMap) ((HeaderHash blk -> ExceptT (HeaderEnvelopeError blk) Identity ())
-> ExceptT (HeaderEnvelopeError blk) Identity ())
-> (HeaderHash blk
-> ExceptT (HeaderEnvelopeError blk) Identity ())
-> ExceptT (HeaderEnvelopeError blk) Identity ()
forall a b. (a -> b) -> a -> b
$
\HeaderHash blk
checkpoint -> Bool
-> ExceptT (HeaderEnvelopeError blk) Identity ()
-> ExceptT (HeaderEnvelopeError blk) Identity ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Header blk -> HeaderHash blk
forall blk. HasHeader (Header blk) => Header blk -> HeaderHash blk
headerHash Header blk
hdr HeaderHash blk -> HeaderHash blk -> Bool
forall a. Eq a => a -> a -> Bool
/= HeaderHash blk
checkpoint) (ExceptT (HeaderEnvelopeError blk) Identity ()
-> ExceptT (HeaderEnvelopeError blk) Identity ())
-> ExceptT (HeaderEnvelopeError blk) Identity ()
-> ExceptT (HeaderEnvelopeError blk) Identity ()
forall a b. (a -> b) -> a -> b
$
HeaderEnvelopeError blk
-> ExceptT (HeaderEnvelopeError blk) Identity ()
forall a.
HeaderEnvelopeError blk
-> ExceptT (HeaderEnvelopeError blk) Identity a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (HeaderEnvelopeError blk
-> ExceptT (HeaderEnvelopeError blk) Identity ())
-> HeaderEnvelopeError blk
-> ExceptT (HeaderEnvelopeError blk) Identity ()
forall a b. (a -> b) -> a -> b
$ BlockNo
-> HeaderHash blk -> HeaderHash blk -> HeaderEnvelopeError blk
forall blk.
BlockNo
-> HeaderHash blk -> HeaderHash blk -> HeaderEnvelopeError blk
CheckpointMismatch (Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr) HeaderHash blk
checkpoint (Header blk -> HeaderHash blk
forall blk. HasHeader (Header blk) => Header blk -> HeaderHash blk
headerHash Header blk
hdr)
data blk =
!(ValidationErr (BlockProtocol blk))
| !(HeaderEnvelopeError blk)
deriving ((forall x. HeaderError blk -> Rep (HeaderError blk) x)
-> (forall x. Rep (HeaderError blk) x -> HeaderError blk)
-> Generic (HeaderError blk)
forall x. Rep (HeaderError blk) x -> HeaderError blk
forall x. HeaderError blk -> Rep (HeaderError blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (HeaderError blk) x -> HeaderError blk
forall blk x. HeaderError blk -> Rep (HeaderError blk) x
$cfrom :: forall blk x. HeaderError blk -> Rep (HeaderError blk) x
from :: forall x. HeaderError blk -> Rep (HeaderError blk) x
$cto :: forall blk x. Rep (HeaderError blk) x -> HeaderError blk
to :: forall x. Rep (HeaderError blk) x -> HeaderError blk
Generic)
deriving instance (BlockSupportsProtocol blk, ValidateEnvelope blk)
=> Eq (HeaderError blk)
deriving instance (BlockSupportsProtocol blk, ValidateEnvelope blk)
=> Show (HeaderError blk)
deriving instance (BlockSupportsProtocol blk, ValidateEnvelope blk)
=> NoThunks (HeaderError blk)
castHeaderError :: ( ValidationErr (BlockProtocol blk )
~ ValidationErr (BlockProtocol blk')
, HeaderHash blk
~ HeaderHash blk'
, OtherHeaderEnvelopeError blk
~ OtherHeaderEnvelopeError blk'
)
=> HeaderError blk -> HeaderError blk'
(HeaderProtocolError ValidationErr (BlockProtocol blk)
e) = ValidationErr (BlockProtocol blk') -> HeaderError blk'
forall blk. ValidationErr (BlockProtocol blk) -> HeaderError blk
HeaderProtocolError ValidationErr (BlockProtocol blk)
ValidationErr (BlockProtocol blk')
e
castHeaderError (HeaderEnvelopeError HeaderEnvelopeError blk
e) = HeaderEnvelopeError blk' -> HeaderError blk'
forall blk. HeaderEnvelopeError blk -> HeaderError blk
HeaderEnvelopeError (HeaderEnvelopeError blk' -> HeaderError blk')
-> HeaderEnvelopeError blk' -> HeaderError blk'
forall a b. (a -> b) -> a -> b
$
HeaderEnvelopeError blk -> HeaderEnvelopeError blk'
forall blk blk'.
(HeaderHash blk ~ HeaderHash blk',
OtherHeaderEnvelopeError blk ~ OtherHeaderEnvelopeError blk') =>
HeaderEnvelopeError blk -> HeaderEnvelopeError blk'
castHeaderEnvelopeError HeaderEnvelopeError blk
e
validateHeader :: (BlockSupportsProtocol blk, ValidateEnvelope blk)
=> TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> Header blk
-> Ticked (HeaderState blk)
-> Except (HeaderError blk) (HeaderState blk)
TopLevelConfig blk
cfg LedgerView (BlockProtocol blk)
ledgerView Header blk
hdr Ticked (HeaderState blk)
st = do
(HeaderEnvelopeError blk -> HeaderError blk)
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderError blk) ()
forall e e' a. (e -> e') -> Except e a -> Except e' a
withExcept HeaderEnvelopeError blk -> HeaderError blk
forall blk. HeaderEnvelopeError blk -> HeaderError blk
HeaderEnvelopeError (Except (HeaderEnvelopeError blk) ()
-> Except (HeaderError blk) ())
-> Except (HeaderEnvelopeError blk) ()
-> Except (HeaderError blk) ()
forall a b. (a -> b) -> a -> b
$
TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> WithOrigin (AnnTip blk)
-> Header blk
-> Except (HeaderEnvelopeError blk) ()
forall blk.
ValidateEnvelope blk =>
TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> WithOrigin (AnnTip blk)
-> Header blk
-> Except (HeaderEnvelopeError blk) ()
validateEnvelope
TopLevelConfig blk
cfg
LedgerView (BlockProtocol blk)
ledgerView
(Ticked (HeaderState blk) -> WithOrigin (AnnTip blk)
forall blk. Ticked (HeaderState blk) -> WithOrigin (AnnTip blk)
untickedHeaderStateTip Ticked (HeaderState blk)
st)
Header blk
hdr
ChainDepState (BlockProtocol blk)
chainDepState' <- (ValidationErr (BlockProtocol blk) -> HeaderError blk)
-> Except
(ValidationErr (BlockProtocol blk))
(ChainDepState (BlockProtocol blk))
-> Except (HeaderError blk) (ChainDepState (BlockProtocol blk))
forall e e' a. (e -> e') -> Except e a -> Except e' a
withExcept ValidationErr (BlockProtocol blk) -> HeaderError blk
forall blk. ValidationErr (BlockProtocol blk) -> HeaderError blk
HeaderProtocolError (Except
(ValidationErr (BlockProtocol blk))
(ChainDepState (BlockProtocol blk))
-> Except (HeaderError blk) (ChainDepState (BlockProtocol blk)))
-> Except
(ValidationErr (BlockProtocol blk))
(ChainDepState (BlockProtocol blk))
-> Except (HeaderError blk) (ChainDepState (BlockProtocol blk))
forall a b. (a -> b) -> a -> b
$
ConsensusConfig (BlockProtocol blk)
-> ValidateView (BlockProtocol blk)
-> SlotNo
-> Ticked (ChainDepState (BlockProtocol blk))
-> Except
(ValidationErr (BlockProtocol blk))
(ChainDepState (BlockProtocol blk))
forall p.
(ConsensusProtocol p, HasCallStack) =>
ConsensusConfig p
-> ValidateView p
-> SlotNo
-> Ticked (ChainDepState p)
-> Except (ValidationErr p) (ChainDepState p)
updateChainDepState
(TopLevelConfig blk -> ConsensusConfig (BlockProtocol blk)
forall blk.
TopLevelConfig blk -> ConsensusConfig (BlockProtocol blk)
configConsensus TopLevelConfig blk
cfg)
(BlockConfig blk -> Header blk -> ValidateView (BlockProtocol blk)
forall blk.
BlockSupportsProtocol blk =>
BlockConfig blk -> Header blk -> ValidateView (BlockProtocol blk)
validateView (TopLevelConfig blk -> BlockConfig blk
forall blk. TopLevelConfig blk -> BlockConfig blk
configBlock TopLevelConfig blk
cfg) Header blk
hdr)
(Header blk -> SlotNo
forall b. HasHeader b => b -> SlotNo
blockSlot Header blk
hdr)
(Ticked (HeaderState blk)
-> Ticked (ChainDepState (BlockProtocol blk))
forall blk.
Ticked (HeaderState blk)
-> Ticked (ChainDepState (BlockProtocol blk))
tickedHeaderStateChainDep Ticked (HeaderState blk)
st)
HeaderState blk -> Except (HeaderError blk) (HeaderState blk)
forall a. a -> ExceptT (HeaderError blk) Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (HeaderState blk -> Except (HeaderError blk) (HeaderState blk))
-> HeaderState blk -> Except (HeaderError blk) (HeaderState blk)
forall a b. (a -> b) -> a -> b
$ WithOrigin (AnnTip blk)
-> ChainDepState (BlockProtocol blk) -> HeaderState blk
forall blk.
WithOrigin (AnnTip blk)
-> ChainDepState (BlockProtocol blk) -> HeaderState blk
HeaderState (AnnTip blk -> WithOrigin (AnnTip blk)
forall t. t -> WithOrigin t
NotOrigin (Header blk -> AnnTip blk
forall blk.
(HasHeader (Header blk), HasAnnTip blk) =>
Header blk -> AnnTip blk
getAnnTip Header blk
hdr)) ChainDepState (BlockProtocol blk)
chainDepState'
revalidateHeader ::
forall blk. (BlockSupportsProtocol blk, ValidateEnvelope blk, HasCallStack)
=> TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> Header blk
-> Ticked (HeaderState blk)
-> HeaderState blk
TopLevelConfig blk
cfg LedgerView (BlockProtocol blk)
ledgerView Header blk
hdr Ticked (HeaderState blk)
st =
Either String () -> HeaderState blk -> HeaderState blk
forall a. HasCallStack => Either String () -> a -> a
assertWithMsg Either String ()
envelopeCheck (HeaderState blk -> HeaderState blk)
-> HeaderState blk -> HeaderState blk
forall a b. (a -> b) -> a -> b
$
WithOrigin (AnnTip blk)
-> ChainDepState (BlockProtocol blk) -> HeaderState blk
forall blk.
WithOrigin (AnnTip blk)
-> ChainDepState (BlockProtocol blk) -> HeaderState blk
HeaderState
(AnnTip blk -> WithOrigin (AnnTip blk)
forall t. t -> WithOrigin t
NotOrigin (Header blk -> AnnTip blk
forall blk.
(HasHeader (Header blk), HasAnnTip blk) =>
Header blk -> AnnTip blk
getAnnTip Header blk
hdr))
ChainDepState (BlockProtocol blk)
chainDepState'
where
chainDepState' :: ChainDepState (BlockProtocol blk)
chainDepState' :: ChainDepState (BlockProtocol blk)
chainDepState' =
ConsensusConfig (BlockProtocol blk)
-> ValidateView (BlockProtocol blk)
-> SlotNo
-> Ticked (ChainDepState (BlockProtocol blk))
-> ChainDepState (BlockProtocol blk)
forall p.
(ConsensusProtocol p, HasCallStack) =>
ConsensusConfig p
-> ValidateView p
-> SlotNo
-> Ticked (ChainDepState p)
-> ChainDepState p
reupdateChainDepState
(TopLevelConfig blk -> ConsensusConfig (BlockProtocol blk)
forall blk.
TopLevelConfig blk -> ConsensusConfig (BlockProtocol blk)
configConsensus TopLevelConfig blk
cfg)
(BlockConfig blk -> Header blk -> ValidateView (BlockProtocol blk)
forall blk.
BlockSupportsProtocol blk =>
BlockConfig blk -> Header blk -> ValidateView (BlockProtocol blk)
validateView (TopLevelConfig blk -> BlockConfig blk
forall blk. TopLevelConfig blk -> BlockConfig blk
configBlock TopLevelConfig blk
cfg) Header blk
hdr)
(Header blk -> SlotNo
forall b. HasHeader b => b -> SlotNo
blockSlot Header blk
hdr)
(Ticked (HeaderState blk)
-> Ticked (ChainDepState (BlockProtocol blk))
forall blk.
Ticked (HeaderState blk)
-> Ticked (ChainDepState (BlockProtocol blk))
tickedHeaderStateChainDep Ticked (HeaderState blk)
st)
envelopeCheck :: Either String ()
envelopeCheck :: Either String ()
envelopeCheck = Except String () -> Either String ()
forall e a. Except e a -> Either e a
runExcept (Except String () -> Either String ())
-> Except String () -> Either String ()
forall a b. (a -> b) -> a -> b
$ (HeaderEnvelopeError blk -> String)
-> Except (HeaderEnvelopeError blk) () -> Except String ()
forall e e' a. (e -> e') -> Except e a -> Except e' a
withExcept HeaderEnvelopeError blk -> String
forall a. Show a => a -> String
show (Except (HeaderEnvelopeError blk) () -> Except String ())
-> Except (HeaderEnvelopeError blk) () -> Except String ()
forall a b. (a -> b) -> a -> b
$
TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> WithOrigin (AnnTip blk)
-> Header blk
-> Except (HeaderEnvelopeError blk) ()
forall blk.
ValidateEnvelope blk =>
TopLevelConfig blk
-> LedgerView (BlockProtocol blk)
-> WithOrigin (AnnTip blk)
-> Header blk
-> Except (HeaderEnvelopeError blk) ()
validateEnvelope
TopLevelConfig blk
cfg
LedgerView (BlockProtocol blk)
ledgerView
(Ticked (HeaderState blk) -> WithOrigin (AnnTip blk)
forall blk. Ticked (HeaderState blk) -> WithOrigin (AnnTip blk)
untickedHeaderStateTip Ticked (HeaderState blk)
st)
Header blk
hdr
data TipInfoIsEBB blk = TipInfoIsEBB !(HeaderHash blk) !IsEBB
deriving ((forall x. TipInfoIsEBB blk -> Rep (TipInfoIsEBB blk) x)
-> (forall x. Rep (TipInfoIsEBB blk) x -> TipInfoIsEBB blk)
-> Generic (TipInfoIsEBB blk)
forall x. Rep (TipInfoIsEBB blk) x -> TipInfoIsEBB blk
forall x. TipInfoIsEBB blk -> Rep (TipInfoIsEBB blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (TipInfoIsEBB blk) x -> TipInfoIsEBB blk
forall blk x. TipInfoIsEBB blk -> Rep (TipInfoIsEBB blk) x
$cfrom :: forall blk x. TipInfoIsEBB blk -> Rep (TipInfoIsEBB blk) x
from :: forall x. TipInfoIsEBB blk -> Rep (TipInfoIsEBB blk) x
$cto :: forall blk x. Rep (TipInfoIsEBB blk) x -> TipInfoIsEBB blk
to :: forall x. Rep (TipInfoIsEBB blk) x -> TipInfoIsEBB blk
Generic)
deriving instance StandardHash blk => Eq (TipInfoIsEBB blk)
deriving instance StandardHash blk => Show (TipInfoIsEBB blk)
deriving instance StandardHash blk => NoThunks (TipInfoIsEBB blk)
defaultEncodeAnnTip :: TipInfo blk ~ HeaderHash blk
=> (HeaderHash blk -> Encoding)
-> (AnnTip blk -> Encoding)
defaultEncodeAnnTip :: forall blk.
(TipInfo blk ~ HeaderHash blk) =>
(HeaderHash blk -> Encoding) -> AnnTip blk -> Encoding
defaultEncodeAnnTip HeaderHash blk -> Encoding
encodeHash AnnTip{BlockNo
SlotNo
TipInfo blk
annTipSlotNo :: forall blk. AnnTip blk -> SlotNo
annTipBlockNo :: forall blk. AnnTip blk -> BlockNo
annTipInfo :: forall blk. AnnTip blk -> TipInfo blk
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk
..} = [Encoding] -> Encoding
forall a. Monoid a => [a] -> a
mconcat [
Word -> Encoding
encodeListLen Word
3
, SlotNo -> Encoding
forall a. Serialise a => a -> Encoding
encode SlotNo
annTipSlotNo
, HeaderHash blk -> Encoding
encodeHash HeaderHash blk
TipInfo blk
annTipInfo
, BlockNo -> Encoding
forall a. Serialise a => a -> Encoding
encode BlockNo
annTipBlockNo
]
defaultDecodeAnnTip :: TipInfo blk ~ HeaderHash blk
=> (forall s. Decoder s (HeaderHash blk))
-> (forall s. Decoder s (AnnTip blk))
defaultDecodeAnnTip :: forall blk.
(TipInfo blk ~ HeaderHash blk) =>
(forall s. Decoder s (HeaderHash blk))
-> forall s. Decoder s (AnnTip blk)
defaultDecodeAnnTip forall s. Decoder s (HeaderHash blk)
decodeHash = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"AnnTip" Int
3
SlotNo
annTipSlotNo <- Decoder s SlotNo
forall s. Decoder s SlotNo
forall a s. Serialise a => Decoder s a
decode
HeaderHash blk
annTipInfo <- Decoder s (HeaderHash blk)
forall s. Decoder s (HeaderHash blk)
decodeHash
BlockNo
annTipBlockNo <- Decoder s BlockNo
forall s. Decoder s BlockNo
forall a s. Serialise a => Decoder s a
decode
AnnTip blk -> Decoder s (AnnTip blk)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnTip{BlockNo
SlotNo
HeaderHash blk
TipInfo blk
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk
annTipSlotNo :: SlotNo
annTipInfo :: HeaderHash blk
annTipBlockNo :: BlockNo
..}
encodeAnnTipIsEBB :: TipInfo blk ~ TipInfoIsEBB blk
=> (HeaderHash blk -> Encoding)
-> (AnnTip blk -> Encoding)
encodeAnnTipIsEBB :: forall blk.
(TipInfo blk ~ TipInfoIsEBB blk) =>
(HeaderHash blk -> Encoding) -> AnnTip blk -> Encoding
encodeAnnTipIsEBB HeaderHash blk -> Encoding
encodeHash AnnTip{BlockNo
SlotNo
TipInfo blk
annTipSlotNo :: forall blk. AnnTip blk -> SlotNo
annTipBlockNo :: forall blk. AnnTip blk -> BlockNo
annTipInfo :: forall blk. AnnTip blk -> TipInfo blk
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipInfo :: TipInfo blk
..} = [Encoding] -> Encoding
forall a. Monoid a => [a] -> a
mconcat [
Word -> Encoding
encodeListLen Word
4
, SlotNo -> Encoding
forall a. Serialise a => a -> Encoding
encode SlotNo
annTipSlotNo
, HeaderHash blk -> Encoding
encodeHash HeaderHash blk
hash
, BlockNo -> Encoding
forall a. Serialise a => a -> Encoding
encode BlockNo
annTipBlockNo
, IsEBB -> Encoding
encodeInfo IsEBB
isEBB
]
where
TipInfoIsEBB HeaderHash blk
hash IsEBB
isEBB = TipInfo blk
annTipInfo
encodeInfo :: IsEBB -> Encoding
encodeInfo :: IsEBB -> Encoding
encodeInfo = IsEBB -> Encoding
forall a. Serialise a => a -> Encoding
encode
decodeAnnTipIsEBB :: TipInfo blk ~ TipInfoIsEBB blk
=> (forall s. Decoder s (HeaderHash blk))
-> (forall s. Decoder s (AnnTip blk))
decodeAnnTipIsEBB :: forall blk.
(TipInfo blk ~ TipInfoIsEBB blk) =>
(forall s. Decoder s (HeaderHash blk))
-> forall s. Decoder s (AnnTip blk)
decodeAnnTipIsEBB forall s. Decoder s (HeaderHash blk)
decodeHash = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"AnnTip" Int
4
SlotNo
annTipSlotNo <- Decoder s SlotNo
forall s. Decoder s SlotNo
forall a s. Serialise a => Decoder s a
decode
HeaderHash blk
hash <- Decoder s (HeaderHash blk)
forall s. Decoder s (HeaderHash blk)
decodeHash
BlockNo
annTipBlockNo <- Decoder s BlockNo
forall s. Decoder s BlockNo
forall a s. Serialise a => Decoder s a
decode
IsEBB
isEBB <- Decoder s IsEBB
forall s. Decoder s IsEBB
decodeInfo
AnnTip blk -> Decoder s (AnnTip blk)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnTip{annTipInfo :: TipInfo blk
annTipInfo = HeaderHash blk -> IsEBB -> TipInfoIsEBB blk
forall blk. HeaderHash blk -> IsEBB -> TipInfoIsEBB blk
TipInfoIsEBB HeaderHash blk
hash IsEBB
isEBB, BlockNo
SlotNo
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
annTipSlotNo :: SlotNo
annTipBlockNo :: BlockNo
..}
where
decodeInfo :: forall s. Decoder s IsEBB
decodeInfo :: forall s. Decoder s IsEBB
decodeInfo = Decoder s IsEBB
forall s. Decoder s IsEBB
forall a s. Serialise a => Decoder s a
decode
encodeHeaderState :: (ChainDepState (BlockProtocol blk) -> Encoding)
-> (AnnTip blk -> Encoding)
-> (HeaderState blk -> Encoding)
ChainDepState (BlockProtocol blk) -> Encoding
encodeChainDepState
AnnTip blk -> Encoding
encodeAnnTip'
HeaderState {WithOrigin (AnnTip blk)
ChainDepState (BlockProtocol blk)
headerStateTip :: forall blk. HeaderState blk -> WithOrigin (AnnTip blk)
headerStateChainDep :: forall blk. HeaderState blk -> ChainDepState (BlockProtocol blk)
headerStateTip :: WithOrigin (AnnTip blk)
headerStateChainDep :: ChainDepState (BlockProtocol blk)
..} = [Encoding] -> Encoding
forall a. Monoid a => [a] -> a
mconcat [
Word -> Encoding
encodeListLen Word
2
, (AnnTip blk -> Encoding) -> WithOrigin (AnnTip blk) -> Encoding
forall a. (a -> Encoding) -> WithOrigin a -> Encoding
Util.CBOR.encodeWithOrigin AnnTip blk -> Encoding
encodeAnnTip' WithOrigin (AnnTip blk)
headerStateTip
, ChainDepState (BlockProtocol blk) -> Encoding
encodeChainDepState ChainDepState (BlockProtocol blk)
headerStateChainDep
]
decodeHeaderState :: (forall s. Decoder s (ChainDepState (BlockProtocol blk)))
-> (forall s. Decoder s (AnnTip blk))
-> (forall s. Decoder s (HeaderState blk))
forall s. Decoder s (ChainDepState (BlockProtocol blk))
decodeChainDepState forall s. Decoder s (AnnTip blk)
decodeAnnTip' = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"HeaderState" Int
2
WithOrigin (AnnTip blk)
headerStateTip <- Decoder s (AnnTip blk) -> Decoder s (WithOrigin (AnnTip blk))
forall s a. Decoder s a -> Decoder s (WithOrigin a)
Util.CBOR.decodeWithOrigin Decoder s (AnnTip blk)
forall s. Decoder s (AnnTip blk)
decodeAnnTip'
ChainDepState (BlockProtocol blk)
headerStateChainDep <- Decoder s (ChainDepState (BlockProtocol blk))
forall s. Decoder s (ChainDepState (BlockProtocol blk))
decodeChainDepState
HeaderState blk -> Decoder s (HeaderState blk)
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return HeaderState {WithOrigin (AnnTip blk)
ChainDepState (BlockProtocol blk)
headerStateTip :: WithOrigin (AnnTip blk)
headerStateChainDep :: ChainDepState (BlockProtocol blk)
headerStateTip :: WithOrigin (AnnTip blk)
headerStateChainDep :: ChainDepState (BlockProtocol blk)
..}