mafoc-0.0.0.1
Safe HaskellSafe-Inferred
LanguageHaskell2010

Mafoc.Core

Synopsis

Documentation

data Interval #

Constructors

Interval 

Fields

Instances

Instances details
Show Interval # 
Instance details

Defined in Mafoc.Core

data UpTo #

Constructors

SlotNo SlotNo 
Infinity 
CurrentTip 

Instances

Instances details
Show UpTo # 
Instance details

Defined in Mafoc.Core

Methods

showsPrec :: Int -> UpTo -> ShowS #

show :: UpTo -> String #

showList :: [UpTo] -> ShowS #

data LocalChainsyncRuntime #

Static configuration for block source

Constructors

LocalChainsyncRuntime 

Fields

data LocalChainsyncConfig a #

Configuration for local chainsync streaming setup.

Instances

Instances details
IsLabel "getNetworkId" (LocalChainsyncConfig NodeConfig -> IO NetworkId) # 
Instance details

Defined in Mafoc.Core

IsLabel "getNetworkId" (LocalChainsyncConfig_ -> IO NetworkId) # 
Instance details

Defined in Mafoc.Core

Methods

fromLabel :: LocalChainsyncConfig_ -> IO NetworkId #

IsLabel "nodeConfig" (LocalChainsyncConfig NodeConfig -> NodeConfig) # 
Instance details

Defined in Mafoc.Core

IsLabel "socketPath" (LocalChainsyncConfig a -> SocketPath) # 
Instance details

Defined in Mafoc.Core

Show a => Show (LocalChainsyncConfig a) # 
Instance details

Defined in Mafoc.Core

newtype NodeInfo a #

Constructors

NodeInfo (Either NodeFolder (SocketPath, a)) 

Instances

Instances details
IsLabel "getNetworkId" (NodeInfo NodeConfig -> IO NetworkId) # 
Instance details

Defined in Mafoc.Core

Methods

fromLabel :: NodeInfo NodeConfig -> IO NetworkId #

IsLabel "nodeConfig" (NodeInfo NodeConfig -> NodeConfig) # 
Instance details

Defined in Mafoc.Core

IsLabel "socketPath" (NodeInfo a -> SocketPath) # 
Instance details

Defined in Mafoc.Core

Show a => Show (NodeInfo a) # 
Instance details

Defined in Mafoc.Core

Methods

showsPrec :: Int -> NodeInfo a -> ShowS #

show :: NodeInfo a -> String #

showList :: [NodeInfo a] -> ShowS #

class Indexer a => IndexerHttpApi a where #

Associated Types

type API a #

Methods

server :: Runtime a -> MVar (State a, BatchState a) -> Server (API a) #

Instances

Instances details
IndexerHttpApi Mamba # 
Instance details

Defined in Mafoc.Indexers.Mamba

Associated Types

type API Mamba #

Methods

server :: Runtime Mamba -> MVar (State Mamba, BatchState Mamba) -> Server (API Mamba) #

type CheckpointPredicateInterval = UTCTime -> UTCTime -> Bool #

data CheckpointInterval #

Constructors

Never 
Every NominalDiffTime 

newtype BatchSize #

Constructors

BatchSize Natural 

Instances

Instances details
Enum BatchSize # 
Instance details

Defined in Mafoc.Core

Num BatchSize # 
Instance details

Defined in Mafoc.Core

Read BatchSize # 
Instance details

Defined in Mafoc.Core

Show BatchSize # 
Instance details

Defined in Mafoc.Core

Eq BatchSize # 
Instance details

Defined in Mafoc.Core

Ord BatchSize # 
Instance details

Defined in Mafoc.Core

class Indexer a where #

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

data Runtime a #

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).

data Event a #

Event type, i.e the "business requirement". Any input block is converted to zero or more events which are then to be persisted.

data State a #

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.

parseCli :: Parser a #

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

Instances details
Indexer AddressBalance # 
Instance details

Defined in Mafoc.Indexers.AddressBalance

Indexer AddressDatum # 
Instance details

Defined in Mafoc.Indexers.AddressDatum

