Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Mafoc.Core
Synopsis
- data DbPathAndTableName = DbPathAndTableName (Maybe FilePath) (Maybe String)
- data Interval = Interval {}
- data UpTo
- = SlotNo SlotNo
- | Infinity
- | CurrentTip
- data ConcurrencyPrimitive
- data LocalChainsyncRuntime = LocalChainsyncRuntime {
- localNodeConnection :: LocalNodeConnectInfo CardanoMode
- interval :: (ChainPoint, UpTo)
- securityParam :: SecurityParam
- logging :: Bool
- profiling :: Maybe ProfilingConfig
- pipelineSize :: Word32
- concurrencyPrimitive :: ConcurrencyPrimitive
- type LocalChainsyncConfig_ = LocalChainsyncConfig (Either NetworkId NodeConfig)
- data LocalChainsyncConfig a = LocalChainsyncConfig {}
- newtype NodeInfo a = NodeInfo (Either NodeFolder (SocketPath, a))
- class Indexer a => IndexerHttpApi a where
- type CheckpointPredicateInterval = UTCTime -> UTCTime -> Bool
- data CheckpointInterval
- newtype BatchSize = BatchSize Natural
- data BatchState a
- = BatchState {
- lastCheckpointTime :: UTCTime
- slotNoBhh :: SlotNoBhh
- indexerState :: State a
- batchFill :: BatchSize
- bufferedEvents :: [[Event a]]
- | BatchEmpty {
- lastCheckpointTime :: UTCTime
- slotNoBhh :: SlotNoBhh
- indexerState :: State a
- | NoProgress {
- chainPointAtStart :: ChainPoint
- lastCheckpointTime :: UTCTime
- = BatchState {
- type RunIndexer = BatchSize -> Stop -> Checkpoint -> ChainsyncStats -> Severity -> CheckpointInterval -> IO ()
- class Indexer a where
- data Runtime a
- data Event a
- data State a
- description :: Text
- parseCli :: Parser a
- toEvents :: Runtime a -> State a -> BlockInMode CardanoMode -> (State a, [Event a])
- initialize :: a -> Trace IO Text -> IO (State a, LocalChainsyncRuntime, Runtime a)
- persistMany :: Runtime a -> [Event a] -> IO ()
- checkpoint :: Runtime a -> State a -> (SlotNo, Hash BlockHeader) -> IO ()
- runIndexer :: forall a. (Indexer a, Show a) => a -> Maybe (Runtime a -> MVar (State a, BatchState a) -> IO ()) -> RunIndexer
- getBatchFill :: BatchState a -> BatchSize
- getBufferedEvents :: BatchState a -> [[Event a]]
- persistStep :: forall a. Indexer a => Trace IO Text -> Runtime a -> Checkpoint -> BatchSize -> CheckpointPredicateInterval -> BatchState a -> (SlotNoBhh, [Event a], State a) -> IO (BatchState a)
- persistStepFinal :: Indexer a => Runtime a -> BatchState a -> Trace IO Text -> IO (Maybe ChainPoint)
- checkpointIntervalPredicate :: CheckpointInterval -> CheckpointPredicateInterval
- initialNotice :: Show a => a -> BatchSize -> Severity -> CheckpointInterval -> Trace IO Text -> IO ()
- modifyStartingPoint :: LocalChainsyncRuntime -> (ChainPoint -> ChainPoint) -> LocalChainsyncRuntime
- initializeLocalChainsync :: LocalChainsyncConfig a -> NetworkId -> Trace IO Text -> IO LocalChainsyncRuntime
- initializeLocalChainsync_ :: LocalChainsyncConfig_ -> Trace IO Text -> IO LocalChainsyncRuntime
- rollbackRingBuffer :: SecurityParam -> Stream (Of (ChainSyncEvent (BlockInMode CardanoMode))) IO () -> Stream (Of (BlockInMode CardanoMode)) IO ()
- blockProducer :: forall r. LocalNodeConnectInfo CardanoMode -> Word32 -> ChainPoint -> ConcurrencyPrimitive -> Stream (Of (ChainSyncEvent (BlockInMode CardanoMode))) IO r
- takeUpTo :: Trace IO Text -> UpTo -> Stop -> Stream (Of (ChainSyncEvent (BlockInMode mode))) IO () -> Stream (Of (ChainSyncEvent (BlockInMode mode))) IO ()
- loadLatestTrace :: String -> IO a -> (FilePath -> IO a) -> Trace IO Text -> IO (a, ChainPoint)
- query1 :: (ToField q, FromRow r) => Connection -> Query -> q -> IO [r]
- mkParam :: ToField v => Query -> Text -> v -> (NamedParam, Query)
- andFilters :: [Query] -> Query
- defaultTableName :: String -> DbPathAndTableName -> (FilePath, String)
- sqliteInitCheckpoints :: Connection -> IO ()
- setCheckpointSqlite :: Connection -> String -> (SlotNo, Hash BlockHeader) -> IO ()
- getCheckpointSqlite :: Connection -> String -> IO (Maybe ChainPoint)
- initializeSqlite :: FilePath -> String -> IO (Connection, ChainPoint)
- sqliteOpen :: FilePath -> IO Connection
- eventsToSingleChainpoint :: [(SlotNo, Hash BlockHeader)] -> Maybe ChainPoint
- chainPointForSlotNo :: Connection -> String -> SlotNo -> IO (Maybe ChainPoint)
- previousChainPointForSlotNo :: Connection -> String -> SlotNo -> IO (Maybe ChainPoint)
- intervalStartToChainSyncStart :: Trace IO Text -> Maybe DbPathAndTableName -> (Bool, Either SlotNo ChainPoint) -> IO ChainPoint
- mkMaybeAddressFilter :: [Address ShelleyAddr] -> Maybe (Address ShelleyAddr -> Bool)
- todo :: a
- data TxIndexInBlock
- data LedgerEra
- newtype SocketPath = SocketPath FilePath
- newtype NodeConfig = NodeConfig FilePath
- newtype NodeFolder = NodeFolder FilePath
- type SlotNoBhh = (SlotNo, Hash BlockHeader)
- getSecurityParamAndNetworkId :: FilePath -> IO (SecurityParam, NetworkId)
- getNetworkId :: FilePath -> IO NetworkId
- tipDistance :: BlockInMode mode -> ChainTip -> Natural
- querySecurityParam :: LocalNodeConnectInfo CardanoMode -> IO SecurityParam
- blockChainPoint :: BlockInMode mode -> ChainPoint
- blockSlotNoBhh :: BlockInMode mode -> SlotNoBhh
- blockSlotNo :: BlockInMode mode -> SlotNo
- chainPointSlotNo :: ChainPoint -> SlotNo
- foldYield :: Monad m => (st -> a -> m (st, b)) -> st -> Stream (Of a) m r -> Stream (Of b) m r
- defaultConfigStderrSeverity :: Severity -> IO Configuration
- slotEra :: SlotNo -> LedgerEra
- allDatums :: Tx era -> [(Hash ScriptData, ScriptData)]
- plutusDatums :: [Tx era] -> [(Hash ScriptData, ScriptData)]
- txPlutusDatums :: Tx era -> [(Hash ScriptData, ScriptData)]
- txAddressDatums :: Tx era -> [(AddressAny, Either (Hash ScriptData) (Hash ScriptData, ScriptData))]
- txDatums :: Tx era -> [Either (Hash ScriptData) (Hash ScriptData, ScriptData)]
- maybeDatum :: TxOut CtxTx era -> Maybe (Either (Hash ScriptData) (Hash ScriptData, ScriptData))
- newtype AssetIdString = AssetIdString AssetId
- newtype SlotNoBhhString = SlotNoBhhString SlotNoBhh
- renderPretty :: Pretty a => a -> Text
- traceInfo :: Trace IO Text -> Doc () -> IO ()
- type CurrentEra = BabbageEra
Documentation
data DbPathAndTableName #
Constructors
DbPathAndTableName (Maybe FilePath) (Maybe String) |
Instances
Show DbPathAndTableName # | |
Defined in Mafoc.Core Methods showsPrec :: Int -> DbPathAndTableName -> ShowS # show :: DbPathAndTableName -> String # showList :: [DbPathAndTableName] -> ShowS # |
Constructors
SlotNo SlotNo | |
Infinity | |
CurrentTip |
data ConcurrencyPrimitive #
This is a very internal data type to help swap the concurrency primitive used to pass blocks from the local chainsync's green thread to the indexer.
Instances
Bounded ConcurrencyPrimitive # | |
Defined in Mafoc.Core | |
Enum ConcurrencyPrimitive # | |
Defined in Mafoc.Core Methods succ :: ConcurrencyPrimitive -> ConcurrencyPrimitive # pred :: ConcurrencyPrimitive -> ConcurrencyPrimitive # toEnum :: Int -> ConcurrencyPrimitive # fromEnum :: ConcurrencyPrimitive -> Int # enumFrom :: ConcurrencyPrimitive -> [ConcurrencyPrimitive] # enumFromThen :: ConcurrencyPrimitive -> ConcurrencyPrimitive -> [ConcurrencyPrimitive] # enumFromTo :: ConcurrencyPrimitive -> ConcurrencyPrimitive -> [ConcurrencyPrimitive] # enumFromThenTo :: ConcurrencyPrimitive -> ConcurrencyPrimitive -> ConcurrencyPrimitive -> [ConcurrencyPrimitive] # | |
Read ConcurrencyPrimitive # | |
Defined in Mafoc.Core Methods readsPrec :: Int -> ReadS ConcurrencyPrimitive # readList :: ReadS [ConcurrencyPrimitive] # | |
Show ConcurrencyPrimitive # | |
Defined in Mafoc.Core Methods showsPrec :: Int -> ConcurrencyPrimitive -> ShowS # show :: ConcurrencyPrimitive -> String # showList :: [ConcurrencyPrimitive] -> ShowS # |
data LocalChainsyncRuntime #
Static configuration for block source
Constructors
LocalChainsyncRuntime | |
Fields
|
type LocalChainsyncConfig_ = LocalChainsyncConfig (Either NetworkId NodeConfig) #
data LocalChainsyncConfig a #
Configuration for local chainsync streaming setup.
Constructors
LocalChainsyncConfig | |
Fields |
Instances
IsLabel "getNetworkId" (LocalChainsyncConfig NodeConfig -> IO NetworkId) # | |
Defined in Mafoc.Core Methods fromLabel :: LocalChainsyncConfig NodeConfig -> IO NetworkId # | |
IsLabel "getNetworkId" (LocalChainsyncConfig_ -> IO NetworkId) # | |
Defined in Mafoc.Core Methods fromLabel :: LocalChainsyncConfig_ -> IO NetworkId # | |
IsLabel "nodeConfig" (LocalChainsyncConfig NodeConfig -> NodeConfig) # | |
Defined in Mafoc.Core Methods fromLabel :: LocalChainsyncConfig NodeConfig -> NodeConfig # | |
IsLabel "socketPath" (LocalChainsyncConfig a -> SocketPath) # | |
Defined in Mafoc.Core Methods fromLabel :: LocalChainsyncConfig a -> SocketPath # | |
Show a => Show (LocalChainsyncConfig a) # | |
Defined in Mafoc.Core Methods showsPrec :: Int -> LocalChainsyncConfig a -> ShowS # show :: LocalChainsyncConfig a -> String # showList :: [LocalChainsyncConfig a] -> ShowS # |
Constructors
NodeInfo (Either NodeFolder (SocketPath, a)) |
Instances
IsLabel "getNetworkId" (NodeInfo NodeConfig -> IO NetworkId) # | |
Defined in Mafoc.Core Methods fromLabel :: NodeInfo NodeConfig -> IO NetworkId # | |
IsLabel "nodeConfig" (NodeInfo NodeConfig -> NodeConfig) # | |
Defined in Mafoc.Core Methods fromLabel :: NodeInfo NodeConfig -> NodeConfig # | |
IsLabel "socketPath" (NodeInfo a -> SocketPath) # | |
Defined in Mafoc.Core Methods fromLabel :: NodeInfo a -> SocketPath # | |
Show a => Show (NodeInfo a) # | |
class Indexer a => IndexerHttpApi a where #
type CheckpointPredicateInterval = UTCTime -> UTCTime -> Bool #
data CheckpointInterval #
Instances
Show CheckpointInterval # | |
Defined in Mafoc.Core Methods showsPrec :: Int -> CheckpointInterval -> ShowS # show :: CheckpointInterval -> String # showList :: [CheckpointInterval] -> ShowS # | |
Eq CheckpointInterval # | |
Defined in Mafoc.Core Methods (==) :: CheckpointInterval -> CheckpointInterval -> Bool # (/=) :: CheckpointInterval -> CheckpointInterval -> Bool # |
Instances
Enum BatchSize # | |
Defined in Mafoc.Core Methods succ :: BatchSize -> BatchSize # pred :: BatchSize -> BatchSize # fromEnum :: BatchSize -> Int # enumFrom :: BatchSize -> [BatchSize] # enumFromThen :: BatchSize -> BatchSize -> [BatchSize] # enumFromTo :: BatchSize -> BatchSize -> [BatchSize] # enumFromThenTo :: BatchSize -> BatchSize -> BatchSize -> [BatchSize] # | |
Num BatchSize # | |
Read BatchSize # | |
Show BatchSize # | |
Eq BatchSize # | |
Ord BatchSize # | |
data BatchState a #
Constructors
BatchState | |
Fields
| |
BatchEmpty | |
Fields
| |
NoProgress | |
Fields
|
type RunIndexer = BatchSize -> Stop -> Checkpoint -> ChainsyncStats -> Severity -> CheckpointInterval -> IO () #
Class for an indexer. The argument a
doubles as both a type
representation (a "tag") for the indexer, and also as the initial
configuration required to run the indexer.
Associated Types
The a
itself doubles as cli configuration, no need for the following:
type Config a = r | r -> a
Runtime configuration, i.e the reader for the indexer, used for e.g the db connection, for communication with other threads (respond to queries).
Event type, i.e the "business requirement". Any input block is converted to zero or more events which are then to be persisted.
The fold state. Some don't require a state so, for those it's defined as a data type with no fields, equivalent to unit. As a consequence these indexers can be resumed from arbitrary chain points on request.
Methods
description :: Text #
A text description of the indexer, used for help messages.
A CLI parser for a
.
toEvents :: Runtime a -> State a -> BlockInMode CardanoMode -> (State a, [Event a]) #
Convert a state and a block to events and a new state.
initialize :: a -> Trace IO Text -> IO (State a, LocalChainsyncRuntime, Runtime a) #
Initialize an indexer from a
to a runtime for local
chainsync, indexer's runtime configuration and the indexer state.
persistMany :: Runtime a -> [Event a] -> IO () #
Persist many events at a time, defaults to mapping over events with persist.
checkpoint :: Runtime a -> State a -> (SlotNo, Hash BlockHeader) -> IO () #
Checkpoint indexer by writing the chain point and the state at that point, destination being provided by the runtime. Checkpoints are used for resuming
Instances
runIndexer :: forall a. (Indexer a, Show a) => a -> Maybe (Runtime a -> MVar (State a, BatchState a) -> IO ()) -> RunIndexer #
Run an indexer
getBatchFill :: BatchState a -> BatchSize #
getBufferedEvents :: BatchState a -> [[Event a]] #
persistStep :: forall a. Indexer a => Trace IO Text -> Runtime a -> Checkpoint -> BatchSize -> CheckpointPredicateInterval -> BatchState a -> (SlotNoBhh, [Event a], State a) -> IO (BatchState a) #
persistStepFinal :: Indexer a => Runtime a -> BatchState a -> Trace IO Text -> IO (Maybe ChainPoint) #
initialNotice :: Show a => a -> BatchSize -> Severity -> CheckpointInterval -> Trace IO Text -> IO () #
modifyStartingPoint :: LocalChainsyncRuntime -> (ChainPoint -> ChainPoint) -> LocalChainsyncRuntime #
initializeLocalChainsync :: LocalChainsyncConfig a -> NetworkId -> Trace IO Text -> IO LocalChainsyncRuntime #
initializeLocalChainsync_ :: LocalChainsyncConfig_ -> Trace IO Text -> IO LocalChainsyncRuntime #
Resolve LocalChainsyncConfig
that came from e.g command line
arguments into an "actionable" LocalChainsyncRuntime
runtime
config which can be used to generate a stream of blocks.
rollbackRingBuffer :: SecurityParam -> Stream (Of (ChainSyncEvent (BlockInMode CardanoMode))) IO () -> Stream (Of (BlockInMode CardanoMode)) IO () #
blockProducer :: forall r. LocalNodeConnectInfo CardanoMode -> Word32 -> ChainPoint -> ConcurrencyPrimitive -> Stream (Of (ChainSyncEvent (BlockInMode CardanoMode))) IO r #
takeUpTo :: Trace IO Text -> UpTo -> Stop -> Stream (Of (ChainSyncEvent (BlockInMode mode))) IO () -> Stream (Of (ChainSyncEvent (BlockInMode mode))) IO () #
query1 :: (ToField q, FromRow r) => Connection -> Query -> q -> IO [r] #
Helper to query with a single param
andFilters :: [Query] -> Query #
Convert [":field1 = field1", ":field2 = field2"]
into ":field1 = field1 AND :field2 = field2"
defaultTableName :: String -> DbPathAndTableName -> (FilePath, String) #
sqliteInitCheckpoints :: Connection -> IO () #
setCheckpointSqlite :: Connection -> String -> (SlotNo, Hash BlockHeader) -> IO () #
getCheckpointSqlite :: Connection -> String -> IO (Maybe ChainPoint) #
Get checkpoint (the place where we left off) for an indexer with name
initializeSqlite :: FilePath -> String -> IO (Connection, ChainPoint) #
If ChainPointAtGenesis is returned, then there was no chain point in the database.
sqliteOpen :: FilePath -> IO Connection #
eventsToSingleChainpoint :: [(SlotNo, Hash BlockHeader)] -> Maybe ChainPoint #
chainPointForSlotNo :: Connection -> String -> SlotNo -> IO (Maybe ChainPoint) #
previousChainPointForSlotNo :: Connection -> String -> SlotNo -> IO (Maybe ChainPoint) #
intervalStartToChainSyncStart :: Trace IO Text -> Maybe DbPathAndTableName -> (Bool, Either SlotNo ChainPoint) -> IO ChainPoint #
Convert starting point from CLI to chainpoint, possibly with the help of header DB.
mkMaybeAddressFilter :: [Address ShelleyAddr] -> Maybe (Address ShelleyAddr -> Bool) #
data TxIndexInBlock #
Instances
Instances
newtype SocketPath #
Constructors
SocketPath FilePath |
Instances
IsString SocketPath # | |
Defined in Mafoc.Upstream Methods fromString :: String -> SocketPath # | |
Show SocketPath # | |
Defined in Mafoc.Upstream Methods showsPrec :: Int -> SocketPath -> ShowS # show :: SocketPath -> String # showList :: [SocketPath] -> ShowS # | |
IsLabel "socketPath" (LocalChainsyncConfig a -> SocketPath) # | |
Defined in Mafoc.Core Methods fromLabel :: LocalChainsyncConfig a -> SocketPath # | |
IsLabel "socketPath" (NodeInfo a -> SocketPath) # | |
Defined in Mafoc.Core Methods fromLabel :: NodeInfo a -> SocketPath # |
newtype NodeConfig #
Constructors
NodeConfig FilePath |
Instances
newtype NodeFolder #
Not sure if anyone actually wants these upstreamed
Constructors
NodeFolder FilePath |
Instances
IsString NodeFolder # | |
Defined in Mafoc.Upstream Methods fromString :: String -> NodeFolder # | |
Show NodeFolder # | |
Defined in Mafoc.Upstream Methods showsPrec :: Int -> NodeFolder -> ShowS # show :: NodeFolder -> String # showList :: [NodeFolder] -> ShowS # | |
IsLabel "nodeConfig" (NodeFolder -> NodeConfig) # | |
Defined in Mafoc.Upstream Methods fromLabel :: NodeFolder -> NodeConfig # |
getSecurityParamAndNetworkId :: FilePath -> IO (SecurityParam, NetworkId) #
getNetworkId :: FilePath -> IO NetworkId #
tipDistance :: BlockInMode mode -> ChainTip -> Natural #
querySecurityParam :: LocalNodeConnectInfo CardanoMode -> IO SecurityParam #
blockChainPoint :: BlockInMode mode -> ChainPoint #
Create a ChainPoint from BlockInMode
blockSlotNoBhh :: BlockInMode mode -> SlotNoBhh #
blockSlotNo :: BlockInMode mode -> SlotNo #
chainPointSlotNo :: ChainPoint -> SlotNo #
foldYield :: Monad m => (st -> a -> m (st, b)) -> st -> Stream (Of a) m r -> Stream (Of b) m r #
Fold a stream of a
's, yield a stream of b
s, while keeping a state of @st".
defaultConfigStderrSeverity :: Severity -> IO Configuration #
plutusDatums :: [Tx era] -> [(Hash ScriptData, ScriptData)] #
Get a map of datum hash to datum from a list of transactions.
txPlutusDatums :: Tx era -> [(Hash ScriptData, ScriptData)] #
txAddressDatums :: Tx era -> [(AddressAny, Either (Hash ScriptData) (Hash ScriptData, ScriptData))] #
maybeDatum :: TxOut CtxTx era -> Maybe (Either (Hash ScriptData) (Hash ScriptData, ScriptData)) #
newtype AssetIdString #
Newtype of AssetId which renders as "policyId.assetName"
Constructors
AssetIdString AssetId |
Instances
ToJSON AssetIdString # | |
Defined in Mafoc.Upstream.Formats Methods toJSON :: AssetIdString -> Value toEncoding :: AssetIdString -> Encoding toJSONList :: [AssetIdString] -> Value toEncodingList :: [AssetIdString] -> Encoding | |
ToJSONKey AssetIdString # | |
Defined in Mafoc.Upstream.Formats Methods toJSONKey :: ToJSONKeyFunction AssetIdString toJSONKeyList :: ToJSONKeyFunction [AssetIdString] | |
Eq AssetIdString # | |
Defined in Mafoc.Upstream.Formats Methods (==) :: AssetIdString -> AssetIdString -> Bool # (/=) :: AssetIdString -> AssetIdString -> Bool # | |
Ord AssetIdString # | |
Defined in Mafoc.Upstream.Formats Methods compare :: AssetIdString -> AssetIdString -> Ordering # (<) :: AssetIdString -> AssetIdString -> Bool # (<=) :: AssetIdString -> AssetIdString -> Bool # (>) :: AssetIdString -> AssetIdString -> Bool # (>=) :: AssetIdString -> AssetIdString -> Bool # max :: AssetIdString -> AssetIdString -> AssetIdString # min :: AssetIdString -> AssetIdString -> AssetIdString # |
newtype SlotNoBhhString #
Constructors
SlotNoBhhString SlotNoBhh |
Instances
Mafoc.Logging
renderPretty :: Pretty a => a -> Text #
Re-exports from other packages
type CurrentEra = BabbageEra #