Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Haskoin.Store
Contents
Synopsis
- data Store = Store {
- peerMgr :: !PeerMgr
- chain :: !Chain
- block :: !BlockStore
- db :: !DatabaseReader
- cache :: !(Maybe CacheConfig)
- pub :: !(Publisher StoreEvent)
- net :: !Network
- ctx :: !Ctx
- data StoreConfig = StoreConfig {
- maxPeers :: !Int
- initPeers :: ![String]
- discover :: !Bool
- db :: !FilePath
- net :: !Network
- redis :: !(Maybe String)
- ctx :: !Ctx
- initGap :: !Word32
- gap :: !Word32
- redisMinAddrs :: !Int
- redisMaxKeys :: !Integer
- noMempool :: !Bool
- wipeMempool :: !Bool
- syncMempool :: !Bool
- mempoolTimeout :: !Int
- peerTimeout :: !NominalDiffTime
- maxPeerLife :: !NominalDiffTime
- connect :: !(SockAddr -> WithConnection)
- stats :: !(Maybe Stats)
- redisSyncInterval :: !Int
- bloom :: !Bool
- data StoreEvent
- withStore :: (MonadLoggerIO m, MonadUnliftIO m) => StoreConfig -> (Store -> m a) -> m a
- module Haskoin.Store.BlockStore
- module Haskoin.Store.Web
- module Haskoin.Store.Database.Reader
- module Haskoin.Store.Database.Types
- module Haskoin.Store.Data
- data CacheConfig = CacheConfig {}
- type CacheT = ReaderT (Maybe CacheConfig)
- data CacheError
- withCache :: Maybe CacheConfig -> CacheT m a -> m a
- connectRedis :: MonadIO m => String -> m Connection
- isInCache :: MonadLoggerIO m => XPubSpec -> CacheT m Bool
- class Monad m => StoreReadBase m where
- getNetwork :: m Network
- getCtx :: m Ctx
- getBestBlock :: m (Maybe BlockHash)
- getBlocksAtHeight :: BlockHeight -> m [BlockHash]
- getBlock :: BlockHash -> m (Maybe BlockData)
- getTxData :: TxHash -> m (Maybe TxData)
- getSpender :: OutPoint -> m (Maybe Spender)
- getBalance :: Address -> m (Maybe Balance)
- getUnspent :: OutPoint -> m (Maybe Unspent)
- getMempool :: m [(UnixTime, TxHash)]
- class StoreReadBase m => StoreReadExtra m where
- getAddressesTxs :: [Address] -> Limits -> m [TxRef]
- getAddressesUnspents :: [Address] -> Limits -> m [Unspent]
- getInitialGap :: m Word32
- getMaxGap :: m Word32
- getNumTxData :: Word64 -> m [TxData]
- getBalances :: [Address] -> m [Balance]
- getAddressTxs :: Address -> Limits -> m [TxRef]
- getAddressUnspents :: Address -> Limits -> m [Unspent]
- xPubBals :: XPubSpec -> m [XPubBal]
- xPubUnspents :: XPubSpec -> [XPubBal] -> Limits -> m [XPubUnspent]
- xPubTxs :: XPubSpec -> [XPubBal] -> Limits -> m [TxRef]
- xPubTxCount :: XPubSpec -> [XPubBal] -> m Word32
- data Limits = Limits {}
- data Start
- = AtTx !TxHash
- | AtBlock !BlockHeight
- getTransaction :: StoreReadBase m => TxHash -> m (Maybe Transaction)
- getDefaultBalance :: StoreReadBase m => Address -> m Balance
- getActiveTxData :: StoreReadBase m => TxHash -> m (Maybe TxData)
- blockAtOrBefore :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData)
Documentation
Store mailboxes.
Constructors
Store | |
Fields
|
data StoreConfig Source #
Configuration for a Store
.
Constructors
StoreConfig | |
Fields
|
data StoreEvent Source #
Events that the store can generate.
withStore :: (MonadLoggerIO m, MonadUnliftIO m) => StoreConfig -> (Store -> m a) -> m a Source #
module Haskoin.Store.BlockStore
module Haskoin.Store.Web
module Haskoin.Store.Database.Types
module Haskoin.Store.Data
Cache
data CacheConfig Source #
Constructors
CacheConfig | |
Instances
data CacheError Source #
Constructors
RedisError Reply | |
RedisTxError !String | |
LogicError !String |
Instances
connectRedis :: MonadIO m => String -> m Connection Source #
Store Reader
class Monad m => StoreReadBase m where Source #
Methods
getNetwork :: m Network Source #
getBestBlock :: m (Maybe BlockHash) Source #
getBlocksAtHeight :: BlockHeight -> m [BlockHash] Source #
getBlock :: BlockHash -> m (Maybe BlockData) Source #
getTxData :: TxHash -> m (Maybe TxData) Source #
getSpender :: OutPoint -> m (Maybe Spender) Source #
getBalance :: Address -> m (Maybe Balance) Source #
getUnspent :: OutPoint -> m (Maybe Unspent) Source #
getMempool :: m [(UnixTime, TxHash)] Source #
Instances
class StoreReadBase m => StoreReadExtra m where Source #
Methods
getAddressesTxs :: [Address] -> Limits -> m [TxRef] Source #
getAddressesUnspents :: [Address] -> Limits -> m [Unspent] Source #
getInitialGap :: m Word32 Source #
getMaxGap :: m Word32 Source #
getNumTxData :: Word64 -> m [TxData] Source #
getBalances :: [Address] -> m [Balance] Source #
getAddressTxs :: Address -> Limits -> m [TxRef] Source #
getAddressUnspents :: Address -> Limits -> m [Unspent] Source #
xPubBals :: XPubSpec -> m [XPubBal] Source #
xPubUnspents :: XPubSpec -> [XPubBal] -> Limits -> m [XPubUnspent] Source #
xPubTxs :: XPubSpec -> [XPubBal] -> Limits -> m [TxRef] Source #
Instances
Constructors
AtTx !TxHash | |
AtBlock !BlockHeight |
Useful Fuctions
getTransaction :: StoreReadBase m => TxHash -> m (Maybe Transaction) Source #
getDefaultBalance :: StoreReadBase m => Address -> m Balance Source #
getActiveTxData :: StoreReadBase m => TxHash -> m (Maybe TxData) Source #
blockAtOrBefore :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData) Source #