| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Haskoin.Store.Database.Types
Synopsis
- data AddrTxKey
- = AddrTxKey { }
- | AddrTxKeyA { }
- | AddrTxKeyB { }
- | AddrTxKeyS
- data AddrOutKey
- = AddrOutKey { }
- | AddrOutKeyA { }
- | AddrOutKeyB { }
- | AddrOutKeyS
- data BestKey = BestKey
- newtype BlockKey = BlockKey {}
- data BalKey
- newtype HeightKey = HeightKey {}
- data MemKey = MemKey
- data TxKey
- decodeTxKey :: Word64 -> ((Word32, Word16), Word8)
- data UnspentKey
- = UnspentKey { }
- | UnspentKeyS { }
- | UnspentKeyB
- data VersionKey = VersionKey
- data BalVal = BalVal {}
- valToBalance :: Address -> BalVal -> Balance
- balanceToVal :: Balance -> BalVal
- data UnspentVal = UnspentVal {}
- toUnspent :: Ctx -> AddrOutKey -> OutVal -> Unspent
- unspentToVal :: Unspent -> (OutPoint, UnspentVal)
- valToUnspent :: Ctx -> OutPoint -> UnspentVal -> Unspent
- data OutVal = OutVal {
- value :: !Word64
- script :: !ByteString
Documentation
Database key for an address transaction.
Constructors
| 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.
Constructors
| AddrOutKey | full key |
| AddrOutKeyA | short key for all spent or unspent outputs |
| AddrOutKeyB | |
| AddrOutKeyS | |
Instances
| Generic AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods readsPrec :: Int -> ReadS AddrOutKey # readList :: ReadS [AddrOutKey] # readPrec :: ReadPrec AddrOutKey # readListPrec :: ReadPrec [AddrOutKey] # | |||||
| Show AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods showsPrec :: Int -> AddrOutKey -> ShowS # show :: AddrOutKey -> String # showList :: [AddrOutKey] -> ShowS # | |||||
| Serialize AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Eq AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Ord AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods compare :: AddrOutKey -> AddrOutKey -> Ordering # (<) :: AddrOutKey -> AddrOutKey -> Bool # (<=) :: AddrOutKey -> AddrOutKey -> Bool # (>) :: AddrOutKey -> AddrOutKey -> Bool # (>=) :: AddrOutKey -> AddrOutKey -> Bool # max :: AddrOutKey -> AddrOutKey -> AddrOutKey # min :: AddrOutKey -> AddrOutKey -> AddrOutKey # | |||||
| Hashable AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Key AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| KeyValue AddrOutKey OutVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| type Rep AddrOutKey Source # | |||||
Defined in Haskoin.Store.Database.Types type Rep AddrOutKey = D1 ('MetaData "AddrOutKey" "Haskoin.Store.Database.Types" "haskoin-store-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'False) ((C1 ('MetaCons "AddrOutKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "address") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Address) :*: (S1 ('MetaSel ('Just "block") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockRef) :*: S1 ('MetaSel ('Just "outpoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OutPoint))) :+: C1 ('MetaCons "AddrOutKeyA" 'PrefixI 'True) (S1 ('MetaSel ('Just "address") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Address))) :+: (C1 ('MetaCons "AddrOutKeyB" 'PrefixI 'True) (S1 ('MetaSel ('Just "address") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Address) :*: S1 ('MetaSel ('Just "block") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockRef)) :+: C1 ('MetaCons "AddrOutKeyS" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
Key for best block in database.
Constructors
| BestKey |
Instances
| Generic BestKey Source # | |
Defined in Haskoin.Store.Database.Types | |
| Read BestKey Source # | |
| Show BestKey Source # | |
| Serialize BestKey Source # | |
| Eq BestKey Source # | |
| Ord BestKey Source # | |
Defined in Haskoin.Store.Database.Types | |
| Hashable BestKey Source # | |
Defined in Haskoin.Store.Database.Types | |
| 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
| Generic BlockKey Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read BlockKey Source # | |||||
| Show BlockKey Source # | |||||
| Serialize BlockKey Source # | |||||
| Eq BlockKey Source # | |||||
| Ord BlockKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Hashable BlockKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| 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
| Generic BalKey Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read BalKey Source # | |||||
| Show BalKey Source # | |||||
| Serialize BalKey Source # | |||||
| Eq BalKey Source # | |||||
| Ord BalKey Source # | |||||
| Hashable BalKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| 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-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'False) (C1 ('MetaCons "BalKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "address") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Address)) :+: C1 ('MetaCons "BalKeyS" 'PrefixI 'False) (U1 :: Type -> Type)) | |||||
Block height database key.
Constructors
| HeightKey | |
Fields | |
Instances
| Generic HeightKey Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read HeightKey Source # | |||||
| Show HeightKey Source # | |||||
| Serialize HeightKey Source # | |||||
| Eq HeightKey Source # | |||||
| Ord HeightKey Source # | |||||
| Hashable HeightKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| 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-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'True) (C1 ('MetaCons "HeightKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockHeight))) | |||||
Mempool transaction database key.
Constructors
| MemKey |
Transaction database key.
Instances
| Generic TxKey Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read TxKey Source # | |||||
| Show TxKey Source # | |||||
| Serialize TxKey Source # | |||||
| Eq TxKey Source # | |||||
| Ord TxKey Source # | |||||
| Hashable TxKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| 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 type Rep TxKey = D1 ('MetaData "TxKey" "Haskoin.Store.Database.Types" "haskoin-store-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'False) (C1 ('MetaCons "TxKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "txid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxHash)) :+: C1 ('MetaCons "TxKeyS" 'PrefixI 'True) (S1 ('MetaSel ('Just "short") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Word32, Word16)))) | |||||
data UnspentKey Source #
Unspent output database key.
Constructors
| UnspentKey | |
| UnspentKeyS | |
| UnspentKeyB | |
Instances
| Generic UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods readsPrec :: Int -> ReadS UnspentKey # readList :: ReadS [UnspentKey] # readPrec :: ReadPrec UnspentKey # readListPrec :: ReadPrec [UnspentKey] # | |||||
| Show UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods showsPrec :: Int -> UnspentKey -> ShowS # show :: UnspentKey -> String # showList :: [UnspentKey] -> ShowS # | |||||
| Serialize UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Eq UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Ord UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods compare :: UnspentKey -> UnspentKey -> Ordering # (<) :: UnspentKey -> UnspentKey -> Bool # (<=) :: UnspentKey -> UnspentKey -> Bool # (>) :: UnspentKey -> UnspentKey -> Bool # (>=) :: UnspentKey -> UnspentKey -> Bool # max :: UnspentKey -> UnspentKey -> UnspentKey # min :: UnspentKey -> UnspentKey -> UnspentKey # | |||||
| Hashable UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Key UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| KeyValue UnspentKey UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| type Rep UnspentKey Source # | |||||
Defined in Haskoin.Store.Database.Types type Rep UnspentKey = D1 ('MetaData "UnspentKey" "Haskoin.Store.Database.Types" "haskoin-store-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'False) (C1 ('MetaCons "UnspentKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "outpoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OutPoint)) :+: (C1 ('MetaCons "UnspentKeyS" 'PrefixI 'True) (S1 ('MetaSel ('Just "txid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxHash)) :+: C1 ('MetaCons "UnspentKeyB" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
data VersionKey Source #
Key for database version.
Constructors
| VersionKey |
Instances
| Generic VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods readsPrec :: Int -> ReadS VersionKey # readList :: ReadS [VersionKey] # readPrec :: ReadPrec VersionKey # readListPrec :: ReadPrec [VersionKey] # | |||||
| Show VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods showsPrec :: Int -> VersionKey -> ShowS # show :: VersionKey -> String # showList :: [VersionKey] -> ShowS # | |||||
| Serialize VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Eq VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Ord VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types Methods compare :: VersionKey -> VersionKey -> Ordering # (<) :: VersionKey -> VersionKey -> Bool # (<=) :: VersionKey -> VersionKey -> Bool # (>) :: VersionKey -> VersionKey -> Bool # (>=) :: VersionKey -> VersionKey -> Bool # max :: VersionKey -> VersionKey -> VersionKey # min :: VersionKey -> VersionKey -> VersionKey # | |||||
| Hashable VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Key VersionKey Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| KeyValue VersionKey Word32 Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| type Rep VersionKey Source # | |||||
Constructors
| BalVal | |
Instances
| Generic BalVal Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read BalVal Source # | |||||
| Show BalVal Source # | |||||
| Serialize BalVal Source # | |||||
| Default BalVal Source # | Default balance for an address. | ||||
Defined in Haskoin.Store.Database.Types | |||||
| NFData BalVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Eq BalVal Source # | |||||
| Ord BalVal Source # | |||||
| Hashable BalVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| KeyValue BalKey BalVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| type Rep BalVal Source # | |||||
Defined in Haskoin.Store.Database.Types type Rep BalVal = D1 ('MetaData "BalVal" "Haskoin.Store.Database.Types" "haskoin-store-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'False) (C1 ('MetaCons "BalVal" 'PrefixI 'True) ((S1 ('MetaSel ('Just "confirmed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "unconfirmed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "utxo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "txs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "received") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))))) | |||||
balanceToVal :: Balance -> BalVal Source #
data UnspentVal Source #
Constructors
| UnspentVal | |
Instances
| Generic UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types Methods readsPrec :: Int -> ReadS UnspentVal # readList :: ReadS [UnspentVal] # readPrec :: ReadPrec UnspentVal # readListPrec :: ReadPrec [UnspentVal] # | |||||
| Show UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types Methods showsPrec :: Int -> UnspentVal -> ShowS # show :: UnspentVal -> String # showList :: [UnspentVal] -> ShowS # | |||||
| Serialize UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| NFData UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types Methods rnf :: UnspentVal -> () # | |||||
| Eq UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| Ord UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types Methods compare :: UnspentVal -> UnspentVal -> Ordering # (<) :: UnspentVal -> UnspentVal -> Bool # (<=) :: UnspentVal -> UnspentVal -> Bool # (>) :: UnspentVal -> UnspentVal -> Bool # (>=) :: UnspentVal -> UnspentVal -> Bool # max :: UnspentVal -> UnspentVal -> UnspentVal # min :: UnspentVal -> UnspentVal -> UnspentVal # | |||||
| Hashable UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| KeyValue UnspentKey UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| type Rep UnspentVal Source # | |||||
Defined in Haskoin.Store.Database.Types type Rep UnspentVal = D1 ('MetaData "UnspentVal" "Haskoin.Store.Database.Types" "haskoin-store-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'False) (C1 ('MetaCons "UnspentVal" 'PrefixI 'True) (S1 ('MetaSel ('Just "block") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockRef) :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "script") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))) | |||||
unspentToVal :: Unspent -> (OutPoint, UnspentVal) Source #
valToUnspent :: Ctx -> OutPoint -> UnspentVal -> Unspent Source #
Constructors
| OutVal | |
Fields
| |
Instances
| Generic OutVal Source # | |||||
Defined in Haskoin.Store.Database.Types Associated Types
| |||||
| Read OutVal Source # | |||||
| Show OutVal Source # | |||||
| Serialize OutVal Source # | |||||
| Eq OutVal Source # | |||||
| Ord OutVal Source # | |||||
| Hashable OutVal Source # | |||||
Defined in Haskoin.Store.Database.Types | |||||
| 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-1.5.11-81XHlEM9jN8EmkKgt2WKgL" 'False) (C1 ('MetaCons "OutVal" 'PrefixI 'True) (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "script") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))) | |||||