Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Limits = Limits {}
- data Start
- = AtTx !TxHash
- | AtBlock !BlockHeight
- class Monad m => StoreReadBase (m :: Type -> Type) 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 :: Type -> Type) 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
- class StoreWrite (m :: Type -> Type) where
- setBest :: BlockHash -> m ()
- insertBlock :: BlockData -> m ()
- setBlocksAtHeight :: [BlockHash] -> BlockHeight -> m ()
- insertTx :: TxData -> m ()
- insertAddrTx :: Address -> TxRef -> m ()
- deleteAddrTx :: Address -> TxRef -> m ()
- insertAddrUnspent :: Address -> Unspent -> m ()
- deleteAddrUnspent :: Address -> Unspent -> m ()
- addToMempool :: TxHash -> UnixTime -> m ()
- deleteFromMempool :: TxHash -> m ()
- setBalance :: Balance -> m ()
- insertUnspent :: Unspent -> m ()
- deleteUnspent :: OutPoint -> m ()
- data StoreEvent
- getActiveBlock :: StoreReadExtra m => BlockHash -> m (Maybe BlockData)
- getActiveTxData :: StoreReadBase m => TxHash -> m (Maybe TxData)
- getDefaultBalance :: StoreReadBase m => Address -> m Balance
- getTransaction :: StoreReadBase m => TxHash -> m (Maybe Transaction)
- getNumTransaction :: StoreReadExtra m => Word64 -> m [Transaction]
- blockAtOrAfter :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData)
- blockAtOrBefore :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData)
- blockAtOrAfterMTP :: (MonadIO m, StoreReadExtra m) => Chain -> UnixTime -> m (Maybe BlockData)
- xPubSummary :: XPubSpec -> [XPubBal] -> XPubSummary
- deriveAddresses :: DeriveAddr -> XPubKey -> Word32 -> [(Word32, Address)]
- deriveFunction :: Ctx -> DeriveType -> DeriveAddr
- deOffset :: Limits -> Limits
- applyLimits :: Limits -> [a] -> [a]
- applyLimitsC :: forall (m :: Type -> Type) i. Monad m => Limits -> ConduitT i i m ()
- applyLimit :: Limit -> [a] -> [a]
- applyLimitC :: forall (m :: Type -> Type) i. Monad m => Limit -> ConduitT i i m ()
- sortTxs :: [Tx] -> [(Word32, Tx)]
- nub' :: Hashable a => [a] -> [a]
- microseconds :: MonadIO m => m Integer
- streamThings :: Monad m => (Limits -> m [a]) -> Maybe (a -> TxHash) -> Limits -> ConduitT () a m ()
- joinDescStreams :: forall (m :: Type -> Type) a. (Monad m, Ord a) => [ConduitT () a m ()] -> ConduitT () a m ()
Documentation
class Monad m => StoreReadBase (m :: Type -> Type) 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 :: Type -> Type) 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
class StoreWrite (m :: Type -> Type) where Source #
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
MonadIO m => StoreWrite (WriterT m) Source # | |
Defined in Haskoin.Store.Database.Writer 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.
getActiveBlock :: StoreReadExtra m => BlockHash -> m (Maybe BlockData) Source #
getActiveTxData :: StoreReadBase m => TxHash -> m (Maybe TxData) Source #
getDefaultBalance :: StoreReadBase m => Address -> m Balance Source #
getTransaction :: StoreReadBase m => TxHash -> m (Maybe Transaction) Source #
getNumTransaction :: 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 #
deriveFunction :: Ctx -> DeriveType -> DeriveAddr Source #
applyLimits :: Limits -> [a] -> [a] Source #
applyLimit :: Limit -> [a] -> [a] Source #
microseconds :: MonadIO m => m Integer Source #