{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
module Ouroboros.Consensus.Storage.ImmutableDB.API (
ImmutableDB (..)
, Iterator (..)
, IteratorResult (..)
, iteratorToList
, traverseIterator
, CompareTip (..)
, SecondaryOffset
, Tip (..)
, blockToTip
, headerToTip
, tipToAnchor
, tipToPoint
, tipToRealPoint
, ApiMisuse (..)
, ImmutableDBError (..)
, MissingBlock (..)
, UnexpectedFailure (..)
, missingBlockPoint
, throwApiMisuse
, throwUnexpectedFailure
, appendBlock
, closeDB
, getBlockComponent
, getTip
, stream
, getKnownBlockComponent
, getTipAnchor
, getTipPoint
, getTipSlot
, hasBlock
, streamAfterKnownPoint
, streamAfterPoint
, streamAll
, withDB
) where
import qualified Codec.CBOR.Read as CBOR
import Control.Monad.Except (ExceptT (..), runExceptT, throwError)
import Control.Monad.Trans.Class (lift)
import Control.ResourceRegistry (ResourceRegistry)
import qualified Data.ByteString.Lazy as Lazy
import Data.Either (isRight)
import Data.Function (on)
import Data.List.NonEmpty (NonEmpty)
import Data.Sequence.Strict (StrictSeq)
import Data.Typeable (Typeable)
import Data.Word (Word32)
import GHC.Generics (Generic)
import NoThunks.Class (OnlyCheckWhnfNamed (..))
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Storage.Common
import Ouroboros.Consensus.Storage.ImmutableDB.Chunks.Internal
import Ouroboros.Consensus.Util.CallStack
import Ouroboros.Consensus.Util.IOLike
import qualified Ouroboros.Network.AnchoredFragment as AF
import System.FS.API.Types (FsError, FsPath)
import System.FS.CRC (CRC)
type SecondaryOffset = Word32
data ImmutableDB m blk = ImmutableDB {
forall (m :: * -> *) blk. ImmutableDB m blk -> HasCallStack => m ()
closeDB_ :: HasCallStack => m ()
, forall (m :: * -> *) blk.
ImmutableDB m blk -> HasCallStack => STM m (WithOrigin (Tip blk))
getTip_ :: HasCallStack => STM m (WithOrigin (Tip blk))
, forall (m :: * -> *) blk.
ImmutableDB m blk
-> forall b.
HasCallStack =>
BlockComponent blk b
-> RealPoint blk -> m (Either (MissingBlock blk) b)
getBlockComponent_ ::
forall b. HasCallStack
=> BlockComponent blk b -> RealPoint blk -> m (Either (MissingBlock blk) b)
, forall (m :: * -> *) blk.
ImmutableDB m blk -> HasCallStack => blk -> m ()
appendBlock_
:: HasCallStack => blk -> m ()
, forall (m :: * -> *) blk.
ImmutableDB m blk
-> forall b.
HasCallStack =>
ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
stream_
:: forall b. HasCallStack
=> ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
}
deriving Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo)
Proxy (ImmutableDB m blk) -> String
(Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo))
-> (Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo))
-> (Proxy (ImmutableDB m blk) -> String)
-> NoThunks (ImmutableDB m blk)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *) blk.
Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo)
forall (m :: * -> *) blk. Proxy (ImmutableDB m blk) -> String
$cnoThunks :: forall (m :: * -> *) blk.
Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *) blk.
Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> ImmutableDB m blk -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall (m :: * -> *) blk. Proxy (ImmutableDB m blk) -> String
showTypeOf :: Proxy (ImmutableDB m blk) -> String
NoThunks via OnlyCheckWhnfNamed "ImmutableDB" (ImmutableDB m blk)
data Iterator m blk b = Iterator {
forall (m :: * -> *) blk b.
Iterator m blk b -> HasCallStack => m (IteratorResult b)
iteratorNext :: HasCallStack => m (IteratorResult b)
, forall (m :: * -> *) blk b.
Iterator m blk b -> HasCallStack => STM m (Maybe (RealPoint blk))
iteratorHasNext :: HasCallStack => STM m (Maybe (RealPoint blk))
, forall (m :: * -> *) blk b.
Iterator m blk b -> HasCallStack => m ()
iteratorClose :: HasCallStack => m ()
}
deriving ((forall a b. (a -> b) -> Iterator m blk a -> Iterator m blk b)
-> (forall a b. a -> Iterator m blk b -> Iterator m blk a)
-> Functor (Iterator m blk)
forall a b. a -> Iterator m blk b -> Iterator m blk a
forall a b. (a -> b) -> Iterator m blk a -> Iterator m blk b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (m :: * -> *) blk a b.
Functor m =>
a -> Iterator m blk b -> Iterator m blk a
forall (m :: * -> *) blk a b.
Functor m =>
(a -> b) -> Iterator m blk a -> Iterator m blk b
$cfmap :: forall (m :: * -> *) blk a b.
Functor m =>
(a -> b) -> Iterator m blk a -> Iterator m blk b
fmap :: forall a b. (a -> b) -> Iterator m blk a -> Iterator m blk b
$c<$ :: forall (m :: * -> *) blk a b.
Functor m =>
a -> Iterator m blk b -> Iterator m blk a
<$ :: forall a b. a -> Iterator m blk b -> Iterator m blk a
Functor)
deriving Context -> Iterator m blk b -> IO (Maybe ThunkInfo)
Proxy (Iterator m blk b) -> String
(Context -> Iterator m blk b -> IO (Maybe ThunkInfo))
-> (Context -> Iterator m blk b -> IO (Maybe ThunkInfo))
-> (Proxy (Iterator m blk b) -> String)
-> NoThunks (Iterator m blk b)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *) blk b.
Context -> Iterator m blk b -> IO (Maybe ThunkInfo)
forall (m :: * -> *) blk b. Proxy (Iterator m blk b) -> String
$cnoThunks :: forall (m :: * -> *) blk b.
Context -> Iterator m blk b -> IO (Maybe ThunkInfo)
noThunks :: Context -> Iterator m blk b -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *) blk b.
Context -> Iterator m blk b -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Iterator m blk b -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall (m :: * -> *) blk b. Proxy (Iterator m blk b) -> String
showTypeOf :: Proxy (Iterator m blk b) -> String
NoThunks via OnlyCheckWhnfNamed "Iterator" (Iterator m blk b)
traverseIterator ::
Monad m
=> (b -> m b')
-> Iterator m blk b
-> Iterator m blk b'
traverseIterator :: forall (m :: * -> *) b b' blk.
Monad m =>
(b -> m b') -> Iterator m blk b -> Iterator m blk b'
traverseIterator b -> m b'
f Iterator m blk b
itr = Iterator{
iteratorNext :: HasCallStack => m (IteratorResult b')
iteratorNext = Iterator m blk b -> HasCallStack => m (IteratorResult b)
forall (m :: * -> *) blk b.
Iterator m blk b -> HasCallStack => m (IteratorResult b)
iteratorNext Iterator m blk b
itr m (IteratorResult b)
-> (IteratorResult b -> m (IteratorResult b'))
-> m (IteratorResult b')
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (b -> m b') -> IteratorResult b -> m (IteratorResult b')
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IteratorResult a -> f (IteratorResult b)
traverse b -> m b'
f
, iteratorHasNext :: HasCallStack => STM m (Maybe (RealPoint blk))
iteratorHasNext = Iterator m blk b -> HasCallStack => STM m (Maybe (RealPoint blk))
forall (m :: * -> *) blk b.
Iterator m blk b -> HasCallStack => STM m (Maybe (RealPoint blk))
iteratorHasNext Iterator m blk b
itr
, iteratorClose :: HasCallStack => m ()
iteratorClose = Iterator m blk b -> HasCallStack => m ()
forall (m :: * -> *) blk b.
Iterator m blk b -> HasCallStack => m ()
iteratorClose Iterator m blk b
itr
}
data IteratorResult b
= IteratorExhausted
| IteratorResult b
deriving (Int -> IteratorResult b -> ShowS
[IteratorResult b] -> ShowS
IteratorResult b -> String
(Int -> IteratorResult b -> ShowS)
-> (IteratorResult b -> String)
-> ([IteratorResult b] -> ShowS)
-> Show (IteratorResult b)
forall b. Show b => Int -> IteratorResult b -> ShowS
forall b. Show b => [IteratorResult b] -> ShowS
forall b. Show b => IteratorResult b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall b. Show b => Int -> IteratorResult b -> ShowS
showsPrec :: Int -> IteratorResult b -> ShowS
$cshow :: forall b. Show b => IteratorResult b -> String
show :: IteratorResult b -> String
$cshowList :: forall b. Show b => [IteratorResult b] -> ShowS
showList :: [IteratorResult b] -> ShowS
Show, IteratorResult b -> IteratorResult b -> Bool
(IteratorResult b -> IteratorResult b -> Bool)
-> (IteratorResult b -> IteratorResult b -> Bool)
-> Eq (IteratorResult b)
forall b. Eq b => IteratorResult b -> IteratorResult b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall b. Eq b => IteratorResult b -> IteratorResult b -> Bool
== :: IteratorResult b -> IteratorResult b -> Bool
$c/= :: forall b. Eq b => IteratorResult b -> IteratorResult b -> Bool
/= :: IteratorResult b -> IteratorResult b -> Bool
Eq, (forall x. IteratorResult b -> Rep (IteratorResult b) x)
-> (forall x. Rep (IteratorResult b) x -> IteratorResult b)
-> Generic (IteratorResult b)
forall x. Rep (IteratorResult b) x -> IteratorResult b
forall x. IteratorResult b -> Rep (IteratorResult b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (IteratorResult b) x -> IteratorResult b
forall b x. IteratorResult b -> Rep (IteratorResult b) x
$cfrom :: forall b x. IteratorResult b -> Rep (IteratorResult b) x
from :: forall x. IteratorResult b -> Rep (IteratorResult b) x
$cto :: forall b x. Rep (IteratorResult b) x -> IteratorResult b
to :: forall x. Rep (IteratorResult b) x -> IteratorResult b
Generic, (forall a b. (a -> b) -> IteratorResult a -> IteratorResult b)
-> (forall a b. a -> IteratorResult b -> IteratorResult a)
-> Functor IteratorResult
forall a b. a -> IteratorResult b -> IteratorResult a
forall a b. (a -> b) -> IteratorResult a -> IteratorResult b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> IteratorResult a -> IteratorResult b
fmap :: forall a b. (a -> b) -> IteratorResult a -> IteratorResult b
$c<$ :: forall a b. a -> IteratorResult b -> IteratorResult a
<$ :: forall a b. a -> IteratorResult b -> IteratorResult a
Functor, (forall m. Monoid m => IteratorResult m -> m)
-> (forall m a. Monoid m => (a -> m) -> IteratorResult a -> m)
-> (forall m a. Monoid m => (a -> m) -> IteratorResult a -> m)
-> (forall a b. (a -> b -> b) -> b -> IteratorResult a -> b)
-> (forall a b. (a -> b -> b) -> b -> IteratorResult a -> b)
-> (forall b a. (b -> a -> b) -> b -> IteratorResult a -> b)
-> (forall b a. (b -> a -> b) -> b -> IteratorResult a -> b)
-> (forall a. (a -> a -> a) -> IteratorResult a -> a)
-> (forall a. (a -> a -> a) -> IteratorResult a -> a)
-> (forall a. IteratorResult a -> [a])
-> (forall a. IteratorResult a -> Bool)
-> (forall a. IteratorResult a -> Int)
-> (forall a. Eq a => a -> IteratorResult a -> Bool)
-> (forall a. Ord a => IteratorResult a -> a)
-> (forall a. Ord a => IteratorResult a -> a)
-> (forall a. Num a => IteratorResult a -> a)
-> (forall a. Num a => IteratorResult a -> a)
-> Foldable IteratorResult
forall a. Eq a => a -> IteratorResult a -> Bool
forall a. Num a => IteratorResult a -> a
forall a. Ord a => IteratorResult a -> a
forall m. Monoid m => IteratorResult m -> m
forall a. IteratorResult a -> Bool
forall a. IteratorResult a -> Int
forall a. IteratorResult a -> [a]
forall a. (a -> a -> a) -> IteratorResult a -> a
forall m a. Monoid m => (a -> m) -> IteratorResult a -> m
forall b a. (b -> a -> b) -> b -> IteratorResult a -> b
forall a b. (a -> b -> b) -> b -> IteratorResult a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => IteratorResult m -> m
fold :: forall m. Monoid m => IteratorResult m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> IteratorResult a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IteratorResult a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> IteratorResult a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> IteratorResult a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> IteratorResult a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IteratorResult a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> IteratorResult a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IteratorResult a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> IteratorResult a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IteratorResult a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> IteratorResult a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> IteratorResult a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> IteratorResult a -> a
foldr1 :: forall a. (a -> a -> a) -> IteratorResult a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> IteratorResult a -> a
foldl1 :: forall a. (a -> a -> a) -> IteratorResult a -> a
$ctoList :: forall a. IteratorResult a -> [a]
toList :: forall a. IteratorResult a -> [a]
$cnull :: forall a. IteratorResult a -> Bool
null :: forall a. IteratorResult a -> Bool
$clength :: forall a. IteratorResult a -> Int
length :: forall a. IteratorResult a -> Int
$celem :: forall a. Eq a => a -> IteratorResult a -> Bool
elem :: forall a. Eq a => a -> IteratorResult a -> Bool
$cmaximum :: forall a. Ord a => IteratorResult a -> a
maximum :: forall a. Ord a => IteratorResult a -> a
$cminimum :: forall a. Ord a => IteratorResult a -> a
minimum :: forall a. Ord a => IteratorResult a -> a
$csum :: forall a. Num a => IteratorResult a -> a
sum :: forall a. Num a => IteratorResult a -> a
$cproduct :: forall a. Num a => IteratorResult a -> a
product :: forall a. Num a => IteratorResult a -> a
Foldable, Functor IteratorResult
Foldable IteratorResult
(Functor IteratorResult, Foldable IteratorResult) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IteratorResult a -> f (IteratorResult b))
-> (forall (f :: * -> *) a.
Applicative f =>
IteratorResult (f a) -> f (IteratorResult a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IteratorResult a -> m (IteratorResult b))
-> (forall (m :: * -> *) a.
Monad m =>
IteratorResult (m a) -> m (IteratorResult a))
-> Traversable IteratorResult
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
IteratorResult (m a) -> m (IteratorResult a)
forall (f :: * -> *) a.
Applicative f =>
IteratorResult (f a) -> f (IteratorResult a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IteratorResult a -> m (IteratorResult b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IteratorResult a -> f (IteratorResult b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IteratorResult a -> f (IteratorResult b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IteratorResult a -> f (IteratorResult b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
IteratorResult (f a) -> f (IteratorResult a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IteratorResult (f a) -> f (IteratorResult a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IteratorResult a -> m (IteratorResult b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IteratorResult a -> m (IteratorResult b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
IteratorResult (m a) -> m (IteratorResult a)
sequence :: forall (m :: * -> *) a.
Monad m =>
IteratorResult (m a) -> m (IteratorResult a)
Traversable)
iteratorToList :: (HasCallStack, Monad m)
=> Iterator m blk b -> m [b]
iteratorToList :: forall (m :: * -> *) blk b.
(HasCallStack, Monad m) =>
Iterator m blk b -> m [b]
iteratorToList Iterator m blk b
it = [b] -> m [b]
go []
where
go :: [b] -> m [b]
go [b]
acc = do
IteratorResult b
next <- Iterator m blk b -> HasCallStack => m (IteratorResult b)
forall (m :: * -> *) blk b.
Iterator m blk b -> HasCallStack => m (IteratorResult b)
iteratorNext Iterator m blk b
it
case IteratorResult b
next of
IteratorResult b
IteratorExhausted -> [b] -> m [b]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([b] -> m [b]) -> [b] -> m [b]
forall a b. (a -> b) -> a -> b
$ [b] -> [b]
forall a. [a] -> [a]
reverse [b]
acc
IteratorResult b
res -> [b] -> m [b]
go (b
resb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
acc)
emptyIterator :: MonadSTM m => Iterator m blk b
emptyIterator :: forall (m :: * -> *) blk b. MonadSTM m => Iterator m blk b
emptyIterator = Iterator {
iteratorNext :: HasCallStack => m (IteratorResult b)
iteratorNext = IteratorResult b -> m (IteratorResult b)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return IteratorResult b
forall b. IteratorResult b
IteratorExhausted
, iteratorHasNext :: HasCallStack => STM m (Maybe (RealPoint blk))
iteratorHasNext = Maybe (RealPoint blk) -> STM m (Maybe (RealPoint blk))
forall a. a -> STM m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (RealPoint blk)
forall a. Maybe a
Nothing
, iteratorClose :: HasCallStack => m ()
iteratorClose = () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
}
data Tip blk = Tip {
forall blk. Tip blk -> SlotNo
tipSlotNo :: !SlotNo
, forall blk. Tip blk -> IsEBB
tipIsEBB :: !IsEBB
, forall blk. Tip blk -> BlockNo
tipBlockNo :: !BlockNo
, forall blk. Tip blk -> HeaderHash blk
tipHash :: !(HeaderHash blk)
}
deriving ((forall x. Tip blk -> Rep (Tip blk) x)
-> (forall x. Rep (Tip blk) x -> Tip blk) -> Generic (Tip blk)
forall x. Rep (Tip blk) x -> Tip blk
forall x. Tip blk -> Rep (Tip blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (Tip blk) x -> Tip blk
forall blk x. Tip blk -> Rep (Tip blk) x
$cfrom :: forall blk x. Tip blk -> Rep (Tip blk) x
from :: forall x. Tip blk -> Rep (Tip blk) x
$cto :: forall blk x. Rep (Tip blk) x -> Tip blk
to :: forall x. Rep (Tip blk) x -> Tip blk
Generic)
deriving instance StandardHash blk => Eq (Tip blk)
deriving instance StandardHash blk => Show (Tip blk)
deriving instance StandardHash blk => NoThunks (Tip blk)
tipToRealPoint :: Tip blk -> RealPoint blk
tipToRealPoint :: forall blk. Tip blk -> RealPoint blk
tipToRealPoint Tip { SlotNo
tipSlotNo :: forall blk. Tip blk -> SlotNo
tipSlotNo :: SlotNo
tipSlotNo, HeaderHash blk
tipHash :: forall blk. Tip blk -> HeaderHash blk
tipHash :: HeaderHash blk
tipHash } = SlotNo -> HeaderHash blk -> RealPoint blk
forall blk. SlotNo -> HeaderHash blk -> RealPoint blk
RealPoint SlotNo
tipSlotNo HeaderHash blk
tipHash
tipToPoint :: WithOrigin (Tip blk) -> Point blk
tipToPoint :: forall blk. WithOrigin (Tip blk) -> Point blk
tipToPoint = \case
WithOrigin (Tip blk)
Origin -> Point blk
forall {k} (block :: k). Point block
GenesisPoint
NotOrigin Tip blk
tip -> RealPoint blk -> Point blk
forall blk. RealPoint blk -> Point blk
realPointToPoint (RealPoint blk -> Point blk) -> RealPoint blk -> Point blk
forall a b. (a -> b) -> a -> b
$ Tip blk -> RealPoint blk
forall blk. Tip blk -> RealPoint blk
tipToRealPoint Tip blk
tip
tipToAnchor :: WithOrigin (Tip blk) -> AF.Anchor blk
tipToAnchor :: forall blk. WithOrigin (Tip blk) -> Anchor blk
tipToAnchor = \case
WithOrigin (Tip blk)
Origin ->
Anchor blk
forall block. Anchor block
AF.AnchorGenesis
NotOrigin (Tip { SlotNo
tipSlotNo :: forall blk. Tip blk -> SlotNo
tipSlotNo :: SlotNo
tipSlotNo, HeaderHash blk
tipHash :: forall blk. Tip blk -> HeaderHash blk
tipHash :: HeaderHash blk
tipHash, BlockNo
tipBlockNo :: forall blk. Tip blk -> BlockNo
tipBlockNo :: BlockNo
tipBlockNo }) ->
SlotNo -> HeaderHash blk -> BlockNo -> Anchor blk
forall block. SlotNo -> HeaderHash block -> BlockNo -> Anchor block
AF.Anchor SlotNo
tipSlotNo HeaderHash blk
tipHash BlockNo
tipBlockNo
headerToTip :: GetHeader blk => Header blk -> Tip blk
Header blk
hdr = Tip {
tipSlotNo :: SlotNo
tipSlotNo = Header blk -> SlotNo
forall b. HasHeader b => b -> SlotNo
blockSlot Header blk
hdr
, tipIsEBB :: IsEBB
tipIsEBB = Header blk -> IsEBB
forall blk. GetHeader blk => Header blk -> IsEBB
headerToIsEBB Header blk
hdr
, tipBlockNo :: BlockNo
tipBlockNo = Header blk -> BlockNo
forall b. HasHeader b => b -> BlockNo
blockNo Header blk
hdr
, tipHash :: HeaderHash blk
tipHash = Header blk -> HeaderHash (Header blk)
forall b. HasHeader b => b -> HeaderHash b
blockHash Header blk
hdr
}
blockToTip :: GetHeader blk => blk -> Tip blk
blockToTip :: forall blk. GetHeader blk => blk -> Tip blk
blockToTip = Header blk -> Tip blk
forall blk. GetHeader blk => Header blk -> Tip blk
headerToTip (Header blk -> Tip blk) -> (blk -> Header blk) -> blk -> Tip blk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. blk -> Header blk
forall blk. GetHeader blk => blk -> Header blk
getHeader
newtype CompareTip blk = CompareTip { forall blk. CompareTip blk -> Tip blk
getCompareTip :: Tip blk }
instance Eq (CompareTip blk) where
CompareTip blk
a == :: CompareTip blk -> CompareTip blk -> Bool
== CompareTip blk
b = CompareTip blk -> CompareTip blk -> Ordering
forall a. Ord a => a -> a -> Ordering
compare CompareTip blk
a CompareTip blk
b Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ
instance Ord (CompareTip blk) where
compare :: CompareTip blk -> CompareTip blk -> Ordering
compare = [CompareTip blk -> CompareTip blk -> Ordering]
-> CompareTip blk -> CompareTip blk -> Ordering
forall a. Monoid a => [a] -> a
mconcat [
SlotNo -> SlotNo -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (SlotNo -> SlotNo -> Ordering)
-> (CompareTip blk -> SlotNo)
-> CompareTip blk
-> CompareTip blk
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Tip blk -> SlotNo
forall blk. Tip blk -> SlotNo
tipSlotNo (Tip blk -> SlotNo)
-> (CompareTip blk -> Tip blk) -> CompareTip blk -> SlotNo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompareTip blk -> Tip blk
forall blk. CompareTip blk -> Tip blk
getCompareTip
, IsEBB -> IsEBB -> Ordering
compareIsEBB (IsEBB -> IsEBB -> Ordering)
-> (CompareTip blk -> IsEBB)
-> CompareTip blk
-> CompareTip blk
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Tip blk -> IsEBB
forall blk. Tip blk -> IsEBB
tipIsEBB (Tip blk -> IsEBB)
-> (CompareTip blk -> Tip blk) -> CompareTip blk -> IsEBB
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompareTip blk -> Tip blk
forall blk. CompareTip blk -> Tip blk
getCompareTip
]
where
compareIsEBB :: IsEBB -> IsEBB -> Ordering
compareIsEBB :: IsEBB -> IsEBB -> Ordering
compareIsEBB IsEBB
IsEBB IsEBB
IsNotEBB = Ordering
LT
compareIsEBB IsEBB
IsNotEBB IsEBB
IsEBB = Ordering
GT
compareIsEBB IsEBB
_ IsEBB
_ = Ordering
EQ
data ImmutableDBError blk =
ApiMisuse (ApiMisuse blk) PrettyCallStack
| UnexpectedFailure (UnexpectedFailure blk)
deriving ((forall x. ImmutableDBError blk -> Rep (ImmutableDBError blk) x)
-> (forall x. Rep (ImmutableDBError blk) x -> ImmutableDBError blk)
-> Generic (ImmutableDBError blk)
forall x. Rep (ImmutableDBError blk) x -> ImmutableDBError blk
forall x. ImmutableDBError blk -> Rep (ImmutableDBError blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (ImmutableDBError blk) x -> ImmutableDBError blk
forall blk x. ImmutableDBError blk -> Rep (ImmutableDBError blk) x
$cfrom :: forall blk x. ImmutableDBError blk -> Rep (ImmutableDBError blk) x
from :: forall x. ImmutableDBError blk -> Rep (ImmutableDBError blk) x
$cto :: forall blk x. Rep (ImmutableDBError blk) x -> ImmutableDBError blk
to :: forall x. Rep (ImmutableDBError blk) x -> ImmutableDBError blk
Generic, Int -> ImmutableDBError blk -> ShowS
[ImmutableDBError blk] -> ShowS
ImmutableDBError blk -> String
(Int -> ImmutableDBError blk -> ShowS)
-> (ImmutableDBError blk -> String)
-> ([ImmutableDBError blk] -> ShowS)
-> Show (ImmutableDBError blk)
forall blk.
(StandardHash blk, Typeable blk) =>
Int -> ImmutableDBError blk -> ShowS
forall blk.
(StandardHash blk, Typeable blk) =>
[ImmutableDBError blk] -> ShowS
forall blk.
(StandardHash blk, Typeable blk) =>
ImmutableDBError blk -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall blk.
(StandardHash blk, Typeable blk) =>
Int -> ImmutableDBError blk -> ShowS
showsPrec :: Int -> ImmutableDBError blk -> ShowS
$cshow :: forall blk.
(StandardHash blk, Typeable blk) =>
ImmutableDBError blk -> String
show :: ImmutableDBError blk -> String
$cshowList :: forall blk.
(StandardHash blk, Typeable blk) =>
[ImmutableDBError blk] -> ShowS
showList :: [ImmutableDBError blk] -> ShowS
Show)
instance (StandardHash blk, Typeable blk)
=> Exception (ImmutableDBError blk) where
displayException :: ImmutableDBError blk -> String
displayException = \case
ApiMisuse {} ->
String
"ImmutableDB incorrectly used, indicative of a bug"
UnexpectedFailure (FileSystemError FsError
fse) ->
FsError -> String
forall e. Exception e => e -> String
displayException FsError
fse
UnexpectedFailure {} ->
String
"The ImmutableDB got corrupted, full validation will be enabled for the next startup"
data ApiMisuse blk =
AppendBlockNotNewerThanTipError (RealPoint blk) (Point blk)
| InvalidIteratorRangeError (StreamFrom blk) (StreamTo blk)
| ClosedDBError
| OpenDBError
deriving instance (StandardHash blk, Typeable blk) => Show (ApiMisuse blk)
throwApiMisuse ::
(MonadThrow m, HasCallStack, StandardHash blk, Typeable blk)
=> ApiMisuse blk -> m a
throwApiMisuse :: forall (m :: * -> *) blk a.
(MonadThrow m, HasCallStack, StandardHash blk, Typeable blk) =>
ApiMisuse blk -> m a
throwApiMisuse ApiMisuse blk
e = ImmutableDBError blk -> m a
forall e a. Exception e => e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ImmutableDBError blk -> m a) -> ImmutableDBError blk -> m a
forall a b. (a -> b) -> a -> b
$ ApiMisuse blk -> PrettyCallStack -> ImmutableDBError blk
forall blk.
ApiMisuse blk -> PrettyCallStack -> ImmutableDBError blk
ApiMisuse ApiMisuse blk
e PrettyCallStack
HasCallStack => PrettyCallStack
prettyCallStack
data UnexpectedFailure blk =
FileSystemError FsError
| InvalidFileError FsPath String PrettyCallStack
| MissingFileError FsPath PrettyCallStack
| ChecksumMismatchError (RealPoint blk) CRC CRC FsPath PrettyCallStack
| ParseError FsPath (RealPoint blk) CBOR.DeserialiseFailure
| TrailingDataError FsPath (RealPoint blk) Lazy.ByteString
| MissingBlockError (MissingBlock blk)
| CorruptBlockError (RealPoint blk)
deriving instance (StandardHash blk, Typeable blk) => Show (UnexpectedFailure blk)
throwUnexpectedFailure ::
(StandardHash blk, Typeable blk, MonadThrow m)
=> UnexpectedFailure blk -> m a
throwUnexpectedFailure :: forall blk (m :: * -> *) a.
(StandardHash blk, Typeable blk, MonadThrow m) =>
UnexpectedFailure blk -> m a
throwUnexpectedFailure = ImmutableDBError blk -> m a
forall e a. Exception e => e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ImmutableDBError blk -> m a)
-> (UnexpectedFailure blk -> ImmutableDBError blk)
-> UnexpectedFailure blk
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnexpectedFailure blk -> ImmutableDBError blk
forall blk. UnexpectedFailure blk -> ImmutableDBError blk
UnexpectedFailure
data MissingBlock blk
= EmptySlot
(RealPoint blk)
ChunkNo
[RelativeSlot]
(Maybe (StrictSeq SecondaryOffset))
| WrongHash (RealPoint blk) (NonEmpty (HeaderHash blk))
| NewerThanTip (RealPoint blk) (Point blk)
deriving (MissingBlock blk -> MissingBlock blk -> Bool
(MissingBlock blk -> MissingBlock blk -> Bool)
-> (MissingBlock blk -> MissingBlock blk -> Bool)
-> Eq (MissingBlock blk)
forall blk.
StandardHash blk =>
MissingBlock blk -> MissingBlock blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall blk.
StandardHash blk =>
MissingBlock blk -> MissingBlock blk -> Bool
== :: MissingBlock blk -> MissingBlock blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
MissingBlock blk -> MissingBlock blk -> Bool
/= :: MissingBlock blk -> MissingBlock blk -> Bool
Eq, Int -> MissingBlock blk -> ShowS
[MissingBlock blk] -> ShowS
MissingBlock blk -> String
(Int -> MissingBlock blk -> ShowS)
-> (MissingBlock blk -> String)
-> ([MissingBlock blk] -> ShowS)
-> Show (MissingBlock blk)
forall blk. StandardHash blk => Int -> MissingBlock blk -> ShowS
forall blk. StandardHash blk => [MissingBlock blk] -> ShowS
forall blk. StandardHash blk => MissingBlock blk -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall blk. StandardHash blk => Int -> MissingBlock blk -> ShowS
showsPrec :: Int -> MissingBlock blk -> ShowS
$cshow :: forall blk. StandardHash blk => MissingBlock blk -> String
show :: MissingBlock blk -> String
$cshowList :: forall blk. StandardHash blk => [MissingBlock blk] -> ShowS
showList :: [MissingBlock blk] -> ShowS
Show, (forall x. MissingBlock blk -> Rep (MissingBlock blk) x)
-> (forall x. Rep (MissingBlock blk) x -> MissingBlock blk)
-> Generic (MissingBlock blk)
forall x. Rep (MissingBlock blk) x -> MissingBlock blk
forall x. MissingBlock blk -> Rep (MissingBlock blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (MissingBlock blk) x -> MissingBlock blk
forall blk x. MissingBlock blk -> Rep (MissingBlock blk) x
$cfrom :: forall blk x. MissingBlock blk -> Rep (MissingBlock blk) x
from :: forall x. MissingBlock blk -> Rep (MissingBlock blk) x
$cto :: forall blk x. Rep (MissingBlock blk) x -> MissingBlock blk
to :: forall x. Rep (MissingBlock blk) x -> MissingBlock blk
Generic)
missingBlockPoint :: MissingBlock blk -> RealPoint blk
missingBlockPoint :: forall blk. MissingBlock blk -> RealPoint blk
missingBlockPoint (EmptySlot RealPoint blk
pt ChunkNo
_ [RelativeSlot]
_ Maybe (StrictSeq SecondaryOffset)
_) = RealPoint blk
pt
missingBlockPoint (WrongHash RealPoint blk
pt NonEmpty (HeaderHash blk)
_) = RealPoint blk
pt
missingBlockPoint (NewerThanTip RealPoint blk
pt Point blk
_) = RealPoint blk
pt
closeDB ::
HasCallStack
=> ImmutableDB m blk
-> m ()
closeDB :: forall (m :: * -> *) blk. HasCallStack => ImmutableDB m blk -> m ()
closeDB = ImmutableDB m blk -> m ()
ImmutableDB m blk -> HasCallStack => m ()
forall (m :: * -> *) blk. ImmutableDB m blk -> HasCallStack => m ()
closeDB_
getTip ::
HasCallStack
=> ImmutableDB m blk
-> STM m (WithOrigin (Tip blk))
getTip :: forall (m :: * -> *) blk.
HasCallStack =>
ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
getTip = ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
ImmutableDB m blk -> HasCallStack => STM m (WithOrigin (Tip blk))
forall (m :: * -> *) blk.
ImmutableDB m blk -> HasCallStack => STM m (WithOrigin (Tip blk))
getTip_
getBlockComponent ::
HasCallStack
=> ImmutableDB m blk
-> BlockComponent blk b -> RealPoint blk -> m (Either (MissingBlock blk) b)
getBlockComponent :: forall (m :: * -> *) blk b.
HasCallStack =>
ImmutableDB m blk
-> BlockComponent blk b
-> RealPoint blk
-> m (Either (MissingBlock blk) b)
getBlockComponent = ImmutableDB m blk
-> BlockComponent blk b
-> RealPoint blk
-> m (Either (MissingBlock blk) b)
ImmutableDB m blk
-> forall b.
HasCallStack =>
BlockComponent blk b
-> RealPoint blk -> m (Either (MissingBlock blk) b)
forall (m :: * -> *) blk.
ImmutableDB m blk
-> forall b.
HasCallStack =>
BlockComponent blk b
-> RealPoint blk -> m (Either (MissingBlock blk) b)
getBlockComponent_
appendBlock ::
HasCallStack
=> ImmutableDB m blk
-> blk -> m ()
appendBlock :: forall (m :: * -> *) blk.
HasCallStack =>
ImmutableDB m blk -> blk -> m ()
appendBlock = ImmutableDB m blk -> blk -> m ()
ImmutableDB m blk -> HasCallStack => blk -> m ()
forall (m :: * -> *) blk.
ImmutableDB m blk -> HasCallStack => blk -> m ()
appendBlock_
stream ::
HasCallStack
=> ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
stream :: forall (m :: * -> *) blk b.
HasCallStack =>
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
stream = ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
ImmutableDB m blk
-> forall b.
HasCallStack =>
ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
forall (m :: * -> *) blk.
ImmutableDB m blk
-> forall b.
HasCallStack =>
ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
stream_
withDB ::
(HasCallStack, MonadThrow m)
=> m (ImmutableDB m blk)
-> (ImmutableDB m blk -> m a)
-> m a
withDB :: forall (m :: * -> *) blk a.
(HasCallStack, MonadThrow m) =>
m (ImmutableDB m blk) -> (ImmutableDB m blk -> m a) -> m a
withDB m (ImmutableDB m blk)
openDB = m (ImmutableDB m blk)
-> (ImmutableDB m blk -> m ()) -> (ImmutableDB m blk -> m a) -> m a
forall a b c. m a -> (a -> m b) -> (a -> m c) -> m c
forall (m :: * -> *) a b c.
MonadThrow m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket m (ImmutableDB m blk)
openDB ImmutableDB m blk -> m ()
forall (m :: * -> *) blk. HasCallStack => ImmutableDB m blk -> m ()
closeDB
getKnownBlockComponent ::
(MonadThrow m, HasHeader blk)
=> ImmutableDB m blk
-> BlockComponent blk b
-> RealPoint blk
-> m b
getKnownBlockComponent :: forall (m :: * -> *) blk b.
(MonadThrow m, HasHeader blk) =>
ImmutableDB m blk -> BlockComponent blk b -> RealPoint blk -> m b
getKnownBlockComponent ImmutableDB m blk
db BlockComponent blk b
blockComponent RealPoint blk
pt =
ImmutableDB m blk
-> BlockComponent blk b
-> RealPoint blk
-> m (Either (MissingBlock blk) b)
forall (m :: * -> *) blk b.
HasCallStack =>
ImmutableDB m blk
-> BlockComponent blk b
-> RealPoint blk
-> m (Either (MissingBlock blk) b)
getBlockComponent ImmutableDB m blk
db BlockComponent blk b
blockComponent RealPoint blk
pt m (Either (MissingBlock blk) b)
-> (Either (MissingBlock blk) b -> m b) -> m b
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left MissingBlock blk
missing -> UnexpectedFailure blk -> m b
forall blk (m :: * -> *) a.
(StandardHash blk, Typeable blk, MonadThrow m) =>
UnexpectedFailure blk -> m a
throwUnexpectedFailure (UnexpectedFailure blk -> m b) -> UnexpectedFailure blk -> m b
forall a b. (a -> b) -> a -> b
$ MissingBlock blk -> UnexpectedFailure blk
forall blk. MissingBlock blk -> UnexpectedFailure blk
MissingBlockError MissingBlock blk
missing
Right b
b -> b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return b
b
streamAfterPoint ::
(MonadSTM m, HasHeader blk, HasCallStack)
=> ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
streamAfterPoint :: forall (m :: * -> *) blk b.
(MonadSTM m, HasHeader blk, HasCallStack) =>
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
streamAfterPoint ImmutableDB m blk
db ResourceRegistry m
registry BlockComponent blk b
blockComponent Point blk
fromPt = ExceptT (MissingBlock blk) m (Iterator m blk b)
-> m (Either (MissingBlock blk) (Iterator m blk b))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (MissingBlock blk) m (Iterator m blk b)
-> m (Either (MissingBlock blk) (Iterator m blk b)))
-> ExceptT (MissingBlock blk) m (Iterator m blk b)
-> m (Either (MissingBlock blk) (Iterator m blk b))
forall a b. (a -> b) -> a -> b
$ do
Point blk
tipPt <- m (Point blk) -> ExceptT (MissingBlock blk) m (Point blk)
forall (m :: * -> *) a.
Monad m =>
m a -> ExceptT (MissingBlock blk) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Point blk) -> ExceptT (MissingBlock blk) m (Point blk))
-> m (Point blk) -> ExceptT (MissingBlock blk) m (Point blk)
forall a b. (a -> b) -> a -> b
$ STM m (Point blk) -> m (Point blk)
forall a. HasCallStack => STM m a -> m a
forall (m :: * -> *) a.
(MonadSTM m, HasCallStack) =>
STM m a -> m a
atomically (STM m (Point blk) -> m (Point blk))
-> STM m (Point blk) -> m (Point blk)
forall a b. (a -> b) -> a -> b
$ ImmutableDB m blk -> STM m (Point blk)
forall (m :: * -> *) blk.
(MonadSTM m, HasCallStack) =>
ImmutableDB m blk -> STM m (Point blk)
getTipPoint ImmutableDB m blk
db
case (Point blk -> WithOrigin (RealPoint blk)
forall blk. Point blk -> WithOrigin (RealPoint blk)
pointToWithOriginRealPoint Point blk
fromPt,
Point blk -> WithOrigin (RealPoint blk)
forall blk. Point blk -> WithOrigin (RealPoint blk)
pointToWithOriginRealPoint Point blk
tipPt) of
(WithOrigin (RealPoint blk)
Origin, WithOrigin (RealPoint blk)
Origin) ->
Iterator m blk b -> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall a. a -> ExceptT (MissingBlock blk) m a
forall (m :: * -> *) a. Monad m => a -> m a
return Iterator m blk b
forall (m :: * -> *) blk b. MonadSTM m => Iterator m blk b
emptyIterator
(NotOrigin RealPoint blk
fromPt', WithOrigin (RealPoint blk)
Origin) ->
MissingBlock blk -> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall a. MissingBlock blk -> ExceptT (MissingBlock blk) m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (MissingBlock blk
-> ExceptT (MissingBlock blk) m (Iterator m blk b))
-> MissingBlock blk
-> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall a b. (a -> b) -> a -> b
$ RealPoint blk -> Point blk -> MissingBlock blk
forall blk. RealPoint blk -> Point blk -> MissingBlock blk
NewerThanTip RealPoint blk
fromPt' Point blk
forall {k} (block :: k). Point block
GenesisPoint
(NotOrigin RealPoint blk
fromPt', NotOrigin RealPoint blk
_) | Point blk -> WithOrigin SlotNo
forall {k} (block :: k). Point block -> WithOrigin SlotNo
pointSlot Point blk
fromPt WithOrigin SlotNo -> WithOrigin SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
> Point blk -> WithOrigin SlotNo
forall {k} (block :: k). Point block -> WithOrigin SlotNo
pointSlot Point blk
tipPt ->
MissingBlock blk -> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall a. MissingBlock blk -> ExceptT (MissingBlock blk) m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (MissingBlock blk
-> ExceptT (MissingBlock blk) m (Iterator m blk b))
-> MissingBlock blk
-> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall a b. (a -> b) -> a -> b
$ RealPoint blk -> Point blk -> MissingBlock blk
forall blk. RealPoint blk -> Point blk -> MissingBlock blk
NewerThanTip RealPoint blk
fromPt' Point blk
tipPt
(NotOrigin RealPoint blk
fromPt', NotOrigin RealPoint blk
tipPt') | RealPoint blk
fromPt' RealPoint blk -> RealPoint blk -> Bool
forall a. Eq a => a -> a -> Bool
== RealPoint blk
tipPt' ->
Iterator m blk b -> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall a. a -> ExceptT (MissingBlock blk) m a
forall (m :: * -> *) a. Monad m => a -> m a
return Iterator m blk b
forall (m :: * -> *) blk b. MonadSTM m => Iterator m blk b
emptyIterator
(WithOrigin (RealPoint blk)
_, NotOrigin RealPoint blk
tipPt') ->
m (Either (MissingBlock blk) (Iterator m blk b))
-> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either (MissingBlock blk) (Iterator m blk b))
-> ExceptT (MissingBlock blk) m (Iterator m blk b))
-> m (Either (MissingBlock blk) (Iterator m blk b))
-> ExceptT (MissingBlock blk) m (Iterator m blk b)
forall a b. (a -> b) -> a -> b
$ ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
forall (m :: * -> *) blk b.
HasCallStack =>
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> StreamFrom blk
-> StreamTo blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
stream
ImmutableDB m blk
db
ResourceRegistry m
registry
BlockComponent blk b
blockComponent
(Point blk -> StreamFrom blk
forall blk. Point blk -> StreamFrom blk
StreamFromExclusive Point blk
fromPt)
(RealPoint blk -> StreamTo blk
forall blk. RealPoint blk -> StreamTo blk
StreamToInclusive RealPoint blk
tipPt')
streamAfterKnownPoint ::
(MonadSTM m, MonadThrow m, HasHeader blk, HasCallStack)
=> ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Iterator m blk b)
streamAfterKnownPoint :: forall (m :: * -> *) blk b.
(MonadSTM m, MonadThrow m, HasHeader blk, HasCallStack) =>
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Iterator m blk b)
streamAfterKnownPoint ImmutableDB m blk
db ResourceRegistry m
registry BlockComponent blk b
blockComponent Point blk
fromPt =
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
forall (m :: * -> *) blk b.
(MonadSTM m, HasHeader blk, HasCallStack) =>
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Either (MissingBlock blk) (Iterator m blk b))
streamAfterPoint ImmutableDB m blk
db ResourceRegistry m
registry BlockComponent blk b
blockComponent Point blk
fromPt m (Either (MissingBlock blk) (Iterator m blk b))
-> (Either (MissingBlock blk) (Iterator m blk b)
-> m (Iterator m blk b))
-> m (Iterator m blk b)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(MissingBlock blk -> m (Iterator m blk b))
-> (Iterator m blk b -> m (Iterator m blk b))
-> Either (MissingBlock blk) (Iterator m blk b)
-> m (Iterator m blk b)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (UnexpectedFailure blk -> m (Iterator m blk b)
forall blk (m :: * -> *) a.
(StandardHash blk, Typeable blk, MonadThrow m) =>
UnexpectedFailure blk -> m a
throwUnexpectedFailure (UnexpectedFailure blk -> m (Iterator m blk b))
-> (MissingBlock blk -> UnexpectedFailure blk)
-> MissingBlock blk
-> m (Iterator m blk b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MissingBlock blk -> UnexpectedFailure blk
forall blk. MissingBlock blk -> UnexpectedFailure blk
MissingBlockError) Iterator m blk b -> m (Iterator m blk b)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
streamAll ::
(MonadSTM m, MonadThrow m, HasHeader blk, HasCallStack)
=> ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> m (Iterator m blk b)
streamAll :: forall (m :: * -> *) blk b.
(MonadSTM m, MonadThrow m, HasHeader blk, HasCallStack) =>
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> m (Iterator m blk b)
streamAll ImmutableDB m blk
db ResourceRegistry m
registry BlockComponent blk b
blockComponent =
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Iterator m blk b)
forall (m :: * -> *) blk b.
(MonadSTM m, MonadThrow m, HasHeader blk, HasCallStack) =>
ImmutableDB m blk
-> ResourceRegistry m
-> BlockComponent blk b
-> Point blk
-> m (Iterator m blk b)
streamAfterKnownPoint ImmutableDB m blk
db ResourceRegistry m
registry BlockComponent blk b
blockComponent Point blk
forall {k} (block :: k). Point block
GenesisPoint
hasBlock ::
(MonadSTM m, HasCallStack)
=> ImmutableDB m blk
-> RealPoint blk
-> m Bool
hasBlock :: forall (m :: * -> *) blk.
(MonadSTM m, HasCallStack) =>
ImmutableDB m blk -> RealPoint blk -> m Bool
hasBlock ImmutableDB m blk
db RealPoint blk
pt = Either (MissingBlock blk) () -> Bool
forall a b. Either a b -> Bool
isRight (Either (MissingBlock blk) () -> Bool)
-> m (Either (MissingBlock blk) ()) -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ImmutableDB m blk
-> BlockComponent blk ()
-> RealPoint blk
-> m (Either (MissingBlock blk) ())
forall (m :: * -> *) blk b.
HasCallStack =>
ImmutableDB m blk
-> BlockComponent blk b
-> RealPoint blk
-> m (Either (MissingBlock blk) b)
getBlockComponent ImmutableDB m blk
db (() -> BlockComponent blk ()
forall a. a -> BlockComponent blk a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) RealPoint blk
pt
getTipPoint ::
(MonadSTM m, HasCallStack)
=> ImmutableDB m blk -> STM m (Point blk)
getTipPoint :: forall (m :: * -> *) blk.
(MonadSTM m, HasCallStack) =>
ImmutableDB m blk -> STM m (Point blk)
getTipPoint = (WithOrigin (Tip blk) -> Point blk)
-> STM m (WithOrigin (Tip blk)) -> STM m (Point blk)
forall a b. (a -> b) -> STM m a -> STM m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap WithOrigin (Tip blk) -> Point blk
forall blk. WithOrigin (Tip blk) -> Point blk
tipToPoint (STM m (WithOrigin (Tip blk)) -> STM m (Point blk))
-> (ImmutableDB m blk -> STM m (WithOrigin (Tip blk)))
-> ImmutableDB m blk
-> STM m (Point blk)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
forall (m :: * -> *) blk.
HasCallStack =>
ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
getTip
getTipAnchor ::
(MonadSTM m, HasCallStack)
=> ImmutableDB m blk -> STM m (AF.Anchor blk)
getTipAnchor :: forall (m :: * -> *) blk.
(MonadSTM m, HasCallStack) =>
ImmutableDB m blk -> STM m (Anchor blk)
getTipAnchor = (WithOrigin (Tip blk) -> Anchor blk)
-> STM m (WithOrigin (Tip blk)) -> STM m (Anchor blk)
forall a b. (a -> b) -> STM m a -> STM m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap WithOrigin (Tip blk) -> Anchor blk
forall blk. WithOrigin (Tip blk) -> Anchor blk
tipToAnchor (STM m (WithOrigin (Tip blk)) -> STM m (Anchor blk))
-> (ImmutableDB m blk -> STM m (WithOrigin (Tip blk)))
-> ImmutableDB m blk
-> STM m (Anchor blk)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
forall (m :: * -> *) blk.
HasCallStack =>
ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
getTip
getTipSlot ::
(MonadSTM m, HasCallStack)
=> ImmutableDB m blk -> STM m (WithOrigin SlotNo)
getTipSlot :: forall (m :: * -> *) blk.
(MonadSTM m, HasCallStack) =>
ImmutableDB m blk -> STM m (WithOrigin SlotNo)
getTipSlot = (WithOrigin (Tip blk) -> WithOrigin SlotNo)
-> STM m (WithOrigin (Tip blk)) -> STM m (WithOrigin SlotNo)
forall a b. (a -> b) -> STM m a -> STM m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Tip blk -> SlotNo) -> WithOrigin (Tip blk) -> WithOrigin SlotNo
forall a b. (a -> b) -> WithOrigin a -> WithOrigin b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Tip blk -> SlotNo
forall blk. Tip blk -> SlotNo
tipSlotNo) (STM m (WithOrigin (Tip blk)) -> STM m (WithOrigin SlotNo))
-> (ImmutableDB m blk -> STM m (WithOrigin (Tip blk)))
-> ImmutableDB m blk
-> STM m (WithOrigin SlotNo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
forall (m :: * -> *) blk.
HasCallStack =>
ImmutableDB m blk -> STM m (WithOrigin (Tip blk))
getTip