| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Haskoin.Store.Data
Synopsis
- data Balance = Balance {}
- zeroBalance :: Address -> Balance
- nullBalance :: Balance -> Bool
- data BlockData = BlockData {}
- confirmed :: BlockRef -> Bool
- data TxRef = TxRef {}
- data TxData = TxData {}
- txDataFee :: TxData -> Word64
- isCoinbaseTx :: Tx -> Bool
- data Transaction = Transaction {}
- transactionData :: Transaction -> Tx
- fromTransaction :: Transaction -> TxData
- toTransaction :: Ctx -> TxData -> Transaction
- data StoreInput
- = StoreCoinbase {
- outpoint :: !OutPoint
- sequence :: !Word32
- script :: !ByteString
- witness :: !WitnessStack
- | StoreInput {
- outpoint :: !OutPoint
- sequence :: !Word32
- script :: !ByteString
- pkscript :: !ByteString
- value :: !Word64
- witness :: !WitnessStack
- address :: !(Maybe Address)
- = StoreCoinbase {
- isCoinbase :: StoreInput -> Bool
- data StoreOutput = StoreOutput {}
- data Prev = Prev {
- script :: !ByteString
- value :: !Word64
- data Spender = Spender {}
- data BlockRef
- type UnixTime = Word64
- getUnixTime :: MonadGet m => m Word64
- putUnixTime :: MonadPut m => Word64 -> m ()
- type BlockPos = Word32
- data Unspent = Unspent {}
- data XPubSpec = XPubSpec {
- key :: !XPubKey
- deriv :: !DeriveType
- data XPubBal = XPubBal {}
- data XPubUnspent = XPubUnspent {}
- data XPubSummary = XPubSummary {}
- data DeriveType
- textToDeriveType :: Text -> Maybe DeriveType
- deriveTypeToText :: DeriveType -> Text
- newtype TxId = TxId TxHash
- newtype GenericResult a = GenericResult {
- get :: a
- newtype SerialList a = SerialList {
- get :: [a]
- newtype RawResult a = RawResult {
- get :: a
- newtype RawResultList a = RawResultList {
- get :: [a]
- data PeerInfo = PeerInfo {}
- class Healthy a where
- data BlockHealth = BlockHealth {
- headers :: !BlockHeight
- blocks :: !BlockHeight
- max :: !Int32
- data TimeHealth = TimeHealth {}
- data CountHealth = CountHealth {}
- data MaxHealth = MaxHealth {}
- data HealthCheck = HealthCheck {
- blocks :: !BlockHealth
- lastBlock :: !TimeHealth
- lastTx :: !TimeHealth
- pendingTxs :: !MaxHealth
- peers :: !CountHealth
- network :: !String
- version :: !String
- time :: !Word64
- data Event
- = EventBlock !BlockHash
- | EventTx !TxHash
- data Except
- data BinfoInfo = BinfoInfo {
- connected :: !Word32
- conversion :: !Double
- fiat :: !BinfoSymbol
- crypto :: !BinfoSymbol
- head :: !BinfoBlockInfo
- data BinfoBlockId
- data BinfoTxId
- encodeBinfoTxId :: Bool -> TxHash -> BinfoTxId
- data BinfoFilter
- data BinfoMultiAddr = BinfoMultiAddr {
- addresses :: ![BinfoBalance]
- wallet :: !BinfoWallet
- txs :: ![BinfoTx]
- info :: !BinfoInfo
- recommendFee :: !Bool
- cashAddr :: !Bool
- data BinfoShortBal = BinfoShortBal {}
- data BinfoBalance
- toBinfoAddrs :: HashMap Address Balance -> HashMap XPubSpec [XPubBal] -> HashMap XPubSpec Word64 -> [BinfoBalance]
- data BinfoRawAddr = BinfoRawAddr {}
- data BinfoAddr
- parseBinfoAddr :: Network -> Ctx -> Text -> Maybe [BinfoAddr]
- data BinfoWallet = BinfoWallet {}
- data BinfoUnspent = BinfoUnspent {
- txid :: !TxHash
- index :: !Word32
- script :: !ByteString
- value :: !Word64
- confirmations :: !Int32
- txidx :: !BinfoTxId
- xpub :: !(Maybe BinfoXPubPath)
- binfoHexValue :: Word64 -> Text
- newtype BinfoUnspents = BinfoUnspents [BinfoUnspent]
- data BinfoBlock = BinfoBlock {}
- toBinfoBlock :: BlockData -> [BinfoTx] -> [BlockHash] -> BinfoBlock
- data BinfoTx = BinfoTx {
- txid :: !TxHash
- version :: !Word32
- inputCount :: !Word32
- outputCount :: !Word32
- size :: !Word32
- weight :: !Word32
- fee :: !Word64
- relayed :: !ByteString
- locktime :: !Word32
- index :: !BinfoTxId
- doubleSpend :: !Bool
- rbf :: !Bool
- balance :: !(Maybe (Int64, Int64))
- timestamp :: !Word64
- blockIndex :: !(Maybe Word32)
- blockHeight :: !(Maybe Word32)
- inputs :: ![BinfoTxInput]
- outputs :: ![BinfoTxOutput]
- relevantTxs :: HashSet Address -> Bool -> Transaction -> HashSet TxHash
- toBinfoTx :: Bool -> HashMap Address (Maybe BinfoXPubPath) -> Bool -> Int64 -> Transaction -> BinfoTx
- toBinfoTxSimple :: Bool -> Transaction -> BinfoTx
- data BinfoTxInput = BinfoTxInput {
- sequence :: !Word32
- witness :: !ByteString
- script :: !ByteString
- index :: !Word32
- output :: !BinfoTxOutput
- data BinfoTxOutput = BinfoTxOutput {}
- data BinfoSpender = BinfoSpender {}
- data BinfoXPubPath = BinfoXPubPath {}
- data BinfoBlockInfo = BinfoBlockInfo {
- hash :: !BlockHash
- height :: !BlockHeight
- timestamp :: !Word32
- index :: !BlockHeight
- toBinfoBlockInfo :: BlockData -> BinfoBlockInfo
- data BinfoSymbol = BinfoSymbol {}
- data BinfoTicker = BinfoTicker {}
- data BinfoRate = BinfoRate {}
- data BinfoHistory = BinfoHistory {}
- toBinfoHistory :: Int64 -> Word64 -> Double -> Double -> Word64 -> TxHash -> BinfoHistory
- newtype BinfoDate = BinfoDate Word64
- data BinfoHeader = BinfoHeader {}
- newtype BinfoMempool = BinfoMempool {}
- newtype BinfoBlockInfos = BinfoBlockInfos {
- get :: [BinfoBlockInfo]
Address Balances
Address balance information.
Constructors
| Balance | |
Instances
zeroBalance :: Address -> Balance Source #
nullBalance :: Balance -> Bool Source #
Block Data
Database value for a block entry.
Constructors
| BlockData | |
Fields
| |
Instances
Transactions
Transaction in relation to an address.
Instances
Constructors
| TxData | |
Instances
isCoinbaseTx :: Tx -> Bool Source #
data Transaction Source #
Detailed transaction information.
Constructors
| Transaction | |
Fields
| |
Instances
transactionData :: Transaction -> Tx Source #
fromTransaction :: Transaction -> TxData Source #
toTransaction :: Ctx -> TxData -> Transaction Source #
data StoreInput Source #
Constructors
| StoreCoinbase | |
Fields
| |
| StoreInput | |
Fields
| |
Instances
isCoinbase :: StoreInput -> Bool Source #
data StoreOutput Source #
Output information.
Constructors
| StoreOutput | |
Instances
Constructors
| Prev | |
Fields
| |
Instances
| Generic Prev Source # | |
| Show Prev Source # | |
| Binary Prev Source # | |
| Serial Prev Source # | |
Defined in Haskoin.Store.Data | |
| Serialize Prev Source # | |
| NFData Prev Source # | |
Defined in Haskoin.Store.Data | |
| Eq Prev Source # | |
| Ord Prev Source # | |
| Hashable Prev Source # | |
Defined in Haskoin.Store.Data | |
| type Rep Prev Source # | |
Defined in Haskoin.Store.Data type Rep Prev = D1 ('MetaData "Prev" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "Prev" 'PrefixI 'True) (S1 ('MetaSel ('Just "script") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) | |
Information about input spending output.
Constructors
| Spender | |
Instances
| FromJSON Spender Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON Spender Source # | |
| Generic Spender Source # | |
| Read Spender Source # | |
| Show Spender Source # | |
| Binary Spender Source # | |
| Serial Spender Source # | |
Defined in Haskoin.Store.Data | |
| Serialize Spender Source # | |
| NFData Spender Source # | |
Defined in Haskoin.Store.Data | |
| Eq Spender Source # | |
| Ord Spender Source # | |
| Hashable Spender Source # | |
Defined in Haskoin.Store.Data | |
| type Rep Spender Source # | |
Defined in Haskoin.Store.Data type Rep Spender = D1 ('MetaData "Spender" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "Spender" 'PrefixI 'True) (S1 ('MetaSel ('Just "txid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxHash) :*: S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32))) | |
Reference to a block where a transaction is stored.
Constructors
| BlockRef | |
Fields
| |
| MemRef | |
Instances
getUnixTime :: MonadGet m => m Word64 Source #
putUnixTime :: MonadPut m => Word64 -> m () Source #
Binary such that ordering is inverted.
Unspent Outputs
Unspent output.
Constructors
| Unspent | |
Instances
Extended Public Keys
Constructors
| XPubSpec | |
Fields
| |
Instances
| Generic XPubSpec Source # | |
| Show XPubSpec Source # | |
| Binary XPubSpec Source # | |
| Serial XPubSpec Source # | |
Defined in Haskoin.Store.Data | |
| Serialize XPubSpec Source # | |
| NFData XPubSpec Source # | |
Defined in Haskoin.Store.Data | |
| Eq XPubSpec Source # | |
| Hashable XPubSpec Source # | |
Defined in Haskoin.Store.Data | |
| type Rep XPubSpec Source # | |
Defined in Haskoin.Store.Data type Rep XPubSpec = D1 ('MetaData "XPubSpec" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "XPubSpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 XPubKey) :*: S1 ('MetaSel ('Just "deriv") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DeriveType))) | |
Address balances for an extended public key.
Instances
data XPubUnspent Source #
Unspent transaction for extended public key.
Constructors
| XPubUnspent | |
Instances
data XPubSummary Source #
Constructors
| XPubSummary | |
Instances
data DeriveType Source #
Constructors
| DeriveNormal | |
| DeriveP2SH | |
| DeriveP2WPKH |
Instances
textToDeriveType :: Text -> Maybe DeriveType Source #
deriveTypeToText :: DeriveType -> Text Source #
Other Data
Instances
| FromJSON TxId Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON TxId Source # | |
| Generic TxId Source # | |
| Show TxId Source # | |
| Binary TxId Source # | |
| Serial TxId Source # | |
Defined in Haskoin.Store.Data | |
| Serialize TxId Source # | |
| NFData TxId Source # | |
Defined in Haskoin.Store.Data | |
| Eq TxId Source # | |
| ApiResource PostTx TxId Source # | |
Defined in Haskoin.Store.WebCommon | |
| type Rep TxId Source # | |
Defined in Haskoin.Store.Data | |
newtype GenericResult a Source #
Constructors
| GenericResult | |
Fields
| |
Instances
newtype SerialList a Source #
Constructors
| SerialList | |
Fields
| |
Instances
Instances
newtype RawResultList a Source #
Constructors
| RawResultList | |
Fields
| |
Instances
Information about a connected peer.
Constructors
| PeerInfo | |
Instances
class Healthy a where Source #
Instances
| Healthy BlockHealth Source # | |
Defined in Haskoin.Store.Data Methods isOK :: BlockHealth -> Bool Source # | |
| Healthy CountHealth Source # | |
Defined in Haskoin.Store.Data Methods isOK :: CountHealth -> Bool Source # | |
| Healthy HealthCheck Source # | |
Defined in Haskoin.Store.Data Methods isOK :: HealthCheck -> Bool Source # | |
| Healthy MaxHealth Source # | |
| Healthy TimeHealth Source # | |
Defined in Haskoin.Store.Data Methods isOK :: TimeHealth -> Bool Source # | |
data BlockHealth Source #
Constructors
| BlockHealth | |
Fields
| |
Instances
data TimeHealth Source #
Constructors
| TimeHealth | |
Instances
data CountHealth Source #
Constructors
| CountHealth | |
Instances
Instances
| FromJSON MaxHealth Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON MaxHealth Source # | |
| Generic MaxHealth Source # | |
| Show MaxHealth Source # | |
| Binary MaxHealth Source # | |
| Serial MaxHealth Source # | |
Defined in Haskoin.Store.Data | |
| Serialize MaxHealth Source # | |
| NFData MaxHealth Source # | |
Defined in Haskoin.Store.Data | |
| Eq MaxHealth Source # | |
| Healthy MaxHealth Source # | |
| type Rep MaxHealth Source # | |
Defined in Haskoin.Store.Data type Rep MaxHealth = D1 ('MetaData "MaxHealth" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "MaxHealth" 'PrefixI 'True) (S1 ('MetaSel ('Just "count") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "max") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64))) | |
data HealthCheck Source #
Constructors
| HealthCheck | |
Fields
| |
Instances
Constructors
| EventBlock !BlockHash | |
| EventTx !TxHash |
Instances
| FromJSON Event Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON Event Source # | |
| Generic Event Source # | |
| Show Event Source # | |
| Binary Event Source # | |
| Serial Event Source # | |
Defined in Haskoin.Store.Data | |
| Serialize Event Source # | |
| NFData Event Source # | |
Defined in Haskoin.Store.Data | |
| Eq Event Source # | |
| ApiResource GetEvents (SerialList Event) Source # | |
Defined in Haskoin.Store.WebCommon | |
| type Rep Event Source # | |
Defined in Haskoin.Store.Data type Rep Event = D1 ('MetaData "Event" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "EventBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockHash)) :+: C1 ('MetaCons "EventTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxHash))) | |
Constructors
| ThingNotFound | |
| ServerError | |
| BadRequest | |
| UserError !String | |
| StringError !String | |
| TxIndexConflict ![TxHash] | |
| ServerTimeout | |
| RequestTooLarge |
Instances
Blockchain.info API
Constructors
| BinfoInfo | |
Fields
| |
Instances
| FromJSON BinfoInfo Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON BinfoInfo Source # | |
| Generic BinfoInfo Source # | |
| Show BinfoInfo Source # | |
| NFData BinfoInfo Source # | |
Defined in Haskoin.Store.Data | |
| Eq BinfoInfo Source # | |
| type Rep BinfoInfo Source # | |
Defined in Haskoin.Store.Data type Rep BinfoInfo = D1 ('MetaData "BinfoInfo" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "BinfoInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "connected") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "conversion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "fiat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinfoSymbol) :*: (S1 ('MetaSel ('Just "crypto") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinfoSymbol) :*: S1 ('MetaSel ('Just "head") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinfoBlockInfo))))) | |
data BinfoBlockId Source #
Constructors
| BinfoBlockHash !BlockHash | |
| BinfoBlockIndex !Word32 |
Instances
Constructors
| BinfoTxIdHash !TxHash | |
| BinfoTxIdIndex !Word64 |
Instances
| FromJSON BinfoTxId Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON BinfoTxId Source # | |
| Generic BinfoTxId Source # | |
| Read BinfoTxId Source # | |
| Show BinfoTxId Source # | |
| NFData BinfoTxId Source # | |
Defined in Haskoin.Store.Data | |
| Eq BinfoTxId Source # | |
| Parsable BinfoTxId Source # | |
Defined in Haskoin.Store.Data | |
| type Rep BinfoTxId Source # | |
Defined in Haskoin.Store.Data type Rep BinfoTxId = D1 ('MetaData "BinfoTxId" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "BinfoTxIdHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxHash)) :+: C1 ('MetaCons "BinfoTxIdIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) | |
data BinfoFilter Source #
Constructors
| BinfoFilterAll | |
| BinfoFilterSent | |
| BinfoFilterReceived | |
| BinfoFilterMoved | |
| BinfoFilterConfirmed | |
| BinfoFilterMempool |
Instances
data BinfoMultiAddr Source #
Constructors
| BinfoMultiAddr | |
Fields
| |
Instances
data BinfoShortBal Source #
Instances
data BinfoBalance Source #
Constructors
| BinfoAddrBalance | |
| BinfoXPubBalance | |
Instances
toBinfoAddrs :: HashMap Address Balance -> HashMap XPubSpec [XPubBal] -> HashMap XPubSpec Word64 -> [BinfoBalance] Source #
data BinfoRawAddr Source #
Constructors
| BinfoRawAddr | |
Instances
Instances
| Generic BinfoAddr Source # | |
| Show BinfoAddr Source # | |
| NFData BinfoAddr Source # | |
Defined in Haskoin.Store.Data | |
| Eq BinfoAddr Source # | |
| Hashable BinfoAddr Source # | |
Defined in Haskoin.Store.Data | |
| type Rep BinfoAddr Source # | |
Defined in Haskoin.Store.Data type Rep BinfoAddr = D1 ('MetaData "BinfoAddr" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "BinfoAddr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Address)) :+: C1 ('MetaCons "BinfoXpub" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 XPubKey))) | |
data BinfoWallet Source #
Constructors
| BinfoWallet | |
Instances
data BinfoUnspent Source #
Constructors
| BinfoUnspent | |
Fields
| |
Instances
binfoHexValue :: Word64 -> Text Source #
newtype BinfoUnspents Source #
Constructors
| BinfoUnspents [BinfoUnspent] |
Instances
data BinfoBlock Source #
Constructors
| BinfoBlock | |
Instances
toBinfoBlock :: BlockData -> [BinfoTx] -> [BlockHash] -> BinfoBlock Source #
Constructors
| BinfoTx | |
Fields
| |
Instances
relevantTxs :: HashSet Address -> Bool -> Transaction -> HashSet TxHash Source #
toBinfoTx :: Bool -> HashMap Address (Maybe BinfoXPubPath) -> Bool -> Int64 -> Transaction -> BinfoTx Source #
toBinfoTxSimple :: Bool -> Transaction -> BinfoTx Source #
data BinfoTxInput Source #
Constructors
| BinfoTxInput | |
Fields
| |
Instances
data BinfoTxOutput Source #
Constructors
| BinfoTxOutput | |
Instances
data BinfoSpender Source #
Constructors
| BinfoSpender | |
Instances
data BinfoXPubPath Source #
Constructors
| BinfoXPubPath | |
Instances
data BinfoBlockInfo Source #
Constructors
| BinfoBlockInfo | |
Fields
| |
Instances
data BinfoSymbol Source #
Constructors
| BinfoSymbol | |
Instances
data BinfoTicker Source #
Constructors
| BinfoTicker | |
Instances
Instances
| FromJSON BinfoRate Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON BinfoRate Source # | |
| Generic BinfoRate Source # | |
| Show BinfoRate Source # | |
| NFData BinfoRate Source # | |
Defined in Haskoin.Store.Data | |
| Eq BinfoRate Source # | |
| type Rep BinfoRate Source # | |
Defined in Haskoin.Store.Data type Rep BinfoRate = D1 ('MetaData "BinfoRate" "Haskoin.Store.Data" "haskoin-store-data-1.2.2-inplace" 'False) (C1 ('MetaCons "BinfoRate" 'PrefixI 'True) (S1 ('MetaSel ('Just "timestamp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "price") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "vol24") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)))) | |
data BinfoHistory Source #
Constructors
| BinfoHistory | |
Instances
toBinfoHistory :: Int64 -> Word64 -> Double -> Double -> Word64 -> TxHash -> BinfoHistory Source #
data BinfoHeader Source #
Constructors
| BinfoHeader | |
Instances
newtype BinfoMempool Source #
Constructors
| BinfoMempool | |
Instances
newtype BinfoBlockInfos Source #
Constructors
| BinfoBlockInfos | |
Fields
| |