| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Haskoin.Store.Data
Synopsis
- data Balance = Balance {}
- balanceToJSON :: Network -> Balance -> Value
- balanceToEncoding :: Network -> Balance -> Encoding
- balanceParseJSON :: Network -> Value -> Parser Balance
- zeroBalance :: Address -> Balance
- nullBalance :: Balance -> Bool
- data BlockData = BlockData {}
- blockDataToJSON :: Network -> BlockData -> Value
- blockDataToEncoding :: Network -> BlockData -> Encoding
- confirmed :: BlockRef -> Bool
- data TxRef = TxRef {
- txRefBlock :: !BlockRef
- txRefHash :: !TxHash
- data TxData = TxData {
- txDataBlock :: !BlockRef
- txData :: !Tx
- txDataPrevs :: !(IntMap Prev)
- txDataDeleted :: !Bool
- txDataRBF :: !Bool
- txDataTime :: !Word64
- data Transaction = Transaction {
- transactionBlock :: !BlockRef
- transactionVersion :: !Word32
- transactionLockTime :: !Word32
- transactionInputs :: ![StoreInput]
- transactionOutputs :: ![StoreOutput]
- transactionDeleted :: !Bool
- transactionRBF :: !Bool
- transactionTime :: !Word64
- transactionId :: !TxHash
- transactionSize :: !Word32
- transactionWeight :: !Word32
- transactionFees :: !Word64
- transactionToJSON :: Network -> Transaction -> Value
- transactionToEncoding :: Network -> Transaction -> Encoding
- transactionParseJSON :: Network -> Value -> Parser Transaction
- transactionData :: Transaction -> Tx
- fromTransaction :: Transaction -> (TxData, IntMap Spender)
- toTransaction :: TxData -> IntMap Spender -> Transaction
- data StoreInput
- = StoreCoinbase { }
- | StoreInput {
- inputPoint :: !OutPoint
- inputSequence :: !Word32
- inputSigScript :: !ByteString
- inputPkScript :: !ByteString
- inputAmount :: !Word64
- inputWitness :: !WitnessStack
- inputAddress :: !(Maybe Address)
- storeInputToJSON :: Network -> StoreInput -> Value
- storeInputToEncoding :: Network -> StoreInput -> Encoding
- storeInputParseJSON :: Network -> Value -> Parser StoreInput
- isCoinbase :: StoreInput -> Bool
- data StoreOutput = StoreOutput {
- outputAmount :: !Word64
- outputScript :: !ByteString
- outputSpender :: !(Maybe Spender)
- outputAddress :: !(Maybe Address)
- storeOutputToJSON :: Network -> StoreOutput -> Value
- storeOutputToEncoding :: Network -> StoreOutput -> Encoding
- storeOutputParseJSON :: Network -> Value -> Parser StoreOutput
- data Prev = Prev {
- prevScript :: !ByteString
- prevAmount :: !Word64
- data Spender = Spender {
- spenderHash :: !TxHash
- spenderIndex :: !Word32
- data BlockRef
- = BlockRef { }
- | MemRef {
- memRefTime :: !UnixTime
- type UnixTime = Word64
- getUnixTime :: Get Word64
- putUnixTime :: Word64 -> Put
- type BlockPos = Word32
- data Unspent = Unspent {}
- unspentToJSON :: Network -> Unspent -> Value
- unspentToEncoding :: Network -> Unspent -> Encoding
- unspentParseJSON :: Network -> Value -> Parser Unspent
- data XPubSpec = XPubSpec {}
- data XPubBal = XPubBal {
- xPubBalPath :: ![KeyIndex]
- xPubBal :: !Balance
- xPubBalToJSON :: Network -> XPubBal -> Value
- xPubBalToEncoding :: Network -> XPubBal -> Encoding
- xPubBalParseJSON :: Network -> Value -> Parser XPubBal
- data XPubUnspent = XPubUnspent {
- xPubUnspentPath :: ![KeyIndex]
- xPubUnspent :: !Unspent
- xPubUnspentToJSON :: Network -> XPubUnspent -> Value
- xPubUnspentToEncoding :: Network -> XPubUnspent -> Encoding
- xPubUnspentParseJSON :: Network -> Value -> Parser XPubUnspent
- data XPubSummary = XPubSummary {}
- data DeriveType
- newtype TxId = TxId TxHash
- newtype GenericResult a = GenericResult {
- getResult :: a
- newtype RawResult a = RawResult {
- getRawResult :: a
- newtype RawResultList a = RawResultList {
- getRawResultList :: [a]
- data PeerInformation = PeerInformation {
- peerUserAgent :: !ByteString
- peerAddress :: !String
- peerVersion :: !Word32
- peerServices :: !Word64
- peerRelay :: !Bool
- class Healthy a where
- data BlockHealth = BlockHealth {}
- data TimeHealth = TimeHealth {
- timeHealthAge :: !Int
- timeHealthMax :: !Int
- data CountHealth = CountHealth {
- countHealthNum :: !Int
- countHealthMin :: !Int
- data MaxHealth = MaxHealth {
- maxHealthNum :: !Int
- maxHealthMax :: !Int
- data HealthCheck = HealthCheck {}
- data Event
- = EventBlock !BlockHash
- | EventTx !TxHash
- data Except
- type BinfoTxIndex = Int64
- isBinfoTxIndexNull :: BinfoTxIndex -> Bool
- isBinfoTxIndexBlock :: BinfoTxIndex -> Bool
- isBinfoTxIndexHash :: BinfoTxIndex -> Bool
- encodeBinfoTxIndexHash :: BinfoTxIndex -> Maybe ByteString
- hashToBinfoTxIndex :: TxHash -> BinfoTxIndex
- blockToBinfoTxIndex :: BlockHeight -> Word32 -> BinfoTxIndex
- matchBinfoTxHash :: Int64 -> TxHash -> Bool
- binfoTxIndexBlock :: BinfoTxIndex -> Maybe (BlockHeight, Word32)
- binfoTransactionIndex :: Bool -> Transaction -> BinfoTxId
- data BinfoTxId
- data BinfoMultiAddr = BinfoMultiAddr {}
- binfoMultiAddrToJSON :: Network -> BinfoMultiAddr -> Value
- binfoMultiAddrToEncoding :: Network -> BinfoMultiAddr -> Encoding
- binfoMultiAddrParseJSON :: Network -> Value -> Parser BinfoMultiAddr
- data BinfoAddress
- = BinfoAddress { }
- | BinfoXPubKey { }
- toBinfoAddrs :: HashMap Address Balance -> HashMap XPubKey [XPubBal] -> HashMap XPubKey Int -> [BinfoAddress]
- binfoAddressToJSON :: Network -> BinfoAddress -> Value
- binfoAddressToEncoding :: Network -> BinfoAddress -> Encoding
- binfoAddressParseJSON :: Network -> Value -> Parser BinfoAddress
- data BinfoAddr
- parseBinfoAddr :: Network -> Text -> Maybe [BinfoAddr]
- data BinfoWallet = BinfoWallet {}
- data BinfoTx = BinfoTx {
- getBinfoTxHash :: !TxHash
- getBinfoTxVer :: !Word32
- getBinfoTxVinSz :: !Word32
- getBinfoTxVoutSz :: !Word32
- getBinfoTxSize :: !Word32
- getBinfoTxWeight :: !Word32
- getBinfoTxFee :: !Word64
- getBinfoTxRelayedBy :: !ByteString
- getBinfoTxLockTime :: !Word32
- getBinfoTxIndex :: !BinfoTxId
- getBinfoTxDoubleSpend :: !Bool
- getBinfoTxResultBal :: !(Maybe (Int64, Int64))
- getBinfoTxTime :: !Word64
- getBinfoTxBlockIndex :: !(Maybe Word32)
- getBinfoTxBlockHeight :: !(Maybe Word32)
- getBinfoTxInputs :: [BinfoTxInput]
- getBinfoTxOutputs :: [BinfoTxOutput]
- relevantTxs :: HashSet Address -> Bool -> Transaction -> HashSet TxHash
- toBinfoTx :: Maybe (HashMap TxHash Transaction) -> HashMap Address (Maybe BinfoXPubPath) -> HashSet Address -> Bool -> Int64 -> Transaction -> BinfoTx
- toBinfoTxSimple :: Maybe (HashMap TxHash Transaction) -> Transaction -> BinfoTx
- binfoTxToJSON :: Network -> BinfoTx -> Value
- binfoTxToEncoding :: Network -> BinfoTx -> Encoding
- binfoTxParseJSON :: Network -> Value -> Parser BinfoTx
- data BinfoTxInput = BinfoTxInput {}
- binfoTxInputToJSON :: Network -> BinfoTxInput -> Value
- binfoTxInputToEncoding :: Network -> BinfoTxInput -> Encoding
- binfoTxInputParseJSON :: Network -> Value -> Parser BinfoTxInput
- data BinfoTxOutput = BinfoTxOutput {
- getBinfoTxOutputType :: !Int
- getBinfoTxOutputSpent :: !Bool
- getBinfoTxOutputValue :: !Word64
- getBinfoTxOutputIndex :: !Word32
- getBinfoTxOutputTxIndex :: !BinfoTxId
- getBinfoTxOutputScript :: !ByteString
- getBinfoTxOutputSpenders :: ![BinfoSpender]
- getBinfoTxOutputAddress :: !(Maybe Address)
- getBinfoTxOutputXPub :: !(Maybe BinfoXPubPath)
- binfoTxOutputToJSON :: Network -> BinfoTxOutput -> Value
- binfoTxOutputToEncoding :: Network -> BinfoTxOutput -> Encoding
- binfoTxOutputParseJSON :: Network -> Value -> Parser BinfoTxOutput
- data BinfoSpender = BinfoSpender {}
- data BinfoXPubPath = BinfoXPubPath {}
- binfoXPubPathToJSON :: Network -> BinfoXPubPath -> Value
- binfoXPubPathToEncoding :: Network -> BinfoXPubPath -> Encoding
- binfoXPubPathParseJSON :: Network -> Value -> Parser BinfoXPubPath
- data BinfoInfo = BinfoInfo {}
- data BinfoBlockInfo = BinfoBlockInfo {}
- data BinfoSymbol = BinfoSymbol {}
- data BinfoTicker = BinfoTicker {}
Address Balances
Address balance information.
Constructors
| Balance | |
Fields
| |
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.
Constructors
| TxRef | |
Fields
| |
Instances
Constructors
| TxData | |
Fields
| |
Instances
| Eq TxData Source # | |
| Ord TxData Source # | |
| Show TxData Source # | |
| Generic TxData Source # | |
| Serialize TxData Source # | |
| NFData TxData Source # | |
Defined in Haskoin.Store.Data | |
| type Rep TxData Source # | |
Defined in Haskoin.Store.Data type Rep TxData = D1 ('MetaData "TxData" "Haskoin.Store.Data" "haskoin-store-data-0.40.2-inplace" 'False) (C1 ('MetaCons "TxData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "txDataBlock") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockRef) :*: (S1 ('MetaSel ('Just "txData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tx) :*: S1 ('MetaSel ('Just "txDataPrevs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IntMap Prev)))) :*: (S1 ('MetaSel ('Just "txDataDeleted") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "txDataRBF") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "txDataTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))))) | |
data Transaction Source #
Detailed transaction information.
Constructors
| Transaction | |
Fields
| |
Instances
transactionToJSON :: Network -> Transaction -> Value Source #
transactionToEncoding :: Network -> Transaction -> Encoding Source #
transactionParseJSON :: Network -> Value -> Parser Transaction Source #
transactionData :: Transaction -> Tx Source #
fromTransaction :: Transaction -> (TxData, IntMap Spender) Source #
toTransaction :: TxData -> IntMap Spender -> Transaction Source #
data StoreInput Source #
Constructors
| StoreCoinbase | |
Fields
| |
| StoreInput | |
Fields
| |
Instances
storeInputToJSON :: Network -> StoreInput -> Value Source #
storeInputToEncoding :: Network -> StoreInput -> Encoding Source #
storeInputParseJSON :: Network -> Value -> Parser StoreInput Source #
isCoinbase :: StoreInput -> Bool Source #
data StoreOutput Source #
Output information.
Constructors
| StoreOutput | |
Fields
| |
Instances
storeOutputToJSON :: Network -> StoreOutput -> Value Source #
storeOutputToEncoding :: Network -> StoreOutput -> Encoding Source #
storeOutputParseJSON :: Network -> Value -> Parser StoreOutput Source #
Constructors
| Prev | |
Fields
| |
Instances
| Eq Prev Source # | |
| Ord Prev Source # | |
| Show Prev Source # | |
| Generic Prev Source # | |
| Hashable Prev Source # | |
Defined in Haskoin.Store.Data | |
| Serialize Prev Source # | |
| NFData 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-0.40.2-inplace" 'False) (C1 ('MetaCons "Prev" 'PrefixI 'True) (S1 ('MetaSel ('Just "prevScript") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "prevAmount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) | |
Information about input spending output.
Constructors
| Spender | |
Fields
| |
Instances
| Eq Spender Source # | |
| Ord Spender Source # | |
| Read Spender Source # | |
| Show Spender Source # | |
| Generic Spender Source # | |
| Hashable Spender Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON Spender Source # | |
Defined in Haskoin.Store.Data | |
| FromJSON Spender Source # | |
| Serialize Spender Source # | |
| NFData 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-0.40.2-inplace" '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 Haskoin.Store.Data | |
| Read BlockRef Source # | |
| Show BlockRef Source # | |
| Generic BlockRef Source # | |
| Hashable BlockRef Source # | |
Defined in Haskoin.Store.Data | |
| ToJSON BlockRef Source # | |
Defined in Haskoin.Store.Data | |
| FromJSON BlockRef Source # | |
| Serialize BlockRef Source # | Serialized entities will sort in reverse order. |
| NFData BlockRef Source # | |
Defined in Haskoin.Store.Data | |
| type Rep BlockRef Source # | |
Defined in Haskoin.Store.Data type Rep BlockRef = D1 ('MetaData "BlockRef" "Haskoin.Store.Data" "haskoin-store-data-0.40.2-inplace" 'False) (C1 ('MetaCons "BlockRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "blockRefHeight") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockHeight) :*: S1 ('MetaSel ('Just "blockRefPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)) :+: C1 ('MetaCons "MemRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "memRefTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnixTime))) | |
getUnixTime :: Get Word64 Source #
putUnixTime :: Word64 -> Put Source #
Serialize such that ordering is inverted.
Unspent Outputs
Unspent output.
Constructors
| Unspent | |
Fields
| |
Instances
Extended Public Keys
Constructors
| XPubSpec | |
Fields
| |
Instances
| Eq XPubSpec Source # | |
| Show XPubSpec Source # | |
| Generic XPubSpec Source # | |
| Hashable XPubSpec Source # | |
Defined in Haskoin.Store.Data | |
| Serialize XPubSpec Source # | |
| NFData 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-0.40.2-inplace" 'False) (C1 ('MetaCons "XPubSpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "xPubSpecKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 XPubKey) :*: S1 ('MetaSel ('Just "xPubDeriveType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DeriveType))) | |
Address balances for an extended public key.
Constructors
| XPubBal | |
Fields
| |
Instances
| Eq XPubBal Source # | |
| Ord XPubBal Source # | |
| Show XPubBal Source # | |
| Generic XPubBal Source # | |
| Serialize XPubBal Source # | |
| NFData XPubBal Source # | |
Defined in Haskoin.Store.Data | |
| ApiResource GetXPubBalances [XPubBal] Source # | |
Defined in Haskoin.Store.WebCommon Methods resourceMethod :: Proxy GetXPubBalances -> StdMethod Source # resourcePath :: Proxy GetXPubBalances -> [Text] -> Text Source # queryParams :: GetXPubBalances -> ([ParamBox], [ParamBox]) Source # captureParams :: Proxy GetXPubBalances -> [ProxyBox] Source # | |
| type Rep XPubBal Source # | |
Defined in Haskoin.Store.Data type Rep XPubBal = D1 ('MetaData "XPubBal" "Haskoin.Store.Data" "haskoin-store-data-0.40.2-inplace" '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
xPubUnspentToJSON :: Network -> XPubUnspent -> Value Source #
xPubUnspentToEncoding :: Network -> XPubUnspent -> Encoding Source #
xPubUnspentParseJSON :: Network -> Value -> Parser XPubUnspent Source #
data XPubSummary Source #
Constructors
| XPubSummary | |
Fields
| |
Instances
data DeriveType Source #
Constructors
| DeriveNormal | |
| DeriveP2SH | |
| DeriveP2WPKH |
Instances
Other Data
Instances
| Eq TxId Source # | |
| Show TxId Source # | |
| Generic TxId Source # | |
| ToJSON TxId Source # | |
Defined in Haskoin.Store.Data | |
| FromJSON TxId Source # | |
| Serialize TxId Source # | |
| NFData TxId Source # | |
Defined in Haskoin.Store.Data | |
| 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
Constructors
| RawResult | |
Fields
| |
Instances
newtype RawResultList a Source #
Constructors
| RawResultList | |
Fields
| |
Instances
data PeerInformation Source #
Information about a connected peer.
Constructors
| PeerInformation | |
Fields
| |
Instances
class Healthy a where Source #
Instances
| Healthy HealthCheck Source # | |
Defined in Haskoin.Store.Data Methods isOK :: HealthCheck -> Bool Source # | |
| Healthy MaxHealth Source # | |
| Healthy CountHealth Source # | |
Defined in Haskoin.Store.Data Methods isOK :: CountHealth -> Bool Source # | |
| Healthy TimeHealth Source # | |
Defined in Haskoin.Store.Data Methods isOK :: TimeHealth -> Bool Source # | |
| Healthy BlockHealth Source # | |
Defined in Haskoin.Store.Data Methods isOK :: BlockHealth -> Bool Source # | |
data BlockHealth Source #
Constructors
| BlockHealth | |
Fields | |
Instances
data TimeHealth Source #
Constructors
| TimeHealth | |
Fields
| |
Instances
data CountHealth Source #
Constructors
| CountHealth | |
Fields
| |
Instances
Constructors
| MaxHealth | |
Fields
| |
Instances
| Eq MaxHealth Source # | |
| Show MaxHealth Source # | |
| Generic MaxHealth Source # | |
| ToJSON MaxHealth Source # | |
Defined in Haskoin.Store.Data | |
| FromJSON MaxHealth Source # | |
| Serialize MaxHealth Source # | |
| NFData MaxHealth Source # | |
Defined in Haskoin.Store.Data | |
| Healthy MaxHealth Source # | |
| type Rep MaxHealth Source # | |
Defined in Haskoin.Store.Data type Rep MaxHealth = D1 ('MetaData "MaxHealth" "Haskoin.Store.Data" "haskoin-store-data-0.40.2-inplace" 'False) (C1 ('MetaCons "MaxHealth" 'PrefixI 'True) (S1 ('MetaSel ('Just "maxHealthNum") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "maxHealthMax") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) | |
data HealthCheck Source #
Constructors
| HealthCheck | |
Fields
| |
Instances
Constructors
| EventBlock !BlockHash | |
| EventTx !TxHash |
Instances
| Eq Event Source # | |
| Show Event Source # | |
| Generic Event Source # | |
| ToJSON Event Source # | |
Defined in Haskoin.Store.Data | |
| FromJSON Event Source # | |
| Serialize Event Source # | |
| NFData Event Source # | |
Defined in Haskoin.Store.Data | |
| ApiResource GetEvents [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-0.40.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 | |
| BlockTooLarge |
Instances
Blockchain.info API
type BinfoTxIndex = Int64 Source #
blockToBinfoTxIndex :: BlockHeight -> Word32 -> BinfoTxIndex Source #
binfoTxIndexBlock :: BinfoTxIndex -> Maybe (BlockHeight, Word32) Source #
binfoTransactionIndex :: Bool -> Transaction -> BinfoTxId Source #
Constructors
| BinfoTxIdHash !TxHash | |
| BinfoTxIdIndex !BinfoTxIndex |
Instances
| Eq BinfoTxId Source # | |
| Read BinfoTxId Source # | |
| Show BinfoTxId Source # | |
| Generic BinfoTxId Source # | |
| ToJSON BinfoTxId Source # | |
Defined in Haskoin.Store.Data | |
| FromJSON BinfoTxId Source # | |
| Serialize BinfoTxId Source # | |
| NFData BinfoTxId Source # | |
Defined in Haskoin.Store.Data | |
| 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-0.40.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 BinfoTxIndex))) | |
data BinfoMultiAddr Source #
Constructors
| BinfoMultiAddr | |
Instances
binfoMultiAddrToJSON :: Network -> BinfoMultiAddr -> Value Source #
data BinfoAddress Source #
Constructors
| BinfoAddress | |
Fields | |
| BinfoXPubKey | |
Fields | |
Instances
toBinfoAddrs :: HashMap Address Balance -> HashMap XPubKey [XPubBal] -> HashMap XPubKey Int -> [BinfoAddress] Source #
binfoAddressToJSON :: Network -> BinfoAddress -> Value Source #
binfoAddressToEncoding :: Network -> BinfoAddress -> Encoding Source #
binfoAddressParseJSON :: Network -> Value -> Parser BinfoAddress Source #
Instances
| Eq BinfoAddr Source # | |
| Show BinfoAddr Source # | |
| Generic BinfoAddr Source # | |
| Hashable BinfoAddr Source # | |
Defined in Haskoin.Store.Data | |
| Serialize BinfoAddr Source # | |
| NFData 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-0.40.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
Constructors
| BinfoTx | |
Fields
| |
Instances
relevantTxs :: HashSet Address -> Bool -> Transaction -> HashSet TxHash Source #
toBinfoTx :: Maybe (HashMap TxHash Transaction) -> HashMap Address (Maybe BinfoXPubPath) -> HashSet Address -> Bool -> Int64 -> Transaction -> BinfoTx Source #
toBinfoTxSimple :: Maybe (HashMap TxHash Transaction) -> Transaction -> BinfoTx Source #
data BinfoTxInput Source #
Constructors
| BinfoTxInput | |
Instances
binfoTxInputToJSON :: Network -> BinfoTxInput -> Value Source #
binfoTxInputToEncoding :: Network -> BinfoTxInput -> Encoding Source #
binfoTxInputParseJSON :: Network -> Value -> Parser BinfoTxInput Source #
data BinfoTxOutput Source #
Constructors
Instances
binfoTxOutputToJSON :: Network -> BinfoTxOutput -> Value Source #
binfoTxOutputParseJSON :: Network -> Value -> Parser BinfoTxOutput Source #
data BinfoSpender Source #
Constructors
| BinfoSpender | |
Fields | |
Instances
data BinfoXPubPath Source #
Constructors
| BinfoXPubPath | |
Fields | |
Instances
binfoXPubPathToJSON :: Network -> BinfoXPubPath -> Value Source #
binfoXPubPathParseJSON :: Network -> Value -> Parser BinfoXPubPath Source #
Constructors
| BinfoInfo | |
Fields | |
Instances
| Eq BinfoInfo Source # | |
| Show BinfoInfo Source # | |
| Generic BinfoInfo Source # | |
| ToJSON BinfoInfo Source # | |
Defined in Haskoin.Store.Data | |
| FromJSON BinfoInfo Source # | |
| NFData BinfoInfo Source # | |
Defined in Haskoin.Store.Data | |
| type Rep BinfoInfo Source # | |
Defined in Haskoin.Store.Data type Rep BinfoInfo = D1 ('MetaData "BinfoInfo" "Haskoin.Store.Data" "haskoin-store-data-0.40.2-inplace" 'False) (C1 ('MetaCons "BinfoInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "getBinfoConnected") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "getBinfoConversion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "getBinfoLocal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinfoSymbol) :*: (S1 ('MetaSel ('Just "getBinfoBTC") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinfoSymbol) :*: S1 ('MetaSel ('Just "getBinfoLatestBlock") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinfoBlockInfo))))) | |
data BinfoBlockInfo Source #
Constructors
| BinfoBlockInfo | |
Instances
data BinfoSymbol Source #
Constructors
| BinfoSymbol | |
Fields | |
Instances
data BinfoTicker Source #
Constructors
| BinfoTicker | |
Fields
| |