Indexer BlockBasics # 
Instance details

Defined in Mafoc.Indexers.BlockBasics

Associated Types

data Runtime BlockBasics #

data Event BlockBasics #

data State BlockBasics #

Indexer Datum # 
Instance details

Defined in Mafoc.Indexers.Datum

Associated Types

data Runtime Datum #

data Event Datum #

data State Datum #

Methods

description :: Text #

parseCli :: Parser Datum #

toEvents :: Runtime Datum -> State Datum -> BlockInMode CardanoMode -> (State Datum, [Event Datum]) #

initialize :: Datum -> Trace IO Text -> IO (State Datum, LocalChainsyncRuntime, Runtime Datum) #

persistMany :: Runtime Datum -> [Event Datum] -> IO () #

checkpoint :: Runtime Datum -> State Datum -> (SlotNo, Hash BlockHeader) -> IO () #

Indexer Deposit # 
Instance details

Defined in Mafoc.Indexers.Deposit

Associated Types

data Runtime Deposit #

data Event Deposit #

data State Deposit #

Methods

description :: Text #

parseCli :: Parser Deposit #

toEvents :: Runtime Deposit -> State Deposit -> BlockInMode CardanoMode -> (State Deposit, [Event Deposit]) #

initialize :: Deposit -> Trace IO Text -> IO (State Deposit, LocalChainsyncRuntime, Runtime Deposit) #

persistMany :: Runtime Deposit -> [Event Deposit] -> IO () #

checkpoint :: Runtime Deposit -> State Deposit -> (SlotNo, Hash BlockHeader) -> IO () #

Indexer EpochNonce # 
Instance details

Defined in Mafoc.Indexers.EpochNonce

Associated Types

data Runtime EpochNonce #

data Event EpochNonce #

data State EpochNonce #

Indexer EpochStakepoolSize # 
Instance details

Defined in Mafoc.Indexers.EpochStakepoolSize

Indexer Mamba # 
Instance details

Defined in Mafoc.Indexers.Mamba

Associated Types

data Runtime Mamba #

data Event Mamba #

data State Mamba #

Methods

description :: Text #

parseCli :: Parser Mamba #

toEvents :: Runtime Mamba -> State Mamba -> BlockInMode CardanoMode -> (State Mamba, [Event Mamba]) #

initialize :: Mamba -> Trace IO Text -> IO (State Mamba, LocalChainsyncRuntime, Runtime Mamba) #

persistMany :: Runtime Mamba -> [Event Mamba] -> IO () #

checkpoint :: Runtime Mamba -> State Mamba -> (SlotNo, Hash BlockHeader) -> IO () #

Indexer MintBurn # 
Instance details

Defined in Mafoc.Indexers.MintBurn

Associated Types

data Runtime MintBurn #

data Event MintBurn #

data State MintBurn #

Methods

description :: Text #

parseCli :: Parser MintBurn #

toEvents :: Runtime MintBurn -> State MintBurn -> BlockInMode CardanoMode -> (State MintBurn, [Event MintBurn]) #

initialize :: MintBurn -> Trace IO Text -> IO (State MintBurn, LocalChainsyncRuntime, Runtime MintBurn) #

persistMany :: Runtime MintBurn -> [Event MintBurn] -> IO () #

checkpoint :: Runtime MintBurn -> State MintBurn -> (SlotNo, Hash BlockHeader) -> IO () #

Indexer NoOp # 
Instance details

Defined in Mafoc.Indexers.NoOp

Associated Types

data Runtime NoOp #

data Event NoOp #

data State NoOp #

Methods

description :: Text #

parseCli :: Parser NoOp #

toEvents :: Runtime NoOp -> State NoOp -> BlockInMode CardanoMode -> (State NoOp, [Event NoOp]) #

initialize :: NoOp -> Trace IO Text -> IO (State NoOp, LocalChainsyncRuntime, Runtime NoOp) #

persistMany :: Runtime NoOp -> [Event NoOp] -> IO () #

checkpoint :: Runtime NoOp -> State NoOp -> (SlotNo, Hash BlockHeader) -> IO () #

