Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data AddrTxKey
- = AddrTxKey {
- addrTxKeyA :: !Address
- addrTxKeyT :: !TxRef
- | AddrTxKeyA {
- addrTxKeyA :: !Address
- | AddrTxKeyB {
- addrTxKeyA :: !Address
- addrTxKeyB :: !BlockRef
- | AddrTxKeyS
- = AddrTxKey {
- data AddrOutKey
- = AddrOutKey {
- addrOutKeyA :: !Address
- addrOutKeyB :: !BlockRef
- addrOutKeyP :: !OutPoint
- | AddrOutKeyA {
- addrOutKeyA :: !Address
- | AddrOutKeyB {
- addrOutKeyA :: !Address
- addrOutKeyB :: !BlockRef
- | AddrOutKeyS
- = AddrOutKey {
- data BestKey = BestKey
- newtype BlockKey = BlockKey {}
- data BalKey
- = BalKey {
- balanceKey :: !Address
- | BalKeyS
- = BalKey {
- newtype HeightKey = HeightKey {}
- data MemKey = MemKey
- data SpenderKey
- = SpenderKey {
- outputPoint :: !OutPoint
- | SpenderKeyS {
- outputKeyS :: !TxHash
- = SpenderKey {
- data TxKey = TxKey {}
- data UnspentKey
- = UnspentKey {
- unspentKey :: !OutPoint
- | UnspentKeyS {
- unspentKeyS :: !TxHash
- | UnspentKeyB
- = UnspentKey {
- data VersionKey = VersionKey
- data BalVal = BalVal {}
- valToBalance :: Address -> BalVal -> Balance
- balanceToVal :: Balance -> BalVal
- data UnspentVal = UnspentVal {}
- toUnspent :: AddrOutKey -> OutVal -> Unspent
- unspentToVal :: Unspent -> (OutPoint, UnspentVal)
- valToUnspent :: OutPoint -> UnspentVal -> Unspent
- data OutVal = OutVal {
- outValAmount :: !Word64
- outValScript :: !ByteString
Documentation
Database key for an address transaction.
AddrTxKey | key for a transaction affecting an address |
| |
AddrTxKeyA | short key that matches all entries |
| |
AddrTxKeyB | |
| |
AddrTxKeyS |
Instances
data AddrOutKey Source #
Database key for an address output.
AddrOutKey | full key |
| |
AddrOutKeyA | short key for all spent or unspent outputs |
| |
AddrOutKeyB | |
| |
AddrOutKeyS |
Instances
Key for best block in database.
Instances
Eq BestKey Source # | |
Ord BestKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Read BestKey Source # | |
Show BestKey Source # | |
Generic BestKey Source # | |
Hashable BestKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Serialize BestKey Source # | |
Key BestKey Source # | |
Defined in Haskoin.Store.Database.Types | |
KeyValue BestKey BlockHash Source # | |
Defined in Haskoin.Store.Database.Types | |
type Rep BestKey Source # | |
Block entry database key.
Instances
Eq BlockKey Source # | |
Ord BlockKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Read BlockKey Source # | |
Show BlockKey Source # | |
Generic BlockKey Source # | |
Hashable BlockKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Serialize BlockKey Source # | |
Key BlockKey Source # | |
Defined in Haskoin.Store.Database.Types | |
KeyValue BlockKey BlockData Source # | |
Defined in Haskoin.Store.Database.Types | |
type Rep BlockKey Source # | |
Defined in Haskoin.Store.Database.Types |
Address balance database key.
Instances
Eq BalKey Source # | |
Ord BalKey Source # | |
Read BalKey Source # | |
Show BalKey Source # | |
Generic BalKey Source # | |
Hashable BalKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Serialize BalKey Source # | |
Key BalKey Source # | |
Defined in Haskoin.Store.Database.Types | |
KeyValue BalKey BalVal Source # | |
Defined in Haskoin.Store.Database.Types | |
type Rep BalKey Source # | |
Defined in Haskoin.Store.Database.Types type Rep BalKey = D1 ('MetaData "BalKey" "Haskoin.Store.Database.Types" "haskoin-store-0.40.2-inplace" 'False) (C1 ('MetaCons "BalKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "balanceKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Address)) :+: C1 ('MetaCons "BalKeyS" 'PrefixI 'False) (U1 :: Type -> Type)) |
Block height database key.
Instances
Eq HeightKey Source # | |
Ord HeightKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Read HeightKey Source # | |
Show HeightKey Source # | |
Generic HeightKey Source # | |
Hashable HeightKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Serialize HeightKey Source # | |
Key HeightKey Source # | |
Defined in Haskoin.Store.Database.Types | |
KeyValue HeightKey [BlockHash] Source # | |
Defined in Haskoin.Store.Database.Types | |
type Rep HeightKey Source # | |
Defined in Haskoin.Store.Database.Types type Rep HeightKey = D1 ('MetaData "HeightKey" "Haskoin.Store.Database.Types" "haskoin-store-0.40.2-inplace" 'True) (C1 ('MetaCons "HeightKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "heightKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockHeight))) |
Mempool transaction database key.
data SpenderKey Source #
Instances
Transaction database key.
Instances
Eq TxKey Source # | |
Ord TxKey Source # | |
Read TxKey Source # | |
Show TxKey Source # | |
Generic TxKey Source # | |
Hashable TxKey Source # | |
Defined in Haskoin.Store.Database.Types | |
Serialize TxKey Source # | |
Key TxKey Source # | |
Defined in Haskoin.Store.Database.Types | |
KeyValue TxKey TxData Source # | |
Defined in Haskoin.Store.Database.Types | |
type Rep TxKey Source # | |
Defined in Haskoin.Store.Database.Types |
data UnspentKey Source #
Unspent output database key.
Instances
data VersionKey Source #
Key for database version.
Instances
BalVal | |
|
Instances
balanceToVal :: Balance -> BalVal Source #
data UnspentVal Source #
Instances
unspentToVal :: Unspent -> (OutPoint, UnspentVal) Source #
valToUnspent :: OutPoint -> UnspentVal -> Unspent Source #
OutVal | |
|
Instances
Eq OutVal Source # | |
Ord OutVal Source # | |
Read OutVal Source # | |
Show OutVal Source # | |
Generic OutVal Source # | |
Hashable OutVal Source # | |
Defined in Haskoin.Store.Database.Types | |
Serialize OutVal Source # | |
KeyValue AddrOutKey OutVal Source # | |
Defined in Haskoin.Store.Database.Types | |
type Rep OutVal Source # | |
Defined in Haskoin.Store.Database.Types type Rep OutVal = D1 ('MetaData "OutVal" "Haskoin.Store.Database.Types" "haskoin-store-0.40.2-inplace" 'False) (C1 ('MetaCons "OutVal" 'PrefixI 'True) (S1 ('MetaSel ('Just "outValAmount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "outValScript") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))) |