haskoin-store-0.65.5: Storage and index for Bitcoin and Bitcoin Cash
Safe HaskellNone
LanguageHaskell2010

Haskoin.Store.Common

Synopsis

Documentation

data Limits Source #

Constructors

Limits 

Fields

Instances

Instances details
Eq Limits Source # 
Instance details

Defined in Haskoin.Store.Common

Methods

(==) :: Limits -> Limits -> Bool #

(/=) :: Limits -> Limits -> Bool #

Show Limits Source # 
Instance details

Defined in Haskoin.Store.Common

Default Limits Source # 
Instance details

Defined in Haskoin.Store.Common

Methods

def :: Limits

data Start Source #

Constructors

AtTx 

Fields

AtBlock 

Fields

Instances

Instances details
Eq Start Source # 
Instance details

Defined in Haskoin.Store.Common

Methods

(==) :: Start -> Start -> Bool #

(/=) :: Start -> Start -> Bool #

Show Start Source # 
Instance details

Defined in Haskoin.Store.Common

Methods

showsPrec :: Int -> Start -> ShowS #

show :: Start -> String #

showList :: [Start] -> ShowS #

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

Instances details
MonadIO m => StoreReadBase (DatabaseReaderT m) Source # 
Instance details

Defined in Haskoin.Store.Database.Reader

Methods

getNetwork :: DatabaseReaderT m Network Source #

getBestBlock :: DatabaseReaderT m (Maybe BlockHash) Source #

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

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

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

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

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

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

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

MonadIO m => StoreReadBase (WriterT m) Source # 
Instance details

Defined in Haskoin.Store.Database.Writer

Methods

getNetwork :: WriterT m Network Source #

getBestBlock :: WriterT m (Maybe BlockHash) Source #

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

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

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

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

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

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

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

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

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 #

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

Instances

Instances details
MonadUnliftIO m => StoreReadExtra (DatabaseReaderT m) Source # 
Instance details

Defined in Haskoin.Store.Database.Reader

Methods

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

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

getInitialGap :: DatabaseReaderT m Word32 Source #

getMaxGap :: DatabaseReaderT m Word32 Source #

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

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

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

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

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

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

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

xPubTxCount :: XPubSpec -> [XPubBal] -> DatabaseReaderT m Word32 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 #

class StoreWrite m where Source #

Methods

setBest :: BlockHash -> m () Source #

insertBlock :: BlockData -> m () Source #

setBlocksAtHeight :: [BlockHash] -> BlockHeight -> m () Source #

insertTx :: TxData -> m () Source #

insertAddrTx :: Address -> TxRef -> m () Source #

deleteAddrTx :: Address -> TxRef -> m () Source #

insertAddrUnspent :: Address -> Unspent -> m () Source #

deleteAddrUnspent :: Address -> Unspent -> m () Source #

addToMempool :: TxHash -> UnixTime -> m () Source #

deleteFromMempool :: TxHash -> m () Source #

setBalance :: Balance -> m () Source #

insertUnspent :: Unspent -> m () Source #

deleteUnspent :: OutPoint -> m () Source #

Instances

Instances details
MonadIO m => StoreWrite (WriterT m) Source # 
Instance details

Defined in Haskoin.Store.Database.Writer

Methods

setBest :: BlockHash -> WriterT m () Source #

insertBlock :: BlockData -> WriterT m () Source #

setBlocksAtHeight :: [BlockHash] -> BlockHeight -> WriterT m () Source #

insertTx :: TxData -> WriterT m () Source #

insertAddrTx :: Address -> TxRef -> WriterT m () Source #

deleteAddrTx :: Address -> TxRef -> WriterT m () Source #

insertAddrUnspent :: Address -> Unspent -> WriterT m () Source #

deleteAddrUnspent :: Address -> Unspent -> WriterT m () Source #

addToMempool :: TxHash -> UnixTime -> WriterT m () Source #

deleteFromMempool :: TxHash -> WriterT m () Source #

setBalance :: Balance -> WriterT m () Source #

insertUnspent :: Unspent -> WriterT m () Source #

deleteUnspent :: OutPoint -> WriterT m () Source #

data StoreEvent Source #

Events that the store can generate.

Constructors

StoreBestBlock !BlockHash 
StoreMempoolNew !TxHash 
StoreMempoolDelete !TxHash 
StorePeerConnected !Peer 
StorePeerDisconnected !Peer 
StorePeerPong !Peer !Word64 
StoreTxAnnounce !Peer ![TxHash] 
StoreTxReject !Peer !TxHash !RejectCode !ByteString 

data PubExcept Source #

Instances

Instances details
Eq PubExcept Source # 
Instance details

Defined in Haskoin.Store.Common

Show PubExcept Source # 
Instance details

Defined in Haskoin.Store.Common

Generic PubExcept Source # 
Instance details

Defined in Haskoin.Store.Common

Associated Types

type Rep PubExcept :: Type -> Type #

Exception PubExcept Source # 
Instance details

Defined in Haskoin.Store.Common

NFData PubExcept Source # 
Instance details

Defined in Haskoin.Store.Common

Methods

rnf :: PubExcept -> () #

Serialize PubExcept Source # 
Instance details

Defined in Haskoin.Store.Common

Methods

put :: Putter PubExcept

get :: Get PubExcept

type Rep PubExcept Source # 
Instance details

Defined in Haskoin.Store.Common

type Rep PubExcept = D1 ('MetaData "PubExcept" "Haskoin.Store.Common" "haskoin-store-0.65.5-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)))

data DataMetrics Source #

Constructors

DataMetrics 

Fields

getActiveBlock :: StoreReadExtra m => BlockHash -> m (Maybe BlockData) Source #

getActiveTxData :: StoreReadBase m => TxHash -> m (Maybe TxData) Source #

getDefaultBalance :: StoreReadBase m => Address -> m Balance Source #

getTransaction :: (Monad m, StoreReadBase m) => TxHash -> m (Maybe Transaction) Source #

getNumTransaction :: (Monad m, StoreReadExtra m) => Word64 -> m [Transaction] Source #

blockAtOrAfter :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData) Source #

blockAtOrBefore :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData) Source #

blockAtOrAfterMTP :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData) Source #

xPubSummary :: XPubSpec -> [XPubBal] -> XPubSummary Source #

deriveAddresses :: DeriveAddr -> XPubKey -> Word32 -> [(Word32, Address)] Source #

deriveFunction :: DeriveType -> DeriveAddr Source #

applyLimits :: Limits -> [a] -> [a] Source #

applyLimitsC :: Monad m => Limits -> ConduitT i i m () Source #

applyLimit :: Limit -> [a] -> [a] Source #

applyLimitC :: Monad m => Limit -> ConduitT i i m () Source #

sortTxs :: [Tx] -> [(Word32, Tx)] Source #

nub' :: (Eq a, Hashable a) => [a] -> [a] Source #

streamThings :: Monad m => (Limits -> m [a]) -> Maybe (a -> TxHash) -> Limits -> ConduitT () a m () Source #

joinDescStreams :: (Monad m, Ord a) => [ConduitT () a m ()] -> ConduitT () a m () Source #