Indexer ScriptTx # 
Instance details

Defined in Mafoc.Indexers.ScriptTx

Associated Types

data Runtime ScriptTx #

data Event ScriptTx #

data State ScriptTx #

Methods

description :: Text #

parseCli :: Parser ScriptTx #

toEvents :: Runtime ScriptTx -> State ScriptTx -> BlockInMode CardanoMode -> (State ScriptTx, [Event ScriptTx]) #

initialize :: ScriptTx -> Trace IO Text -> IO (State ScriptTx, LocalChainsyncRuntime, Runtime ScriptTx) #

persistMany :: Runtime ScriptTx -> [Event ScriptTx] -> IO () #

checkpoint :: Runtime ScriptTx -> State ScriptTx -> (SlotNo, Hash BlockHeader) -> IO () #

Indexer Utxo # 
Instance details

Defined in Mafoc.Indexers.Utxo

Associated Types

data Runtime Utxo #

data Event Utxo #

data State Utxo #

Methods

description :: Text #

parseCli :: Parser Utxo #

toEvents :: Runtime Utxo -> State Utxo -> BlockInMode CardanoMode -> (State Utxo, [Event Utxo]) #

initialize :: Utxo -> Trace IO Text -> IO (State Utxo, LocalChainsyncRuntime, Runtime Utxo) #

persistMany :: Runtime Utxo -> [Event Utxo] -> IO () #

checkpoint :: Runtime Utxo -> State Utxo -> (SlotNo, Hash BlockHeader) -> IO () #

runIndexer :: forall a. (Indexer a, Show a) => a -> Maybe (Runtime a -> MVar (State a, BatchState a) -> IO ()) -> RunIndexer #

Run an indexer

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 () #

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 () #

loadLatestTrace :: String -> IO a -> (FilePath -> IO a) -> Trace IO Text -> IO (a, ChainPoint) #

query1 :: (ToField q, FromRow r) => Connection -> Query -> q -> IO [r] #

Helper to query with a single param

mkParam :: ToField v => Query -> Text -> v -> (NamedParam, Query) #

andFilters :: [Query] -> Query #

Convert [":field1 = field1", ":field2 = field2"] into ":field1 = field1 AND :field2 = field2"

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) #

todo :: a #

data TxIndexInBlock #

Instances

Instances details
FromJSON TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Methods

parseJSON :: Value -> Parser TxIndexInBlock

parseJSONList :: Value -> Parser [TxIndexInBlock]

ToJSON TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Methods

toJSON :: TxIndexInBlock -> Value

toEncoding :: TxIndexInBlock -> Encoding

toJSONList :: [TxIndexInBlock] -> Value

toEncodingList :: [TxIndexInBlock] -> Encoding

Enum TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Num TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Show TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

FromCBOR TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Methods

fromCBOR :: Decoder s TxIndexInBlock

label :: Proxy TxIndexInBlock -> Text

ToCBOR TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Methods

toCBOR :: TxIndexInBlock -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIndexInBlock -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIndexInBlock] -> Size

Eq TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Ord TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

FromField TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Methods

fromField :: FieldParser TxIndexInBlock

ToField TxIndexInBlock # 
Instance details

Defined in Mafoc.Upstream

Methods

toField :: TxIndexInBlock -> SQLData

data LedgerEra #

Instances

Instances details
ToJSON LedgerEra # 
Instance details

Defined in Mafoc.Upstream

Methods

toJSON :: LedgerEra -> Value

toEncoding :: LedgerEra -> Encoding

toJSONList :: [LedgerEra] -> Value

toEncodingList :: [LedgerEra] -> Encoding

Bounded LedgerEra # 
Instance details

Defined in Mafoc.Upstream

Enum LedgerEra # 
Instance details

Defined in Mafoc.Upstream

Generic LedgerEra # 
Instance details

Defined in Mafoc.Upstream

Associated Types

type Rep LedgerEra :: Type -> Type #

Show LedgerEra # 
Instance details

Defined in Mafoc.Upstream

Eq LedgerEra # 
Instance details

Defined in Mafoc.Upstream

Ord LedgerEra # 
Instance details

