{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
module Ouroboros.Consensus.Storage.VolatileDB.Impl.Types (
mkBlocksPerFile
, unBlocksPerFile
, BlocksPerFile
, BlockValidationPolicy (..)
, ParseError (..)
, TraceEvent (..)
, BlockOffset (..)
, BlockSize (..)
, FileId
, InternalBlockInfo (..)
, ReverseIndex
, SuccessorsIndex
) where
import Data.Map.Strict (Map)
import Data.Set (Set)
import Data.Word (Word32, Word64)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Util.CBOR (ReadIncrementalErr (..))
import Ouroboros.Consensus.Storage.FS.API.Types (FsPath)
import Ouroboros.Consensus.Storage.VolatileDB.API (BlockInfo)
newtype BlocksPerFile = BlocksPerFile { BlocksPerFile -> Word32
unBlocksPerFile :: Word32 }
deriving ((forall x. BlocksPerFile -> Rep BlocksPerFile x)
-> (forall x. Rep BlocksPerFile x -> BlocksPerFile)
-> Generic BlocksPerFile
forall x. Rep BlocksPerFile x -> BlocksPerFile
forall x. BlocksPerFile -> Rep BlocksPerFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlocksPerFile x -> BlocksPerFile
$cfrom :: forall x. BlocksPerFile -> Rep BlocksPerFile x
Generic, Int -> BlocksPerFile -> ShowS
[BlocksPerFile] -> ShowS
BlocksPerFile -> String
(Int -> BlocksPerFile -> ShowS)
-> (BlocksPerFile -> String)
-> ([BlocksPerFile] -> ShowS)
-> Show BlocksPerFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlocksPerFile] -> ShowS
$cshowList :: [BlocksPerFile] -> ShowS
show :: BlocksPerFile -> String
$cshow :: BlocksPerFile -> String
showsPrec :: Int -> BlocksPerFile -> ShowS
$cshowsPrec :: Int -> BlocksPerFile -> ShowS
Show)
mkBlocksPerFile :: Word32 -> BlocksPerFile
mkBlocksPerFile :: Word32 -> BlocksPerFile
mkBlocksPerFile Word32
0 = String -> BlocksPerFile
forall a. HasCallStack => String -> a
error String
"BlocksPerFile must be positive"
mkBlocksPerFile Word32
n = Word32 -> BlocksPerFile
BlocksPerFile Word32
n
data BlockValidationPolicy =
NoValidation
| ValidateAll
deriving (BlockValidationPolicy -> BlockValidationPolicy -> Bool
(BlockValidationPolicy -> BlockValidationPolicy -> Bool)
-> (BlockValidationPolicy -> BlockValidationPolicy -> Bool)
-> Eq BlockValidationPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockValidationPolicy -> BlockValidationPolicy -> Bool
$c/= :: BlockValidationPolicy -> BlockValidationPolicy -> Bool
== :: BlockValidationPolicy -> BlockValidationPolicy -> Bool
$c== :: BlockValidationPolicy -> BlockValidationPolicy -> Bool
Eq)
data ParseError blk =
BlockReadErr ReadIncrementalErr
| BlockCorruptedErr (HeaderHash blk)
| DuplicatedBlock (HeaderHash blk) FsPath FsPath
deriving instance StandardHash blk => Eq (ParseError blk)
deriving instance StandardHash blk => Show (ParseError blk)
data TraceEvent blk
= DBAlreadyClosed
| BlockAlreadyHere (HeaderHash blk)
| Truncate (ParseError blk) FsPath BlockOffset
| InvalidFileNames [FsPath]
deriving (TraceEvent blk -> TraceEvent blk -> Bool
(TraceEvent blk -> TraceEvent blk -> Bool)
-> (TraceEvent blk -> TraceEvent blk -> Bool)
-> Eq (TraceEvent blk)
forall blk.
StandardHash blk =>
TraceEvent blk -> TraceEvent blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceEvent blk -> TraceEvent blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
TraceEvent blk -> TraceEvent blk -> Bool
== :: TraceEvent blk -> TraceEvent blk -> Bool
$c== :: forall blk.
StandardHash blk =>
TraceEvent blk -> TraceEvent blk -> Bool
Eq, (forall x. TraceEvent blk -> Rep (TraceEvent blk) x)
-> (forall x. Rep (TraceEvent blk) x -> TraceEvent blk)
-> Generic (TraceEvent blk)
forall x. Rep (TraceEvent blk) x -> TraceEvent blk
forall x. TraceEvent blk -> Rep (TraceEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (TraceEvent blk) x -> TraceEvent blk
forall blk x. TraceEvent blk -> Rep (TraceEvent blk) x
$cto :: forall blk x. Rep (TraceEvent blk) x -> TraceEvent blk
$cfrom :: forall blk x. TraceEvent blk -> Rep (TraceEvent blk) x
Generic, Int -> TraceEvent blk -> ShowS
[TraceEvent blk] -> ShowS
TraceEvent blk -> String
(Int -> TraceEvent blk -> ShowS)
-> (TraceEvent blk -> String)
-> ([TraceEvent blk] -> ShowS)
-> Show (TraceEvent blk)
forall blk. StandardHash blk => Int -> TraceEvent blk -> ShowS
forall blk. StandardHash blk => [TraceEvent blk] -> ShowS
forall blk. StandardHash blk => TraceEvent blk -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TraceEvent blk] -> ShowS
$cshowList :: forall blk. StandardHash blk => [TraceEvent blk] -> ShowS
show :: TraceEvent blk -> String
$cshow :: forall blk. StandardHash blk => TraceEvent blk -> String
showsPrec :: Int -> TraceEvent blk -> ShowS
$cshowsPrec :: forall blk. StandardHash blk => Int -> TraceEvent blk -> ShowS
Show)
type FileId = Int
type ReverseIndex blk = Map (HeaderHash blk) (InternalBlockInfo blk)
type SuccessorsIndex blk = Map (ChainHash blk) (Set (HeaderHash blk))
newtype BlockSize = BlockSize { BlockSize -> Word32
unBlockSize :: Word32 }
deriving (BlockSize -> BlockSize -> Bool
(BlockSize -> BlockSize -> Bool)
-> (BlockSize -> BlockSize -> Bool) -> Eq BlockSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockSize -> BlockSize -> Bool
$c/= :: BlockSize -> BlockSize -> Bool
== :: BlockSize -> BlockSize -> Bool
$c== :: BlockSize -> BlockSize -> Bool
Eq, Int -> BlockSize -> ShowS
[BlockSize] -> ShowS
BlockSize -> String
(Int -> BlockSize -> ShowS)
-> (BlockSize -> String)
-> ([BlockSize] -> ShowS)
-> Show BlockSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockSize] -> ShowS
$cshowList :: [BlockSize] -> ShowS
show :: BlockSize -> String
$cshow :: BlockSize -> String
showsPrec :: Int -> BlockSize -> ShowS
$cshowsPrec :: Int -> BlockSize -> ShowS
Show, (forall x. BlockSize -> Rep BlockSize x)
-> (forall x. Rep BlockSize x -> BlockSize) -> Generic BlockSize
forall x. Rep BlockSize x -> BlockSize
forall x. BlockSize -> Rep BlockSize x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockSize x -> BlockSize
$cfrom :: forall x. BlockSize -> Rep BlockSize x
Generic, Context -> BlockSize -> IO (Maybe ThunkInfo)
Proxy BlockSize -> String
(Context -> BlockSize -> IO (Maybe ThunkInfo))
-> (Context -> BlockSize -> IO (Maybe ThunkInfo))
-> (Proxy BlockSize -> String)
-> NoThunks BlockSize
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy BlockSize -> String
$cshowTypeOf :: Proxy BlockSize -> String
wNoThunks :: Context -> BlockSize -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> BlockSize -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlockSize -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> BlockSize -> IO (Maybe ThunkInfo)
NoThunks)
newtype BlockOffset = BlockOffset { BlockOffset -> Word64
unBlockOffset :: Word64 }
deriving (BlockOffset -> BlockOffset -> Bool
(BlockOffset -> BlockOffset -> Bool)
-> (BlockOffset -> BlockOffset -> Bool) -> Eq BlockOffset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockOffset -> BlockOffset -> Bool
$c/= :: BlockOffset -> BlockOffset -> Bool
== :: BlockOffset -> BlockOffset -> Bool
$c== :: BlockOffset -> BlockOffset -> Bool
Eq, Int -> BlockOffset -> ShowS
[BlockOffset] -> ShowS
BlockOffset -> String
(Int -> BlockOffset -> ShowS)
-> (BlockOffset -> String)
-> ([BlockOffset] -> ShowS)
-> Show BlockOffset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockOffset] -> ShowS
$cshowList :: [BlockOffset] -> ShowS
show :: BlockOffset -> String
$cshow :: BlockOffset -> String
showsPrec :: Int -> BlockOffset -> ShowS
$cshowsPrec :: Int -> BlockOffset -> ShowS
Show, (forall x. BlockOffset -> Rep BlockOffset x)
-> (forall x. Rep BlockOffset x -> BlockOffset)
-> Generic BlockOffset
forall x. Rep BlockOffset x -> BlockOffset
forall x. BlockOffset -> Rep BlockOffset x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockOffset x -> BlockOffset
$cfrom :: forall x. BlockOffset -> Rep BlockOffset x
Generic, Context -> BlockOffset -> IO (Maybe ThunkInfo)
Proxy BlockOffset -> String
(Context -> BlockOffset -> IO (Maybe ThunkInfo))
-> (Context -> BlockOffset -> IO (Maybe ThunkInfo))
-> (Proxy BlockOffset -> String)
-> NoThunks BlockOffset
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy BlockOffset -> String
$cshowTypeOf :: Proxy BlockOffset -> String
wNoThunks :: Context -> BlockOffset -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> BlockOffset -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlockOffset -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> BlockOffset -> IO (Maybe ThunkInfo)
NoThunks)
data InternalBlockInfo blk = InternalBlockInfo {
InternalBlockInfo blk -> FsPath
ibiFile :: !FsPath
, InternalBlockInfo blk -> BlockOffset
ibiBlockOffset :: !BlockOffset
, InternalBlockInfo blk -> BlockSize
ibiBlockSize :: !BlockSize
, InternalBlockInfo blk -> BlockInfo blk
ibiBlockInfo :: !(BlockInfo blk)
, InternalBlockInfo blk -> SomeSecond (NestedCtxt Header) blk
ibiNestedCtxt :: !(SomeSecond (NestedCtxt Header) blk)
}
deriving ((forall x. InternalBlockInfo blk -> Rep (InternalBlockInfo blk) x)
-> (forall x.
Rep (InternalBlockInfo blk) x -> InternalBlockInfo blk)
-> Generic (InternalBlockInfo blk)
forall x. Rep (InternalBlockInfo blk) x -> InternalBlockInfo blk
forall x. InternalBlockInfo blk -> Rep (InternalBlockInfo blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (InternalBlockInfo blk) x -> InternalBlockInfo blk
forall blk x.
InternalBlockInfo blk -> Rep (InternalBlockInfo blk) x
$cto :: forall blk x.
Rep (InternalBlockInfo blk) x -> InternalBlockInfo blk
$cfrom :: forall blk x.
InternalBlockInfo blk -> Rep (InternalBlockInfo blk) x
Generic, Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo)
Proxy (InternalBlockInfo blk) -> String
(Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo))
-> (Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo))
-> (Proxy (InternalBlockInfo blk) -> String)
-> NoThunks (InternalBlockInfo blk)
forall blk.
(StandardHash blk, Typeable blk) =>
Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo)
forall blk.
(StandardHash blk, Typeable blk) =>
Proxy (InternalBlockInfo blk) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (InternalBlockInfo blk) -> String
$cshowTypeOf :: forall blk.
(StandardHash blk, Typeable blk) =>
Proxy (InternalBlockInfo blk) -> String
wNoThunks :: Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall blk.
(StandardHash blk, Typeable blk) =>
Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall blk.
(StandardHash blk, Typeable blk) =>
Context -> InternalBlockInfo blk -> IO (Maybe ThunkInfo)
NoThunks)