haskoin-store-0.65.6: Storage and index for Bitcoin and Bitcoin Cash
Safe HaskellSafe-Inferred
LanguageHaskell2010

Haskoin.Store.Cache

Documentation

data CacheConfig Source #

Constructors

CacheConfig 

Fields

Instances

Instances details
(MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) => StoreReadBase (CacheT m) Source # 
Instance details

Defined in Haskoin.Store.Cache

Methods

getNetwork :: CacheT m Network Source #

getBestBlock :: CacheT m (Maybe BlockHash) Source #

getBlocksAtHeight :: BlockHeight -> CacheT m [BlockHash] Source #

getBlock :: BlockHash -> CacheT m (Maybe BlockData) Source #

getTxData :: TxHash -> CacheT m (Maybe TxData) Source #

getSpender :: OutPoint -> CacheT m (Maybe Spender) Source #

getBalance :: Address -> CacheT m (Maybe Balance) Source #

getUnspent :: OutPoint -> CacheT m (Maybe Unspent) Source #

getMempool :: CacheT m [(UnixTime, TxHash)] Source #

(MonadUnliftIO m, MonadLoggerIO m, StoreReadExtra m) => StoreReadExtra (CacheT m) Source # 
Instance details

Defined in Haskoin.Store.Cache

Methods

getAddressesTxs :: [Address] -> Limits -> CacheT m [TxRef] Source #

getAddressesUnspents :: [Address] -> Limits -> CacheT m [Unspent] Source #

getInitialGap :: CacheT m Word32 Source #

getMaxGap :: CacheT m Word32 Source #

getNumTxData :: Word64 -> CacheT m [TxData] Source #

getBalances :: [Address] -> CacheT m [Balance] Source #

getAddressTxs :: Address -> Limits -> CacheT m [TxRef] Source #

getAddressUnspents :: Address -> Limits -> CacheT m [Unspent] Source #

xPubBals :: XPubSpec -> CacheT m [XPubBal] Source #

xPubUnspents :: XPubSpec -> [XPubBal] -> Limits -> CacheT m [XPubUnspent] Source #

xPubTxs :: XPubSpec -> [XPubBal] -> Limits -> CacheT m [TxRef] Source #

xPubTxCount :: XPubSpec -> [XPubBal] -> CacheT m Word32 Source #

data CacheError Source #

Instances

Instances details
Exception CacheError Source # 
Instance details

Defined in Haskoin.Store.Cache

Generic CacheError Source # 
Instance details

Defined in Haskoin.Store.Cache

Associated Types

type Rep CacheError :: Type -> Type #

Show CacheError Source # 
Instance details

Defined in Haskoin.Store.Cache

NFData CacheError Source # 
Instance details

Defined in Haskoin.Store.Cache

Methods

rnf :: CacheError -> () #

Eq CacheError Source # 
Instance details

Defined in Haskoin.Store.Cache

type Rep CacheError Source # 
Instance details

Defined in Haskoin.Store.Cache

type Rep CacheError = D1 ('MetaData "CacheError" "Haskoin.Store.Cache" "haskoin-store-0.65.6-inplace" 'False) (C1 ('MetaCons "RedisError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Reply)) :+: (C1 ('MetaCons "RedisTxError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)) :+: C1 ('MetaCons "LogicError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))

connectRedis :: MonadIO m => String -> m Connection Source #

blockRefScore :: BlockRef -> Double Source #

scoreBlockRef :: Double -> BlockRef Source #

type CacheWriter = Mailbox CacheWriterMessage Source #

type CacheWriterInbox = Inbox CacheWriterMessage Source #

cacheNewTx :: MonadIO m => TxHash -> CacheWriter -> m () Source #

cacheWriter :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadExtra m) => CacheConfig -> CacheWriterInbox -> m () Source #

cacheDelXPubs :: (MonadUnliftIO m, MonadLoggerIO m, StoreReadBase m) => [XPubSpec] -> CacheT m Integer Source #

isInCache :: MonadLoggerIO m => XPubSpec -> CacheT m Bool Source #