{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
module Ouroboros.Consensus.Storage.ChainDB.Impl.Paths (
LookupBlockInfo
, extendWithSuccessors
, maximalCandidates
, Path (..)
, computePath
, ReversePath (..)
, computeReversePath
, isReachable
) where
import Data.Foldable as Foldable (foldl')
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Word (Word64)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Fragment.Diff (ChainDiff (..))
import qualified Ouroboros.Consensus.Fragment.Diff as Diff
import Ouroboros.Consensus.Storage.ChainDB.API hiding (ChainDB (..),
closeDB, getMaxSlotNo)
import qualified Ouroboros.Consensus.Storage.VolatileDB as VolatileDB
import Ouroboros.Network.AnchoredFragment (AnchoredFragment)
import qualified Ouroboros.Network.AnchoredFragment as AF
type LookupBlockInfo blk = HeaderHash blk -> Maybe (VolatileDB.BlockInfo blk)
maximalCandidates ::
forall blk.
(ChainHash blk -> Set (HeaderHash blk))
-> Maybe Word64
-> Point blk
-> [NonEmpty (HeaderHash blk)]
maximalCandidates :: forall blk.
(ChainHash blk -> Set (HeaderHash blk))
-> Maybe Word64 -> Point blk -> [NonEmpty (HeaderHash blk)]
maximalCandidates ChainHash blk -> Set (HeaderHash blk)
succsOf Maybe Word64
sizeLimit Point blk
b =
([HeaderHash blk] -> Maybe (NonEmpty (HeaderHash blk)))
-> [[HeaderHash blk]] -> [NonEmpty (HeaderHash blk)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ([HeaderHash blk] -> Maybe (NonEmpty (HeaderHash blk))
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty ([HeaderHash blk] -> Maybe (NonEmpty (HeaderHash blk)))
-> ([HeaderHash blk] -> [HeaderHash blk])
-> [HeaderHash blk]
-> Maybe (NonEmpty (HeaderHash blk))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [HeaderHash blk] -> [HeaderHash blk]
forall {a}. [a] -> [a]
trimToSizeLimit) ([[HeaderHash blk]] -> [NonEmpty (HeaderHash blk)])
-> [[HeaderHash blk]] -> [NonEmpty (HeaderHash blk)]
forall a b. (a -> b) -> a -> b
$ ChainHash blk -> [[HeaderHash blk]]
go (Point blk -> ChainHash blk
forall {k} (block :: k). Point block -> ChainHash block
pointHash Point blk
b)
where
go :: ChainHash blk -> [[HeaderHash blk]]
go :: ChainHash blk -> [[HeaderHash blk]]
go ChainHash blk
mbHash = case Set (HeaderHash blk) -> [HeaderHash blk]
forall a. Set a -> [a]
Set.toList (Set (HeaderHash blk) -> [HeaderHash blk])
-> Set (HeaderHash blk) -> [HeaderHash blk]
forall a b. (a -> b) -> a -> b
$ ChainHash blk -> Set (HeaderHash blk)
succsOf ChainHash blk
mbHash of
[] -> [[]]
[HeaderHash blk]
succs -> [ HeaderHash blk
next HeaderHash blk -> [HeaderHash blk] -> [HeaderHash blk]
forall a. a -> [a] -> [a]
: [HeaderHash blk]
candidate
| HeaderHash blk
next <- [HeaderHash blk]
succs
, [HeaderHash blk]
candidate <- ChainHash blk -> [[HeaderHash blk]]
go (HeaderHash blk -> ChainHash blk
forall {k} (b :: k). HeaderHash b -> ChainHash b
BlockHash HeaderHash blk
next)
]
trimToSizeLimit :: [a] -> [a]
trimToSizeLimit = case Maybe Word64
sizeLimit of
Just Word64
limit -> Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
limit)
Maybe Word64
Nothing -> [a] -> [a]
forall a. a -> a
id
extendWithSuccessors ::
forall blk. HasHeader blk
=> (ChainHash blk -> Set (HeaderHash blk))
-> LookupBlockInfo blk
-> ChainDiff (HeaderFields blk)
-> NonEmpty (ChainDiff (HeaderFields blk))
extendWithSuccessors :: forall blk.
HasHeader blk =>
(ChainHash blk -> Set (HeaderHash blk))
-> LookupBlockInfo blk
-> ChainDiff (HeaderFields blk)
-> NonEmpty (ChainDiff (HeaderFields blk))
extendWithSuccessors ChainHash blk -> Set (HeaderHash blk)
succsOf LookupBlockInfo blk
lookupBlockInfo ChainDiff (HeaderFields blk)
diff =
case [ChainDiff (HeaderFields blk)]
-> Maybe (NonEmpty (ChainDiff (HeaderFields blk)))
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty [ChainDiff (HeaderFields blk)]
extensions of
Maybe (NonEmpty (ChainDiff (HeaderFields blk)))
Nothing -> ChainDiff (HeaderFields blk)
diff ChainDiff (HeaderFields blk)
-> [ChainDiff (HeaderFields blk)]
-> NonEmpty (ChainDiff (HeaderFields blk))
forall a. a -> [a] -> NonEmpty a
NE.:| []
Just NonEmpty (ChainDiff (HeaderFields blk))
extensions' -> NonEmpty (ChainDiff (HeaderFields blk))
extensions'
where
extensions :: [ChainDiff (HeaderFields blk)]
extensions =
[ (ChainDiff (HeaderFields blk)
-> HeaderFields blk -> ChainDiff (HeaderFields blk))
-> ChainDiff (HeaderFields blk)
-> NonEmpty (HeaderFields blk)
-> ChainDiff (HeaderFields blk)
forall b a. (b -> a -> b) -> b -> NonEmpty a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl' ChainDiff (HeaderFields blk)
-> HeaderFields blk -> ChainDiff (HeaderFields blk)
forall b. HasHeader b => ChainDiff b -> b -> ChainDiff b
Diff.append ChainDiff (HeaderFields blk)
diff (HeaderHash blk -> HeaderFields blk
lookupHeaderFields (HeaderHash blk -> HeaderFields blk)
-> NonEmpty (HeaderHash blk) -> NonEmpty (HeaderFields blk)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (HeaderHash blk)
candHashes)
| NonEmpty (HeaderHash blk)
candHashes <- (ChainHash blk -> Set (HeaderHash blk))
-> Maybe Word64 -> Point blk -> [NonEmpty (HeaderHash blk)]
forall blk.
(ChainHash blk -> Set (HeaderHash blk))
-> Maybe Word64 -> Point blk -> [NonEmpty (HeaderHash blk)]
maximalCandidates ChainHash blk -> Set (HeaderHash blk)
succsOf Maybe Word64
forall a. Maybe a
Nothing (Point (HeaderFields blk) -> Point blk
forall {k1} {k2} (b :: k1) (b' :: k2).
Coercible (HeaderHash b) (HeaderHash b') =>
Point b -> Point b'
castPoint (ChainDiff (HeaderFields blk) -> Point (HeaderFields blk)
forall b. HasHeader b => ChainDiff b -> Point b
Diff.getTip ChainDiff (HeaderFields blk)
diff))
]
lookupHeaderFields :: HeaderHash blk -> HeaderFields blk
lookupHeaderFields :: HeaderHash blk -> HeaderFields blk
lookupHeaderFields =
BlockInfo blk -> HeaderFields blk
forall blk. BlockInfo blk -> HeaderFields blk
headerFieldsFromBlockInfo
(BlockInfo blk -> HeaderFields blk)
-> (HeaderHash blk -> BlockInfo blk)
-> HeaderHash blk
-> HeaderFields blk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockInfo blk -> Maybe (BlockInfo blk) -> BlockInfo blk
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> BlockInfo blk
forall a. HasCallStack => [Char] -> a
error [Char]
"successor must in the VolatileDB")
(Maybe (BlockInfo blk) -> BlockInfo blk)
-> LookupBlockInfo blk -> HeaderHash blk -> BlockInfo blk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LookupBlockInfo blk
lookupBlockInfo
computePath ::
forall blk. HasHeader blk
=> LookupBlockInfo blk
-> StreamFrom blk
-> StreamTo blk
-> Maybe (Path blk)
computePath :: forall blk.
HasHeader blk =>
LookupBlockInfo blk
-> StreamFrom blk -> StreamTo blk -> Maybe (Path blk)
computePath LookupBlockInfo blk
lookupBlockInfo StreamFrom blk
from StreamTo blk
to =
case LookupBlockInfo blk -> HeaderHash blk -> Maybe (ReversePath blk)
forall blk.
LookupBlockInfo blk -> HeaderHash blk -> Maybe (ReversePath blk)
computeReversePath LookupBlockInfo blk
lookupBlockInfo (RealPoint blk -> HeaderHash blk
forall blk. RealPoint blk -> HeaderHash blk
realPointHash RealPoint blk
endPt) of
Maybe (ReversePath blk)
Nothing -> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ RealPoint blk -> Path blk
forall blk. RealPoint blk -> Path blk
NotInVolatileDB RealPoint blk
endPt
Just ReversePath blk
volPath -> [RealPoint blk] -> ReversePath blk -> Maybe (Path blk)
go [] ReversePath blk
volPath
where
endPt :: RealPoint blk
endPt :: RealPoint blk
endPt = case StreamTo blk
to of
StreamToInclusive RealPoint blk
pt -> RealPoint blk
pt
fieldsToRealPoint :: HeaderFields blk -> RealPoint blk
fieldsToRealPoint :: HeaderFields blk -> RealPoint blk
fieldsToRealPoint HeaderFields blk
flds =
SlotNo -> HeaderHash blk -> RealPoint blk
forall blk. SlotNo -> HeaderHash blk -> RealPoint blk
RealPoint (HeaderFields blk -> SlotNo
forall k (b :: k). HeaderFields b -> SlotNo
headerFieldSlot HeaderFields blk
flds) (HeaderFields blk -> HeaderHash blk
forall k (b :: k). HeaderFields b -> HeaderHash b
headerFieldHash HeaderFields blk
flds)
addToAcc :: HeaderFields blk -> [RealPoint blk] -> [RealPoint blk]
addToAcc :: HeaderFields blk -> [RealPoint blk] -> [RealPoint blk]
addToAcc HeaderFields blk
flds [RealPoint blk]
pts = RealPoint blk
pt RealPoint blk -> [RealPoint blk] -> [RealPoint blk]
forall a. a -> [a] -> [a]
: [RealPoint blk]
pts
where
!pt :: RealPoint blk
pt = HeaderFields blk -> RealPoint blk
fieldsToRealPoint HeaderFields blk
flds
go ::
[RealPoint blk]
-> ReversePath blk
-> Maybe (Path blk)
go :: [RealPoint blk] -> ReversePath blk -> Maybe (Path blk)
go ![RealPoint blk]
acc = \case
ReversePath blk
StoppedAtGenesis
| StreamFromExclusive Point blk
GenesisPoint <- StreamFrom blk
from
-> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ [RealPoint blk] -> Path blk
forall blk. [RealPoint blk] -> Path blk
CompletelyInVolatileDB [RealPoint blk]
acc
| Bool
otherwise
-> Maybe (Path blk)
forall a. Maybe a
Nothing
StoppedAt HeaderHash blk
hash BlockNo
_bno
| StreamFromExclusive Point blk
GenesisPoint <- StreamFrom blk
from
-> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ HeaderHash blk -> [RealPoint blk] -> Path blk
forall blk. HeaderHash blk -> [RealPoint blk] -> Path blk
PartiallyInVolatileDB HeaderHash blk
hash [RealPoint blk]
acc
| StreamFromExclusive (BlockPoint SlotNo
_ HeaderHash blk
hash') <- StreamFrom blk
from
, HeaderHash blk
hash HeaderHash blk -> HeaderHash blk -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderHash blk
hash'
-> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ [RealPoint blk] -> Path blk
forall blk. [RealPoint blk] -> Path blk
CompletelyInVolatileDB [RealPoint blk]
acc
| StreamFromExclusive (BlockPoint SlotNo
_ HeaderHash blk
_) <- StreamFrom blk
from
-> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ HeaderHash blk -> [RealPoint blk] -> Path blk
forall blk. HeaderHash blk -> [RealPoint blk] -> Path blk
PartiallyInVolatileDB HeaderHash blk
hash [RealPoint blk]
acc
| StreamFromInclusive RealPoint blk
_ <- StreamFrom blk
from
-> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ HeaderHash blk -> [RealPoint blk] -> Path blk
forall blk. HeaderHash blk -> [RealPoint blk] -> Path blk
PartiallyInVolatileDB HeaderHash blk
hash [RealPoint blk]
acc
ReversePath blk
volPath' ::> (HeaderFields blk
flds, IsEBB
_isEBB)
| StreamFromExclusive Point blk
GenesisPoint <- StreamFrom blk
from
-> [RealPoint blk] -> ReversePath blk -> Maybe (Path blk)
go (HeaderFields blk -> [RealPoint blk] -> [RealPoint blk]
addToAcc HeaderFields blk
flds [RealPoint blk]
acc) ReversePath blk
volPath'
| StreamFromExclusive (BlockPoint SlotNo
_ HeaderHash blk
hash') <- StreamFrom blk
from
, HeaderFields blk -> HeaderHash blk
forall k (b :: k). HeaderFields b -> HeaderHash b
headerFieldHash HeaderFields blk
flds HeaderHash blk -> HeaderHash blk -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderHash blk
hash'
-> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ [RealPoint blk] -> Path blk
forall blk. [RealPoint blk] -> Path blk
CompletelyInVolatileDB [RealPoint blk]
acc
| StreamFromExclusive (BlockPoint SlotNo
_ HeaderHash blk
_) <- StreamFrom blk
from
-> [RealPoint blk] -> ReversePath blk -> Maybe (Path blk)
go (HeaderFields blk -> [RealPoint blk] -> [RealPoint blk]
addToAcc HeaderFields blk
flds [RealPoint blk]
acc) ReversePath blk
volPath'
| StreamFromInclusive RealPoint blk
pt' <- StreamFrom blk
from
, HeaderFields blk -> RealPoint blk
fieldsToRealPoint HeaderFields blk
flds RealPoint blk -> RealPoint blk -> Bool
forall a. Eq a => a -> a -> Bool
== RealPoint blk
pt'
-> Path blk -> Maybe (Path blk)
forall a. a -> Maybe a
Just (Path blk -> Maybe (Path blk)) -> Path blk -> Maybe (Path blk)
forall a b. (a -> b) -> a -> b
$ [RealPoint blk] -> Path blk
forall blk. [RealPoint blk] -> Path blk
CompletelyInVolatileDB (HeaderFields blk -> [RealPoint blk] -> [RealPoint blk]
addToAcc HeaderFields blk
flds [RealPoint blk]
acc)
| StreamFromInclusive RealPoint blk
_ <- StreamFrom blk
from
-> [RealPoint blk] -> ReversePath blk -> Maybe (Path blk)
go (HeaderFields blk -> [RealPoint blk] -> [RealPoint blk]
addToAcc HeaderFields blk
flds [RealPoint blk]
acc) ReversePath blk
volPath'
data Path blk =
NotInVolatileDB (RealPoint blk)
| CompletelyInVolatileDB [RealPoint blk]
| PartiallyInVolatileDB (HeaderHash blk) [RealPoint blk]
deriving instance HasHeader blk => Eq (Path blk)
deriving instance HasHeader blk => Show (Path blk)
headerFieldsFromBlockInfo :: VolatileDB.BlockInfo blk -> HeaderFields blk
VolatileDB.BlockInfo { SlotNo
biSlotNo :: SlotNo
biSlotNo :: forall blk. BlockInfo blk -> SlotNo
biSlotNo, HeaderHash blk
biHash :: HeaderHash blk
biHash :: forall blk. BlockInfo blk -> HeaderHash blk
biHash, BlockNo
biBlockNo :: BlockNo
biBlockNo :: forall blk. BlockInfo blk -> BlockNo
biBlockNo } =
HeaderFields {
headerFieldHash :: HeaderHash blk
headerFieldHash = HeaderHash blk
biHash
, headerFieldSlot :: SlotNo
headerFieldSlot = SlotNo
biSlotNo
, headerFieldBlockNo :: BlockNo
headerFieldBlockNo = BlockNo
biBlockNo
}
data ReversePath blk =
StoppedAtGenesis
| StoppedAt (HeaderHash blk) BlockNo
| (ReversePath blk) ::> (HeaderFields blk, IsEBB)
computeReversePath
:: forall blk.
LookupBlockInfo blk
-> HeaderHash blk
-> Maybe (ReversePath blk)
computeReversePath :: forall blk.
LookupBlockInfo blk -> HeaderHash blk -> Maybe (ReversePath blk)
computeReversePath LookupBlockInfo blk
lookupBlockInfo HeaderHash blk
endHash =
case LookupBlockInfo blk
lookupBlockInfo HeaderHash blk
endHash of
Maybe (BlockInfo blk)
Nothing -> Maybe (ReversePath blk)
forall a. Maybe a
Nothing
Just blockInfo :: BlockInfo blk
blockInfo@VolatileDB.BlockInfo { BlockNo
biBlockNo :: forall blk. BlockInfo blk -> BlockNo
biBlockNo :: BlockNo
biBlockNo, IsEBB
biIsEBB :: IsEBB
biIsEBB :: forall blk. BlockInfo blk -> IsEBB
biIsEBB, ChainHash blk
biPrevHash :: ChainHash blk
biPrevHash :: forall blk. BlockInfo blk -> ChainHash blk
biPrevHash } -> ReversePath blk -> Maybe (ReversePath blk)
forall a. a -> Maybe a
Just (ReversePath blk -> Maybe (ReversePath blk))
-> ReversePath blk -> Maybe (ReversePath blk)
forall a b. (a -> b) -> a -> b
$
ChainHash blk -> BlockNo -> IsEBB -> ReversePath blk
go ChainHash blk
biPrevHash BlockNo
biBlockNo IsEBB
biIsEBB ReversePath blk -> (HeaderFields blk, IsEBB) -> ReversePath blk
forall blk.
ReversePath blk -> (HeaderFields blk, IsEBB) -> ReversePath blk
::> (BlockInfo blk -> HeaderFields blk
forall blk. BlockInfo blk -> HeaderFields blk
headerFieldsFromBlockInfo BlockInfo blk
blockInfo, IsEBB
biIsEBB)
where
go ::
ChainHash blk
-> BlockNo
-> IsEBB
-> ReversePath blk
go :: ChainHash blk -> BlockNo -> IsEBB -> ReversePath blk
go ChainHash blk
predecessor BlockNo
lastBlockNo IsEBB
lastIsEBB = case ChainHash blk
predecessor of
ChainHash blk
GenesisHash -> ReversePath blk
forall blk. ReversePath blk
StoppedAtGenesis
BlockHash HeaderHash blk
prevHash -> case LookupBlockInfo blk
lookupBlockInfo HeaderHash blk
prevHash of
Maybe (BlockInfo blk)
Nothing ->
HeaderHash blk -> BlockNo -> ReversePath blk
forall blk. HeaderHash blk -> BlockNo -> ReversePath blk
StoppedAt HeaderHash blk
prevHash (BlockNo -> IsEBB -> BlockNo
prevBlockNo BlockNo
lastBlockNo IsEBB
lastIsEBB)
Just blockInfo :: BlockInfo blk
blockInfo@VolatileDB.BlockInfo { BlockNo
biBlockNo :: forall blk. BlockInfo blk -> BlockNo
biBlockNo :: BlockNo
biBlockNo, IsEBB
biIsEBB :: forall blk. BlockInfo blk -> IsEBB
biIsEBB :: IsEBB
biIsEBB, ChainHash blk
biPrevHash :: forall blk. BlockInfo blk -> ChainHash blk
biPrevHash :: ChainHash blk
biPrevHash } ->
ChainHash blk -> BlockNo -> IsEBB -> ReversePath blk
go ChainHash blk
biPrevHash BlockNo
biBlockNo IsEBB
biIsEBB ReversePath blk -> (HeaderFields blk, IsEBB) -> ReversePath blk
forall blk.
ReversePath blk -> (HeaderFields blk, IsEBB) -> ReversePath blk
::> (BlockInfo blk -> HeaderFields blk
forall blk. BlockInfo blk -> HeaderFields blk
headerFieldsFromBlockInfo BlockInfo blk
blockInfo, IsEBB
biIsEBB)
prevBlockNo :: BlockNo -> IsEBB -> BlockNo
prevBlockNo :: BlockNo -> IsEBB -> BlockNo
prevBlockNo BlockNo
bno IsEBB
isEBB = case (BlockNo
bno, IsEBB
isEBB) of
(BlockNo
0, IsEBB
IsNotEBB) -> [Char] -> BlockNo
forall a. HasCallStack => [Char] -> a
error [Char]
"precondition violated"
(BlockNo
_, IsEBB
IsNotEBB) -> BlockNo
bno BlockNo -> BlockNo -> BlockNo
forall a. Num a => a -> a -> a
- BlockNo
1
(BlockNo
_, IsEBB
IsEBB) -> BlockNo
bno
isReachable
:: forall blk. (HasHeader blk, GetHeader blk)
=> LookupBlockInfo blk
-> AnchoredFragment (Header blk)
-> RealPoint blk
-> Maybe (ChainDiff (HeaderFields blk))
isReachable :: forall blk.
(HasHeader blk, GetHeader blk) =>
LookupBlockInfo blk
-> AnchoredFragment (Header blk)
-> RealPoint blk
-> Maybe (ChainDiff (HeaderFields blk))
isReachable LookupBlockInfo blk
lookupBlockInfo = \AnchoredFragment (Header blk)
chain RealPoint blk
b ->
case LookupBlockInfo blk -> HeaderHash blk -> Maybe (ReversePath blk)
forall blk.
LookupBlockInfo blk -> HeaderHash blk -> Maybe (ReversePath blk)
computeReversePath LookupBlockInfo blk
lookupBlockInfo (RealPoint blk -> HeaderHash blk
forall blk. RealPoint blk -> HeaderHash blk
realPointHash RealPoint blk
b) of
Maybe (ReversePath blk)
Nothing -> Maybe (ChainDiff (HeaderFields blk))
forall a. Maybe a
Nothing
Just ReversePath blk
reversePath -> AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go AnchoredFragment (Header blk)
chain ReversePath blk
reversePath Word64
0 []
where
go
:: AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go :: AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go AnchoredFragment (Header blk)
chain ReversePath blk
path !Word64
rollback [HeaderFields blk]
acc = case (AnchoredFragment (Header blk)
chain, ReversePath blk
path) of
(AF.Empty Anchor (Header blk)
anchor, StoppedAt HeaderHash blk
hash BlockNo
bno)
| Anchor (Header blk) -> WithOrigin BlockNo
forall block. Anchor block -> WithOrigin BlockNo
AF.anchorToBlockNo Anchor (Header blk)
anchor WithOrigin BlockNo -> WithOrigin BlockNo -> Bool
forall a. Eq a => a -> a -> Bool
== BlockNo -> WithOrigin BlockNo
forall t. t -> WithOrigin t
NotOrigin BlockNo
bno
, Anchor (Header blk) -> ChainHash (Header blk)
forall block. Anchor block -> ChainHash block
AF.anchorToHash Anchor (Header blk)
anchor ChainHash (Header blk) -> ChainHash (Header blk) -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderHash (Header blk) -> ChainHash (Header blk)
forall {k} (b :: k). HeaderHash b -> ChainHash b
BlockHash HeaderHash blk
HeaderHash (Header blk)
hash
-> ChainDiff (HeaderFields blk)
-> Maybe (ChainDiff (HeaderFields blk))
forall a. a -> Maybe a
Just (Word64
-> AnchoredFragment (HeaderFields blk)
-> ChainDiff (HeaderFields blk)
forall b. Word64 -> AnchoredFragment b -> ChainDiff b
ChainDiff Word64
rollback (Anchor (HeaderFields blk)
-> [HeaderFields blk] -> AnchoredFragment (HeaderFields blk)
forall v a b. Anchorable v a b => a -> [b] -> AnchoredSeq v a b
AF.fromOldestFirst (Anchor (Header blk) -> Anchor (HeaderFields blk)
forall a b. (HeaderHash a ~ HeaderHash b) => Anchor a -> Anchor b
AF.castAnchor Anchor (Header blk)
anchor) [HeaderFields blk]
acc))
| Bool
otherwise
-> Maybe (ChainDiff (HeaderFields blk))
forall a. Maybe a
Nothing
(AF.Empty Anchor (Header blk)
anchor, ReversePath blk
path' ::> (HeaderFields blk
flds, IsEBB
_))
| Anchor blk -> WithOrigin (HeaderFields blk)
forall block. Anchor block -> WithOrigin (HeaderFields block)
AF.anchorToHeaderFields (Anchor (Header blk) -> Anchor blk
forall a b. (HeaderHash a ~ HeaderHash b) => Anchor a -> Anchor b
AF.castAnchor Anchor (Header blk)
anchor) WithOrigin (HeaderFields blk)
-> WithOrigin (HeaderFields blk) -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderFields blk -> WithOrigin (HeaderFields blk)
forall t. t -> WithOrigin t
NotOrigin HeaderFields blk
flds
-> ChainDiff (HeaderFields blk)
-> Maybe (ChainDiff (HeaderFields blk))
forall a. a -> Maybe a
Just (Word64
-> AnchoredFragment (HeaderFields blk)
-> ChainDiff (HeaderFields blk)
forall b. Word64 -> AnchoredFragment b -> ChainDiff b
ChainDiff Word64
rollback (Anchor (HeaderFields blk)
-> [HeaderFields blk] -> AnchoredFragment (HeaderFields blk)
forall v a b. Anchorable v a b => a -> [b] -> AnchoredSeq v a b
AF.fromOldestFirst (Anchor (Header blk) -> Anchor (HeaderFields blk)
forall a b. (HeaderHash a ~ HeaderHash b) => Anchor a -> Anchor b
AF.castAnchor Anchor (Header blk)
anchor) [HeaderFields blk]
acc))
| Anchor (Header blk) -> WithOrigin BlockNo
forall block. Anchor block -> WithOrigin BlockNo
AF.anchorToBlockNo Anchor (Header blk)
anchor WithOrigin BlockNo -> WithOrigin BlockNo -> Bool
forall a. Ord a => a -> a -> Bool
> BlockNo -> WithOrigin BlockNo
forall t. t -> WithOrigin t
NotOrigin (HeaderFields blk -> BlockNo
forall k (b :: k). HeaderFields b -> BlockNo
headerFieldBlockNo HeaderFields blk
flds)
-> Maybe (ChainDiff (HeaderFields blk))
forall a. Maybe a
Nothing
| Bool
otherwise
-> AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go AnchoredFragment (Header blk)
chain ReversePath blk
path' Word64
rollback (HeaderFields blk
fldsHeaderFields blk -> [HeaderFields blk] -> [HeaderFields blk]
forall a. a -> [a] -> [a]
:[HeaderFields blk]
acc)
(AnchoredFragment (Header blk)
chain' AF.:> Header blk
hdr, StoppedAt HeaderHash blk
hash BlockNo
bno)
| Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr BlockNo -> BlockNo -> Bool
forall a. Eq a => a -> a -> Bool
== BlockNo
bno
, 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
hash
, let anchor :: Anchor (HeaderFields blk)
anchor = Anchor (Header blk) -> Anchor (HeaderFields blk)
forall a b. (HeaderHash a ~ HeaderHash b) => Anchor a -> Anchor b
AF.castAnchor (Header blk -> Anchor (Header blk)
forall block. HasHeader block => block -> Anchor block
AF.anchorFromBlock Header blk
hdr)
-> ChainDiff (HeaderFields blk)
-> Maybe (ChainDiff (HeaderFields blk))
forall a. a -> Maybe a
Just (Word64
-> AnchoredFragment (HeaderFields blk)
-> ChainDiff (HeaderFields blk)
forall b. Word64 -> AnchoredFragment b -> ChainDiff b
ChainDiff Word64
rollback (Anchor (HeaderFields blk)
-> [HeaderFields blk] -> AnchoredFragment (HeaderFields blk)
forall v a b. Anchorable v a b => a -> [b] -> AnchoredSeq v a b
AF.fromOldestFirst Anchor (HeaderFields blk)
anchor [HeaderFields blk]
acc))
| Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr BlockNo -> BlockNo -> Bool
forall a. Ord a => a -> a -> Bool
< BlockNo
bno
-> Maybe (ChainDiff (HeaderFields blk))
forall a. Maybe a
Nothing
| Bool
otherwise
-> AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go AnchoredFragment (Header blk)
chain' ReversePath blk
path (Word64
rollback Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) [HeaderFields blk]
acc
(AnchoredFragment (Header blk)
_, ReversePath blk
StoppedAtGenesis)
| Anchor (Header blk) -> Bool
forall block. Anchor block -> Bool
AF.anchorIsGenesis (AnchoredFragment (Header blk) -> Anchor (Header blk)
forall v a b. AnchoredSeq v a b -> a
AF.anchor AnchoredFragment (Header blk)
chain)
-> let !rollback' :: Word64
rollback' = Word64
rollback Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (AnchoredFragment (Header blk) -> Int
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Int
AF.length AnchoredFragment (Header blk)
chain)
in ChainDiff (HeaderFields blk)
-> Maybe (ChainDiff (HeaderFields blk))
forall a. a -> Maybe a
Just (Word64
-> AnchoredFragment (HeaderFields blk)
-> ChainDiff (HeaderFields blk)
forall b. Word64 -> AnchoredFragment b -> ChainDiff b
ChainDiff Word64
rollback' (Anchor (HeaderFields blk)
-> [HeaderFields blk] -> AnchoredFragment (HeaderFields blk)
forall v a b. Anchorable v a b => a -> [b] -> AnchoredSeq v a b
AF.fromOldestFirst Anchor (HeaderFields blk)
forall block. Anchor block
AF.AnchorGenesis [HeaderFields blk]
acc))
| Bool
otherwise
-> Maybe (ChainDiff (HeaderFields blk))
forall a. Maybe a
Nothing
(AnchoredFragment (Header blk)
chain' AF.:> Header blk
hdr, ReversePath blk
path' ::> (HeaderFields blk
flds, IsEBB
ptIsEBB)) ->
case Header blk
hdr Header blk -> (BlockNo, IsEBB) -> Ordering
`ebbAwareCompare` (HeaderFields blk -> BlockNo
forall k (b :: k). HeaderFields b -> BlockNo
headerFieldBlockNo HeaderFields blk
flds, IsEBB
ptIsEBB) of
Ordering
LT -> AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go AnchoredFragment (Header blk)
chain ReversePath blk
path' Word64
rollback (HeaderFields blk
fldsHeaderFields blk -> [HeaderFields blk] -> [HeaderFields blk]
forall a. a -> [a] -> [a]
:[HeaderFields blk]
acc)
Ordering
GT -> AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go AnchoredFragment (Header blk)
chain' ReversePath blk
path (Word64
rollback Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) [HeaderFields blk]
acc
Ordering
EQ | Header blk -> HeaderHash (Header blk)
forall b. HasHeader b => b -> HeaderHash b
blockHash Header blk
hdr HeaderHash blk -> HeaderHash blk -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderFields blk -> HeaderHash blk
forall k (b :: k). HeaderFields b -> HeaderHash b
headerFieldHash HeaderFields blk
flds
, let anchor :: Anchor (HeaderFields blk)
anchor = Anchor (Header blk) -> Anchor (HeaderFields blk)
forall a b. (HeaderHash a ~ HeaderHash b) => Anchor a -> Anchor b
AF.castAnchor (Header blk -> Anchor (Header blk)
forall block. HasHeader block => block -> Anchor block
AF.anchorFromBlock Header blk
hdr)
-> ChainDiff (HeaderFields blk)
-> Maybe (ChainDiff (HeaderFields blk))
forall a. a -> Maybe a
Just (Word64
-> AnchoredFragment (HeaderFields blk)
-> ChainDiff (HeaderFields blk)
forall b. Word64 -> AnchoredFragment b -> ChainDiff b
ChainDiff Word64
rollback (Anchor (HeaderFields blk)
-> [HeaderFields blk] -> AnchoredFragment (HeaderFields blk)
forall v a b. Anchorable v a b => a -> [b] -> AnchoredSeq v a b
AF.fromOldestFirst Anchor (HeaderFields blk)
anchor [HeaderFields blk]
acc))
| Bool
otherwise
-> AnchoredFragment (Header blk)
-> ReversePath blk
-> Word64
-> [HeaderFields blk]
-> Maybe (ChainDiff (HeaderFields blk))
go AnchoredFragment (Header blk)
chain' ReversePath blk
path' (Word64
rollback Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) (HeaderFields blk
fldsHeaderFields blk -> [HeaderFields blk] -> [HeaderFields blk]
forall a. a -> [a] -> [a]
:[HeaderFields blk]
acc)
ebbAwareCompare :: Header blk -> (BlockNo, IsEBB) -> Ordering
ebbAwareCompare :: Header blk -> (BlockNo, IsEBB) -> Ordering
ebbAwareCompare Header blk
hdr (BlockNo
ptBlockNo, IsEBB
ptIsEBB) =
BlockNo -> BlockNo -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr) BlockNo
ptBlockNo Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend`
case (Header blk -> IsEBB
forall blk. GetHeader blk => Header blk -> IsEBB
headerToIsEBB Header blk
hdr, IsEBB
ptIsEBB) of
(IsEBB
IsEBB, IsEBB
IsNotEBB) -> Ordering
GT
(IsEBB
IsNotEBB, IsEBB
IsEBB) -> Ordering
LT
(IsEBB
IsEBB, IsEBB
IsEBB) -> Ordering
EQ
(IsEBB
IsNotEBB, IsEBB
IsNotEBB) -> Ordering
EQ