Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Store = Store {
- storeManager :: !PeerManager
- storeChain :: !Chain
- storeBlock :: !BlockStore
- storeDB :: !DatabaseReader
- storeCache :: !(Maybe CacheConfig)
- storePublisher :: !(Publisher StoreEvent)
- storeNetwork :: !Network
- data StoreConfig = StoreConfig {
- storeConfMaxPeers :: !Int
- storeConfInitPeers :: ![HostPort]
- storeConfDiscover :: !Bool
- storeConfDB :: !FilePath
- storeConfNetwork :: !Network
- storeConfCache :: !(Maybe String)
- storeConfInitialGap :: !Word32
- storeConfGap :: !Word32
- storeConfCacheMin :: !Int
- storeConfMaxKeys :: !Integer
- storeConfNoMempool :: !Bool
- storeConfWipeMempool :: !Bool
- storeConfSyncMempool :: !Bool
- storeConfPeerTimeout :: !NominalDiffTime
- storeConfPeerMaxLife :: !NominalDiffTime
- storeConfConnect :: !(SockAddr -> WithConnection)
- storeConfCacheRetryDelay :: !Int
- storeConfStats :: !(Maybe Store)
- 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 {
- cacheConn :: !Connection
- cacheMin :: !Int
- cacheMax :: !Integer
- cacheChain :: !Chain
- cacheRetryDelay :: !Int
- cacheMetrics :: !(Maybe CacheMetrics)
- type CacheT = ReaderT (Maybe CacheConfig)
- data CacheError
- withCache :: StoreReadBase m => 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
- 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
- getTransaction :: (Monad m, 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)
- data PubExcept
Documentation
Store mailboxes.
Store | |
|
data StoreConfig Source #
Configuration for a Store
.
StoreConfig | |
|
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 #
CacheConfig | |
|
Instances
data CacheError Source #
Instances
withCache :: StoreReadBase m => Maybe CacheConfig -> CacheT m a -> m a Source #
connectRedis :: MonadIO m => String -> m Connection Source #
Store Reader
class Monad m => StoreReadBase m where Source #
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 #
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
Useful Fuctions
getTransaction :: (Monad m, 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 #
Other Data
Instances
Eq PubExcept Source # | |
Show PubExcept Source # | |
Generic PubExcept Source # | |
Exception PubExcept Source # | |
Defined in Haskoin.Store.Common toException :: PubExcept -> SomeException # fromException :: SomeException -> Maybe PubExcept # displayException :: PubExcept -> String # | |
Serialize PubExcept Source # | |
NFData PubExcept Source # | |
Defined in Haskoin.Store.Common | |
type Rep PubExcept Source # | |
Defined in Haskoin.Store.Common type Rep PubExcept = D1 ('MetaData "PubExcept" "Haskoin.Store.Common" "haskoin-store-0.65.0-inplace" 'False) ((C1 ('MetaCons "PubNoPeers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PubReject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RejectCode))) :+: (C1 ('MetaCons "PubTimeout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PubPeerDisconnected" 'PrefixI 'False) (U1 :: Type -> Type))) |