| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Haskoin.Store
Synopsis
- data Store = Store {
- storeManager :: !Manager
- storeChain :: !Chain
- storeBlock :: !BlockStore
- type BlockStore = Mailbox BlockMessage
- data StoreConfig = StoreConfig {
- storeConfMaxPeers :: !Int
- storeConfInitPeers :: ![HostPort]
- storeConfDiscover :: !Bool
- storeConfDB :: !DB
- storeConfNetwork :: !Network
- storeConfListen :: !(Listen StoreEvent)
- data StoreEvent
- data BlockData = BlockData {}
- data Transaction = Transaction {}
- data Input
- = Coinbase {
- inputPoint :: !OutPoint
- inputSequence :: !Word32
- inputSigScript :: !ByteString
- inputWitness :: !(Maybe WitnessStack)
- | Input {
- inputPoint :: !OutPoint
- inputSequence :: !Word32
- inputSigScript :: !ByteString
- inputPkScript :: !ByteString
- inputAmount :: !Word64
- inputWitness :: !(Maybe WitnessStack)
- = Coinbase {
- data Output = Output {
- outputAmount :: !Word64
- outputScript :: !ByteString
- outputSpender :: !(Maybe Spender)
- data Spender = Spender {
- spenderHash :: !TxHash
- spenderIndex :: !Word32
- data BlockRef
- = BlockRef { }
- | MemRef {
- memRefTime :: !PreciseUnixTime
- data Unspent = Unspent {}
- data AddressTx = AddressTx {}
- data XPubTx = XPubTx {
- xPubTxPath :: ![KeyIndex]
- xPubTx :: !AddressTx
- data XPubBal = XPubBal {
- xPubBalPath :: ![KeyIndex]
- xPubBal :: !Balance
- data XPubUnspent = XPubUnspent {
- xPubUnspentPath :: ![KeyIndex]
- xPubUnspent :: !Unspent
- data Balance = Balance {
- balanceAddress :: !Address
- balanceAmount :: !Word64
- balanceZero :: !Word64
- balanceCount :: !Word64
- data PeerInformation = PeerInformation {
- peerUserAgent :: !ByteString
- peerAddress :: !SockAddr
- peerVersion :: !Word32
- peerServices :: !Word64
- peerRelay :: !Bool
- withStore :: (MonadLoggerIO m, MonadUnliftIO m) => StoreConfig -> (Store -> m a) -> m a
- store :: (MonadLoggerIO m, MonadUnliftIO m) => StoreConfig -> Inbox ManagerMessage -> Inbox ChainMessage -> Inbox BlockMessage -> m ()
- getBestBlock :: StoreRead r m => r -> m (Maybe BlockHash)
- getBlocksAtHeight :: StoreRead r m => r -> BlockHeight -> m [BlockHash]
- getBlock :: StoreRead r m => r -> BlockHash -> m (Maybe BlockData)
- getTransaction :: (Monad m, StoreRead r m) => r -> TxHash -> m (Maybe Transaction)
- getTxData :: StoreRead r m => r -> TxHash -> m (Maybe TxData)
- getSpenders :: StoreRead r m => r -> TxHash -> m (IntMap Spender)
- getSpender :: StoreRead r m => r -> OutPoint -> m (Maybe Spender)
- fromTransaction :: Transaction -> (TxData, IntMap Spender)
- toTransaction :: TxData -> IntMap Spender -> Transaction
- getBalance :: BalanceRead b m => b -> Address -> m (Maybe Balance)
- getMempool :: StoreStream r m => r -> ConduitT () (PreciseUnixTime, TxHash) m ()
- getAddressUnspents :: StoreStream r m => r -> Address -> ConduitT () Unspent m ()
- getAddressTxs :: StoreStream r m => r -> Address -> ConduitT () AddressTx m ()
- getPeersInformation :: MonadIO m => Manager -> m [PeerInformation]
- xpubTxs :: (Monad m, StoreStream i m) => i -> XPubKey -> ConduitT () XPubTx m ()
- xpubBals :: (Monad m, StoreStream i m, BalanceRead i m) => i -> XPubKey -> m [XPubBal]
- xpubUnspent :: (Monad m, StoreStream i m, StoreRead i m) => i -> XPubKey -> ConduitT () XPubUnspent m ()
- publishTx :: (MonadUnliftIO m, MonadLoggerIO m) => Manager -> Tx -> m Bool
- transactionData :: Transaction -> Tx
- isCoinbase :: Input -> Bool
- confirmed :: BlockRef -> Bool
- transactionToJSON :: Network -> Transaction -> Value
- transactionToEncoding :: Network -> Transaction -> Encoding
- outputToJSON :: Network -> Output -> Value
- outputToEncoding :: Network -> Output -> Encoding
- inputToJSON :: Network -> Input -> Value
- inputToEncoding :: Network -> Input -> Encoding
- unspentToJSON :: Network -> Unspent -> Value
- unspentToEncoding :: Network -> Unspent -> Encoding
- balanceToJSON :: Network -> Balance -> Value
- balanceToEncoding :: Network -> Balance -> Encoding
- addressTxToJSON :: Network -> AddressTx -> Value
- addressTxToEncoding :: Network -> AddressTx -> Encoding
- xPubTxToJSON :: Network -> XPubTx -> Value
- xPubTxToEncoding :: Network -> XPubTx -> Encoding
- xPubBalToJSON :: Network -> XPubBal -> Value
- xPubBalToEncoding :: Network -> XPubBal -> Encoding
- xPubUnspentToJSON :: Network -> XPubUnspent -> Value
- xPubUnspentToEncoding :: Network -> XPubUnspent -> Encoding
- cbAfterHeight :: (Monad m, StoreRead i m) => i -> Int -> BlockHeight -> TxHash -> m (Maybe Bool)
- mergeSourcesBy :: (Foldable f, Monad m) => (a -> a -> Ordering) -> f (ConduitT () a m ()) -> ConduitT i a m ()
Documentation
Store mailboxes.
Constructors
| Store | |
Fields
| |
type BlockStore = Mailbox BlockMessage Source #
Mailbox for block store.
data StoreConfig Source #
Configuration for a Store.
Constructors
| StoreConfig | |
Fields
| |
data StoreEvent Source #
Events that the store can generate.
Constructors
| StoreBestBlock !BlockHash | new best block |
| StoreMempoolNew !TxHash | new mempool transaction |
| StorePeerConnected !Peer !SockAddr | new peer connected |
| StorePeerDisconnected !Peer !SockAddr | peer has disconnected |
| StorePeerPong !Peer !Word64 | peer responded |
Database value for a block entry.
Constructors
| BlockData | |
Fields
| |
Instances
data Transaction Source #
Detailed transaction information.
Constructors
| Transaction | |
Fields
| |
Instances
Input information.
Constructors
| Coinbase | coinbase details |
Fields
| |
| Input | input details |
Fields
| |
Instances
Output information.
Constructors
| Output | |
Fields
| |
Instances
| Eq Output Source # | |
| Ord Output Source # | |
| Read Output Source # | |
| Show Output Source # | |
| Generic Output Source # | |
| Hashable Output Source # | |
Defined in Network.Haskoin.Store.Data | |
| Serialize Output Source # | |
| type Rep Output Source # | |
Defined in Network.Haskoin.Store.Data type Rep Output = D1 (MetaData "Output" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "Output" PrefixI True) (S1 (MetaSel (Just "outputAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64) :*: (S1 (MetaSel (Just "outputScript") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Just "outputSpender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Spender))))) | |
Information about input spending output.
Constructors
| Spender | |
Fields
| |
Instances
| Eq Spender Source # | |
| Ord Spender Source # | |
Defined in Network.Haskoin.Store.Data | |
| Read Spender Source # | |
| Show Spender Source # | |
| Generic Spender Source # | |
| Hashable Spender Source # | |
Defined in Network.Haskoin.Store.Data | |
| ToJSON Spender Source # | |
Defined in Network.Haskoin.Store.Data | |
| Serialize Spender Source # | |
| type Rep Spender Source # | |
Defined in Network.Haskoin.Store.Data type Rep Spender = D1 (MetaData "Spender" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "Spender" PrefixI True) (S1 (MetaSel (Just "spenderHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TxHash) :*: S1 (MetaSel (Just "spenderIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32))) | |
Reference to a block where a transaction is stored.
Constructors
| BlockRef | |
Fields
| |
| MemRef | |
Fields
| |
Instances
| Eq BlockRef Source # | |
| Ord BlockRef Source # | |
Defined in Network.Haskoin.Store.Data | |
| Read BlockRef Source # | |
| Show BlockRef Source # | |
| Generic BlockRef Source # | |
| Hashable BlockRef Source # | |
Defined in Network.Haskoin.Store.Data | |
| ToJSON BlockRef Source # | |
Defined in Network.Haskoin.Store.Data | |
| Serialize BlockRef Source # | |
| type Rep BlockRef Source # | |
Defined in Network.Haskoin.Store.Data | |
Unspent output.
Constructors
| Unspent | |
Fields
| |
Instances
| Eq Unspent Source # | |
| Ord Unspent Source # | |
Defined in Network.Haskoin.Store.Data | |
| Show Unspent Source # | |
| Generic Unspent Source # | |
| Hashable Unspent Source # | |
Defined in Network.Haskoin.Store.Data | |
| Serialize Unspent Source # | |
| type Rep Unspent Source # | |
Defined in Network.Haskoin.Store.Data type Rep Unspent = D1 (MetaData "Unspent" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "Unspent" PrefixI True) ((S1 (MetaSel (Just "unspentBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BlockRef) :*: S1 (MetaSel (Just "unspentPoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OutPoint)) :*: (S1 (MetaSel (Just "unspentAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Just "unspentScript") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ShortByteString)))) | |
Transaction in relation to an address.
Constructors
| AddressTx | |
Fields
| |
Instances
| Eq AddressTx Source # | |
| Ord AddressTx Source # | |
| Show AddressTx Source # | |
| Generic AddressTx Source # | |
| Hashable AddressTx Source # | |
Defined in Network.Haskoin.Store.Data | |
| Serialize AddressTx Source # | |
| type Rep AddressTx Source # | |
Defined in Network.Haskoin.Store.Data type Rep AddressTx = D1 (MetaData "AddressTx" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "AddressTx" PrefixI True) (S1 (MetaSel (Just "addressTxAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Address) :*: (S1 (MetaSel (Just "addressTxBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BlockRef) :*: S1 (MetaSel (Just "addressTxHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TxHash)))) | |
Address transaction from an extended public key.
Constructors
| XPubTx | |
Fields
| |
Instances
| Eq XPubTx Source # | |
| Show XPubTx Source # | |
| Generic XPubTx Source # | |
| type Rep XPubTx Source # | |
Defined in Network.Haskoin.Store.Data type Rep XPubTx = D1 (MetaData "XPubTx" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "XPubTx" PrefixI True) (S1 (MetaSel (Just "xPubTxPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [KeyIndex]) :*: S1 (MetaSel (Just "xPubTx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AddressTx))) | |
Address balances for an extended public key.
Constructors
| XPubBal | |
Fields
| |
Instances
| Eq XPubBal Source # | |
| Show XPubBal Source # | |
| Generic XPubBal Source # | |
| type Rep XPubBal Source # | |
Defined in Network.Haskoin.Store.Data type Rep XPubBal = D1 (MetaData "XPubBal" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "XPubBal" PrefixI True) (S1 (MetaSel (Just "xPubBalPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [KeyIndex]) :*: S1 (MetaSel (Just "xPubBal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Balance))) | |
data XPubUnspent Source #
Unspent transaction for extended public key.
Constructors
| XPubUnspent | |
Fields
| |
Instances
| Eq XPubUnspent Source # | |
Defined in Network.Haskoin.Store.Data | |
| Show XPubUnspent Source # | |
Defined in Network.Haskoin.Store.Data Methods showsPrec :: Int -> XPubUnspent -> ShowS # show :: XPubUnspent -> String # showList :: [XPubUnspent] -> ShowS # | |
| Generic XPubUnspent Source # | |
Defined in Network.Haskoin.Store.Data Associated Types type Rep XPubUnspent :: * -> * # | |
| type Rep XPubUnspent Source # | |
Defined in Network.Haskoin.Store.Data type Rep XPubUnspent = D1 (MetaData "XPubUnspent" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "XPubUnspent" PrefixI True) (S1 (MetaSel (Just "xPubUnspentPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [KeyIndex]) :*: S1 (MetaSel (Just "xPubUnspent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Unspent))) | |
Address balance information.
Constructors
| Balance | |
Fields
| |
Instances
| Eq Balance Source # | |
| Ord Balance Source # | |
Defined in Network.Haskoin.Store.Data | |
| Read Balance Source # | |
| Show Balance Source # | |
| Generic Balance Source # | |
| Hashable Balance Source # | |
Defined in Network.Haskoin.Store.Data | |
| Serialize Balance Source # | |
| type Rep Balance Source # | |
Defined in Network.Haskoin.Store.Data type Rep Balance = D1 (MetaData "Balance" "Network.Haskoin.Store.Data" "haskoin-store-0.6.7-7b3X6k9ipC0Dxz9Qh36xqD" False) (C1 (MetaCons "Balance" PrefixI True) ((S1 (MetaSel (Just "balanceAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Address) :*: S1 (MetaSel (Just "balanceAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64)) :*: (S1 (MetaSel (Just "balanceZero") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Just "balanceCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64)))) | |
data PeerInformation Source #
Information about a connected peer.
Constructors
| PeerInformation | |
Fields
| |
Instances
withStore :: (MonadLoggerIO m, MonadUnliftIO m) => StoreConfig -> (Store -> m a) -> m a Source #
store :: (MonadLoggerIO m, MonadUnliftIO m) => StoreConfig -> Inbox ManagerMessage -> Inbox ChainMessage -> Inbox BlockMessage -> m () Source #
Run a Haskoin Store instance. It will launch a network node and a
BlockStore, connect to the network and start synchronizing blocks and
transactions.
getBestBlock :: StoreRead r m => r -> m (Maybe BlockHash) Source #
getBlocksAtHeight :: StoreRead r m => r -> BlockHeight -> m [BlockHash] Source #
getTransaction :: (Monad m, StoreRead r m) => r -> TxHash -> m (Maybe Transaction) Source #
fromTransaction :: Transaction -> (TxData, IntMap Spender) Source #
toTransaction :: TxData -> IntMap Spender -> Transaction Source #
getMempool :: StoreStream r m => r -> ConduitT () (PreciseUnixTime, TxHash) m () Source #
getPeersInformation :: MonadIO m => Manager -> m [PeerInformation] Source #
Obtain information about connected peers from peer manager process.
xpubUnspent :: (Monad m, StoreStream i m, StoreRead i m) => i -> XPubKey -> ConduitT () XPubUnspent m () Source #
publishTx :: (MonadUnliftIO m, MonadLoggerIO m) => Manager -> Tx -> m Bool Source #
Publish a new transaction to the network.
transactionData :: Transaction -> Tx Source #
transactionToJSON :: Network -> Transaction -> Value Source #
transactionToEncoding :: Network -> Transaction -> Encoding Source #
xPubUnspentToJSON :: Network -> XPubUnspent -> Value Source #
xPubUnspentToEncoding :: Network -> XPubUnspent -> Encoding Source #
cbAfterHeight :: (Monad m, StoreRead i m) => i -> Int -> BlockHeight -> TxHash -> m (Maybe Bool) Source #
Check if any of the ancestors of this transaction is a coinbase after the
specified height. Returns Nothing if answer cannot be computed before
hitting limits.