Defined in Mafoc.Upstream

type Rep LedgerEra # 
Instance details

Defined in Mafoc.Upstream

type Rep LedgerEra = D1 ('MetaData "LedgerEra" "Mafoc.Upstream" "mafoc-0.0.0.1-inplace" 'False) ((C1 ('MetaCons "Byron" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Shelley" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Allegra" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Mary" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Alonzo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Babbage" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype SocketPath #

Constructors

SocketPath FilePath 

Instances

Instances details
IsString SocketPath # 
Instance details

Defined in Mafoc.Upstream

Show SocketPath # 
Instance details

Defined in Mafoc.Upstream

IsLabel "socketPath" (LocalChainsyncConfig a -> SocketPath) # 
Instance details

Defined in Mafoc.Core

IsLabel "socketPath" (NodeInfo a -> SocketPath) # 
Instance details

Defined in Mafoc.Core

newtype NodeConfig #

Constructors

NodeConfig FilePath 

Instances

Instances details
IsString NodeConfig # 
Instance details

Defined in Mafoc.Upstream

Show NodeConfig # 
Instance details

Defined in Mafoc.Upstream

IsLabel "getNetworkId" (LocalChainsyncConfig NodeConfig -> IO NetworkId) # 
Instance details

Defined in Mafoc.Core

IsLabel "getNetworkId" (LocalChainsyncConfig_ -> IO NetworkId) # 
Instance details

Defined in Mafoc.Core

Methods

fromLabel :: LocalChainsyncConfig_ -> IO NetworkId #

IsLabel "getNetworkId" (NodeInfo NodeConfig -> IO NetworkId) # 
Instance details

Defined in Mafoc.Core

Methods

fromLabel :: NodeInfo NodeConfig -> IO NetworkId #

IsLabel "getNetworkId" (NodeConfig -> IO NetworkId) # 
Instance details

Defined in Mafoc.Upstream

Methods

fromLabel :: NodeConfig -> IO NetworkId #

IsLabel "nodeConfig" (LocalChainsyncConfig NodeConfig -> NodeConfig) # 
Instance details

Defined in Mafoc.Core

IsLabel "nodeConfig" (NodeInfo NodeConfig -> NodeConfig) # 
Instance details

Defined in Mafoc.Core

IsLabel "nodeConfig" (NodeFolder -> NodeConfig) # 
Instance details

Defined in Mafoc.Upstream

newtype NodeFolder #

Not sure if anyone actually wants these upstreamed

Constructors

NodeFolder FilePath 

Instances

Instances details
IsString NodeFolder # 
Instance details

Defined in Mafoc.Upstream

Show NodeFolder # 
Instance details

Defined in Mafoc.Upstream

IsLabel "nodeConfig" (NodeFolder -> NodeConfig) # 
Instance details

Defined in Mafoc.Upstream

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 #

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 bs, while keeping a state of @st".

defaultConfigStderrSeverity :: Severity -> IO Configuration #

slotEra :: SlotNo -> LedgerEra #

allDatums :: Tx era -> [(Hash ScriptData, ScriptData)] #

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))] #

txDatums :: Tx era -> [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

Instances details
ToJSON AssetIdString # 
Instance details

Defined in Mafoc.Upstream.Formats

Methods

toJSON :: AssetIdString -> Value

toEncoding :: AssetIdString -> Encoding

toJSONList :: [AssetIdString] -> Value

toEncodingList :: [AssetIdString] -> Encoding

ToJSONKey AssetIdString # 
Instance details

Defined in Mafoc.Upstream.Formats

Methods

toJSONKey :: ToJSONKeyFunction AssetIdString

toJSONKeyList :: ToJSONKeyFunction [AssetIdString]

Eq AssetIdString # 
Instance details

Defined in Mafoc.Upstream.Formats

Ord AssetIdString # 
Instance details

Defined in Mafoc.Upstream.Formats

Mafoc.Logging

renderPretty :: Pretty a => a -> Text #

traceInfo :: Trace IO Text -> Doc () -> IO () #

Re-exports from other packages

type CurrentEra = BabbageEra #