{-# LANGUAGE DeriveAnyClass        #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Haskoin.Store.Database.Types
    ( AddrTxKey(..)
    , AddrOutKey(..)
    , BestKey(..)
    , BlockKey(..)
    , BalKey(..)
    , HeightKey(..)
    , MemKey(..)
    , SpenderKey(..)
    , TxKey(..)
    , UnspentKey(..)
    , VersionKey(..)
    , BalVal(..)
    , valToBalance
    , balanceToVal
    , UnspentVal(..)
    , toUnspent
    , unspentToVal
    , valToUnspent
    , OutVal(..)
    ) where

import           Control.DeepSeq        (NFData)
import           Control.Monad          (guard)
import           Data.Bits              (Bits, shiftL, shiftR, (.|.))
import           Data.ByteString        (ByteString)
import qualified Data.ByteString        as BS
import           Data.ByteString.Short  (ShortByteString)
import qualified Data.ByteString.Short  as BSS
import           Data.Default           (Default (..))
import           Data.Either            (fromRight)
import           Data.Hashable          (Hashable)
import           Data.Serialize         (Serialize (..), decode, encode,
                                         getBytes, getWord8, putWord8, runPut)
import           Data.Word              (Word16, Word32, Word64, Word8)
import           Database.RocksDB.Query (Key, KeyValue)
import           GHC.Generics           (Generic)
import           Haskoin                (Address, BlockHash, BlockHeight,
                                         OutPoint (..), TxHash, eitherToMaybe,
                                         scriptToAddressBS)
import           Haskoin.Store.Data     (Balance (..), BlockData, BlockRef,
                                         Spender, TxData, TxRef (..), UnixTime,
                                         Unspent (..))

-- | Database key for an address transaction.
data AddrTxKey
    = AddrTxKey { AddrTxKey -> Address
addrTxKeyA :: !Address
                , AddrTxKey -> TxRef
addrTxKeyT :: !TxRef
                }
      -- ^ key for a transaction affecting an address
    | AddrTxKeyA { addrTxKeyA :: !Address }
      -- ^ short key that matches all entries
    | AddrTxKeyB { addrTxKeyA :: !Address
                 , AddrTxKey -> BlockRef
addrTxKeyB :: !BlockRef
                 }
    | AddrTxKeyS
    deriving (Int -> AddrTxKey -> ShowS
[AddrTxKey] -> ShowS
AddrTxKey -> String
(Int -> AddrTxKey -> ShowS)
-> (AddrTxKey -> String)
-> ([AddrTxKey] -> ShowS)
-> Show AddrTxKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddrTxKey] -> ShowS
$cshowList :: [AddrTxKey] -> ShowS
show :: AddrTxKey -> String
$cshow :: AddrTxKey -> String
showsPrec :: Int -> AddrTxKey -> ShowS
$cshowsPrec :: Int -> AddrTxKey -> ShowS
Show, AddrTxKey -> AddrTxKey -> Bool
(AddrTxKey -> AddrTxKey -> Bool)
-> (AddrTxKey -> AddrTxKey -> Bool) -> Eq AddrTxKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddrTxKey -> AddrTxKey -> Bool
$c/= :: AddrTxKey -> AddrTxKey -> Bool
== :: AddrTxKey -> AddrTxKey -> Bool
$c== :: AddrTxKey -> AddrTxKey -> Bool
Eq, Eq AddrTxKey
Eq AddrTxKey =>
(AddrTxKey -> AddrTxKey -> Ordering)
-> (AddrTxKey -> AddrTxKey -> Bool)
-> (AddrTxKey -> AddrTxKey -> Bool)
-> (AddrTxKey -> AddrTxKey -> Bool)
-> (AddrTxKey -> AddrTxKey -> Bool)
-> (AddrTxKey -> AddrTxKey -> AddrTxKey)
-> (AddrTxKey -> AddrTxKey -> AddrTxKey)
-> Ord AddrTxKey
AddrTxKey -> AddrTxKey -> Bool
AddrTxKey -> AddrTxKey -> Ordering
AddrTxKey -> AddrTxKey -> AddrTxKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AddrTxKey -> AddrTxKey -> AddrTxKey
$cmin :: AddrTxKey -> AddrTxKey -> AddrTxKey
max :: AddrTxKey -> AddrTxKey -> AddrTxKey
$cmax :: AddrTxKey -> AddrTxKey -> AddrTxKey
>= :: AddrTxKey -> AddrTxKey -> Bool
$c>= :: AddrTxKey -> AddrTxKey -> Bool
> :: AddrTxKey -> AddrTxKey -> Bool
$c> :: AddrTxKey -> AddrTxKey -> Bool
<= :: AddrTxKey -> AddrTxKey -> Bool
$c<= :: AddrTxKey -> AddrTxKey -> Bool
< :: AddrTxKey -> AddrTxKey -> Bool
$c< :: AddrTxKey -> AddrTxKey -> Bool
compare :: AddrTxKey -> AddrTxKey -> Ordering
$ccompare :: AddrTxKey -> AddrTxKey -> Ordering
$cp1Ord :: Eq AddrTxKey
Ord, (forall x. AddrTxKey -> Rep AddrTxKey x)
-> (forall x. Rep AddrTxKey x -> AddrTxKey) -> Generic AddrTxKey
forall x. Rep AddrTxKey x -> AddrTxKey
forall x. AddrTxKey -> Rep AddrTxKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddrTxKey x -> AddrTxKey
$cfrom :: forall x. AddrTxKey -> Rep AddrTxKey x
Generic, Int -> AddrTxKey -> Int
AddrTxKey -> Int
(Int -> AddrTxKey -> Int)
-> (AddrTxKey -> Int) -> Hashable AddrTxKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: AddrTxKey -> Int
$chash :: AddrTxKey -> Int
hashWithSalt :: Int -> AddrTxKey -> Int
$chashWithSalt :: Int -> AddrTxKey -> Int
Hashable)

instance Serialize AddrTxKey
    -- 0x05 · Address · BlockRef · TxHash
                                          where
    put :: Putter AddrTxKey
put AddrTxKey { addrTxKeyA :: AddrTxKey -> Address
addrTxKeyA = Address
a
                  , addrTxKeyT :: AddrTxKey -> TxRef
addrTxKeyT = TxRef {txRefBlock :: TxRef -> BlockRef
txRefBlock = BlockRef
b, txRefHash :: TxRef -> TxHash
txRefHash = TxHash
t}
                  } = do
        Putter AddrTxKey
forall t. Serialize t => Putter t
put $WAddrTxKeyB :: Address -> BlockRef -> AddrTxKey
AddrTxKeyB {addrTxKeyA :: Address
addrTxKeyA = Address
a, addrTxKeyB :: BlockRef
addrTxKeyB = BlockRef
b}
        Putter TxHash
forall t. Serialize t => Putter t
put TxHash
t
    -- 0x05 · Address
    put AddrTxKeyA {addrTxKeyA :: AddrTxKey -> Address
addrTxKeyA = Address
a} = do
        Putter AddrTxKey
forall t. Serialize t => Putter t
put AddrTxKey
AddrTxKeyS
        Putter Address
forall t. Serialize t => Putter t
put Address
a
    -- 0x05 · Address · BlockRef
    put AddrTxKeyB {addrTxKeyA :: AddrTxKey -> Address
addrTxKeyA = Address
a, addrTxKeyB :: AddrTxKey -> BlockRef
addrTxKeyB = BlockRef
b} = do
        Putter AddrTxKey
forall t. Serialize t => Putter t
put $WAddrTxKeyA :: Address -> AddrTxKey
AddrTxKeyA {addrTxKeyA :: Address
addrTxKeyA = Address
a}
        Putter BlockRef
forall t. Serialize t => Putter t
put BlockRef
b
    -- 0x05
    put AddrTxKeyS = Putter Word8
putWord8 0x05
    get :: Get AddrTxKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x05) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        Address
a <- Get Address
forall t. Serialize t => Get t
get
        BlockRef
b <- Get BlockRef
forall t. Serialize t => Get t
get
        TxHash
t <- Get TxHash
forall t. Serialize t => Get t
get
        AddrTxKey -> Get AddrTxKey
forall (m :: * -> *) a. Monad m => a -> m a
return
            $WAddrTxKey :: Address -> TxRef -> AddrTxKey
AddrTxKey
                { addrTxKeyA :: Address
addrTxKeyA = Address
a
                , addrTxKeyT :: TxRef
addrTxKeyT = $WTxRef :: BlockRef -> TxHash -> TxRef
TxRef {txRefBlock :: BlockRef
txRefBlock = BlockRef
b, txRefHash :: TxHash
txRefHash = TxHash
t}
                }

instance Key AddrTxKey
instance KeyValue AddrTxKey ()

-- | Database key for an address output.
data AddrOutKey
    = AddrOutKey { AddrOutKey -> Address
addrOutKeyA :: !Address
                 , AddrOutKey -> BlockRef
addrOutKeyB :: !BlockRef
                 , AddrOutKey -> OutPoint
addrOutKeyP :: !OutPoint }
      -- ^ full key
    | AddrOutKeyA { addrOutKeyA :: !Address }
      -- ^ short key for all spent or unspent outputs
    | AddrOutKeyB { addrOutKeyA :: !Address
                  , addrOutKeyB :: !BlockRef
                  }
    | AddrOutKeyS
    deriving (Int -> AddrOutKey -> ShowS
[AddrOutKey] -> ShowS
AddrOutKey -> String
(Int -> AddrOutKey -> ShowS)
-> (AddrOutKey -> String)
-> ([AddrOutKey] -> ShowS)
-> Show AddrOutKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddrOutKey] -> ShowS
$cshowList :: [AddrOutKey] -> ShowS
show :: AddrOutKey -> String
$cshow :: AddrOutKey -> String
showsPrec :: Int -> AddrOutKey -> ShowS
$cshowsPrec :: Int -> AddrOutKey -> ShowS
Show, ReadPrec [AddrOutKey]
ReadPrec AddrOutKey
Int -> ReadS AddrOutKey
ReadS [AddrOutKey]
(Int -> ReadS AddrOutKey)
-> ReadS [AddrOutKey]
-> ReadPrec AddrOutKey
-> ReadPrec [AddrOutKey]
-> Read AddrOutKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddrOutKey]
$creadListPrec :: ReadPrec [AddrOutKey]
readPrec :: ReadPrec AddrOutKey
$creadPrec :: ReadPrec AddrOutKey
readList :: ReadS [AddrOutKey]
$creadList :: ReadS [AddrOutKey]
readsPrec :: Int -> ReadS AddrOutKey
$creadsPrec :: Int -> ReadS AddrOutKey
Read, AddrOutKey -> AddrOutKey -> Bool
(AddrOutKey -> AddrOutKey -> Bool)
-> (AddrOutKey -> AddrOutKey -> Bool) -> Eq AddrOutKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddrOutKey -> AddrOutKey -> Bool
$c/= :: AddrOutKey -> AddrOutKey -> Bool
== :: AddrOutKey -> AddrOutKey -> Bool
$c== :: AddrOutKey -> AddrOutKey -> Bool
Eq, Eq AddrOutKey
Eq AddrOutKey =>
(AddrOutKey -> AddrOutKey -> Ordering)
-> (AddrOutKey -> AddrOutKey -> Bool)
-> (AddrOutKey -> AddrOutKey -> Bool)
-> (AddrOutKey -> AddrOutKey -> Bool)
-> (AddrOutKey -> AddrOutKey -> Bool)
-> (AddrOutKey -> AddrOutKey -> AddrOutKey)
-> (AddrOutKey -> AddrOutKey -> AddrOutKey)
-> Ord AddrOutKey
AddrOutKey -> AddrOutKey -> Bool
AddrOutKey -> AddrOutKey -> Ordering
AddrOutKey -> AddrOutKey -> AddrOutKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AddrOutKey -> AddrOutKey -> AddrOutKey
$cmin :: AddrOutKey -> AddrOutKey -> AddrOutKey
max :: AddrOutKey -> AddrOutKey -> AddrOutKey
$cmax :: AddrOutKey -> AddrOutKey -> AddrOutKey
>= :: AddrOutKey -> AddrOutKey -> Bool
$c>= :: AddrOutKey -> AddrOutKey -> Bool
> :: AddrOutKey -> AddrOutKey -> Bool
$c> :: AddrOutKey -> AddrOutKey -> Bool
<= :: AddrOutKey -> AddrOutKey -> Bool
$c<= :: AddrOutKey -> AddrOutKey -> Bool
< :: AddrOutKey -> AddrOutKey -> Bool
$c< :: AddrOutKey -> AddrOutKey -> Bool
compare :: AddrOutKey -> AddrOutKey -> Ordering
$ccompare :: AddrOutKey -> AddrOutKey -> Ordering
$cp1Ord :: Eq AddrOutKey
Ord, (forall x. AddrOutKey -> Rep AddrOutKey x)
-> (forall x. Rep AddrOutKey x -> AddrOutKey) -> Generic AddrOutKey
forall x. Rep AddrOutKey x -> AddrOutKey
forall x. AddrOutKey -> Rep AddrOutKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddrOutKey x -> AddrOutKey
$cfrom :: forall x. AddrOutKey -> Rep AddrOutKey x
Generic, Int -> AddrOutKey -> Int
AddrOutKey -> Int
(Int -> AddrOutKey -> Int)
-> (AddrOutKey -> Int) -> Hashable AddrOutKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: AddrOutKey -> Int
$chash :: AddrOutKey -> Int
hashWithSalt :: Int -> AddrOutKey -> Int
$chashWithSalt :: Int -> AddrOutKey -> Int
Hashable)

instance Serialize AddrOutKey
    -- 0x06 · StoreAddr · BlockRef · OutPoint
                                              where
    put :: Putter AddrOutKey
put AddrOutKey {addrOutKeyA :: AddrOutKey -> Address
addrOutKeyA = Address
a, addrOutKeyB :: AddrOutKey -> BlockRef
addrOutKeyB = BlockRef
b, addrOutKeyP :: AddrOutKey -> OutPoint
addrOutKeyP = OutPoint
p} = do
        Putter AddrOutKey
forall t. Serialize t => Putter t
put $WAddrOutKeyB :: Address -> BlockRef -> AddrOutKey
AddrOutKeyB {addrOutKeyA :: Address
addrOutKeyA = Address
a, addrOutKeyB :: BlockRef
addrOutKeyB = BlockRef
b}
        Putter OutPoint
forall t. Serialize t => Putter t
put OutPoint
p
    -- 0x06 · StoreAddr · BlockRef
    put AddrOutKeyB {addrOutKeyA :: AddrOutKey -> Address
addrOutKeyA = Address
a, addrOutKeyB :: AddrOutKey -> BlockRef
addrOutKeyB = BlockRef
b} = do
        Putter AddrOutKey
forall t. Serialize t => Putter t
put $WAddrOutKeyA :: Address -> AddrOutKey
AddrOutKeyA {addrOutKeyA :: Address
addrOutKeyA = Address
a}
        Putter BlockRef
forall t. Serialize t => Putter t
put BlockRef
b
    -- 0x06 · StoreAddr
    put AddrOutKeyA {addrOutKeyA :: AddrOutKey -> Address
addrOutKeyA = Address
a} = do
        Putter AddrOutKey
forall t. Serialize t => Putter t
put AddrOutKey
AddrOutKeyS
        Putter Address
forall t. Serialize t => Putter t
put Address
a
    -- 0x06
    put AddrOutKeyS = Putter Word8
putWord8 0x06
    get :: Get AddrOutKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x06) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        Address -> BlockRef -> OutPoint -> AddrOutKey
AddrOutKey (Address -> BlockRef -> OutPoint -> AddrOutKey)
-> Get Address -> Get (BlockRef -> OutPoint -> AddrOutKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Address
forall t. Serialize t => Get t
get Get (BlockRef -> OutPoint -> AddrOutKey)
-> Get BlockRef -> Get (OutPoint -> AddrOutKey)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get BlockRef
forall t. Serialize t => Get t
get Get (OutPoint -> AddrOutKey) -> Get OutPoint -> Get AddrOutKey
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get OutPoint
forall t. Serialize t => Get t
get

instance Key AddrOutKey

data OutVal = OutVal
    { OutVal -> Word64
outValAmount :: !Word64
    , OutVal -> ByteString
outValScript :: !ByteString
    } deriving (Int -> OutVal -> ShowS
[OutVal] -> ShowS
OutVal -> String
(Int -> OutVal -> ShowS)
-> (OutVal -> String) -> ([OutVal] -> ShowS) -> Show OutVal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutVal] -> ShowS
$cshowList :: [OutVal] -> ShowS
show :: OutVal -> String
$cshow :: OutVal -> String
showsPrec :: Int -> OutVal -> ShowS
$cshowsPrec :: Int -> OutVal -> ShowS
Show, ReadPrec [OutVal]
ReadPrec OutVal
Int -> ReadS OutVal
ReadS [OutVal]
(Int -> ReadS OutVal)
-> ReadS [OutVal]
-> ReadPrec OutVal
-> ReadPrec [OutVal]
-> Read OutVal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OutVal]
$creadListPrec :: ReadPrec [OutVal]
readPrec :: ReadPrec OutVal
$creadPrec :: ReadPrec OutVal
readList :: ReadS [OutVal]
$creadList :: ReadS [OutVal]
readsPrec :: Int -> ReadS OutVal
$creadsPrec :: Int -> ReadS OutVal
Read, OutVal -> OutVal -> Bool
(OutVal -> OutVal -> Bool)
-> (OutVal -> OutVal -> Bool) -> Eq OutVal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutVal -> OutVal -> Bool
$c/= :: OutVal -> OutVal -> Bool
== :: OutVal -> OutVal -> Bool
$c== :: OutVal -> OutVal -> Bool
Eq, Eq OutVal
Eq OutVal =>
(OutVal -> OutVal -> Ordering)
-> (OutVal -> OutVal -> Bool)
-> (OutVal -> OutVal -> Bool)
-> (OutVal -> OutVal -> Bool)
-> (OutVal -> OutVal -> Bool)
-> (OutVal -> OutVal -> OutVal)
-> (OutVal -> OutVal -> OutVal)
-> Ord OutVal
OutVal -> OutVal -> Bool
OutVal -> OutVal -> Ordering
OutVal -> OutVal -> OutVal
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OutVal -> OutVal -> OutVal
$cmin :: OutVal -> OutVal -> OutVal
max :: OutVal -> OutVal -> OutVal
$cmax :: OutVal -> OutVal -> OutVal
>= :: OutVal -> OutVal -> Bool
$c>= :: OutVal -> OutVal -> Bool
> :: OutVal -> OutVal -> Bool
$c> :: OutVal -> OutVal -> Bool
<= :: OutVal -> OutVal -> Bool
$c<= :: OutVal -> OutVal -> Bool
< :: OutVal -> OutVal -> Bool
$c< :: OutVal -> OutVal -> Bool
compare :: OutVal -> OutVal -> Ordering
$ccompare :: OutVal -> OutVal -> Ordering
$cp1Ord :: Eq OutVal
Ord, (forall x. OutVal -> Rep OutVal x)
-> (forall x. Rep OutVal x -> OutVal) -> Generic OutVal
forall x. Rep OutVal x -> OutVal
forall x. OutVal -> Rep OutVal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OutVal x -> OutVal
$cfrom :: forall x. OutVal -> Rep OutVal x
Generic, Int -> OutVal -> Int
OutVal -> Int
(Int -> OutVal -> Int) -> (OutVal -> Int) -> Hashable OutVal
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: OutVal -> Int
$chash :: OutVal -> Int
hashWithSalt :: Int -> OutVal -> Int
$chashWithSalt :: Int -> OutVal -> Int
Hashable, Get OutVal
Putter OutVal
Putter OutVal -> Get OutVal -> Serialize OutVal
forall t. Putter t -> Get t -> Serialize t
get :: Get OutVal
$cget :: Get OutVal
put :: Putter OutVal
$cput :: Putter OutVal
Serialize)

instance KeyValue AddrOutKey OutVal

-- | Transaction database key.
data TxKey = TxKey { TxKey -> TxHash
txKey :: TxHash }
    deriving (Int -> TxKey -> ShowS
[TxKey] -> ShowS
TxKey -> String
(Int -> TxKey -> ShowS)
-> (TxKey -> String) -> ([TxKey] -> ShowS) -> Show TxKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxKey] -> ShowS
$cshowList :: [TxKey] -> ShowS
show :: TxKey -> String
$cshow :: TxKey -> String
showsPrec :: Int -> TxKey -> ShowS
$cshowsPrec :: Int -> TxKey -> ShowS
Show, ReadPrec [TxKey]
ReadPrec TxKey
Int -> ReadS TxKey
ReadS [TxKey]
(Int -> ReadS TxKey)
-> ReadS [TxKey]
-> ReadPrec TxKey
-> ReadPrec [TxKey]
-> Read TxKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TxKey]
$creadListPrec :: ReadPrec [TxKey]
readPrec :: ReadPrec TxKey
$creadPrec :: ReadPrec TxKey
readList :: ReadS [TxKey]
$creadList :: ReadS [TxKey]
readsPrec :: Int -> ReadS TxKey
$creadsPrec :: Int -> ReadS TxKey
Read, TxKey -> TxKey -> Bool
(TxKey -> TxKey -> Bool) -> (TxKey -> TxKey -> Bool) -> Eq TxKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxKey -> TxKey -> Bool
$c/= :: TxKey -> TxKey -> Bool
== :: TxKey -> TxKey -> Bool
$c== :: TxKey -> TxKey -> Bool
Eq, Eq TxKey
Eq TxKey =>
(TxKey -> TxKey -> Ordering)
-> (TxKey -> TxKey -> Bool)
-> (TxKey -> TxKey -> Bool)
-> (TxKey -> TxKey -> Bool)
-> (TxKey -> TxKey -> Bool)
-> (TxKey -> TxKey -> TxKey)
-> (TxKey -> TxKey -> TxKey)
-> Ord TxKey
TxKey -> TxKey -> Bool
TxKey -> TxKey -> Ordering
TxKey -> TxKey -> TxKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TxKey -> TxKey -> TxKey
$cmin :: TxKey -> TxKey -> TxKey
max :: TxKey -> TxKey -> TxKey
$cmax :: TxKey -> TxKey -> TxKey
>= :: TxKey -> TxKey -> Bool
$c>= :: TxKey -> TxKey -> Bool
> :: TxKey -> TxKey -> Bool
$c> :: TxKey -> TxKey -> Bool
<= :: TxKey -> TxKey -> Bool
$c<= :: TxKey -> TxKey -> Bool
< :: TxKey -> TxKey -> Bool
$c< :: TxKey -> TxKey -> Bool
compare :: TxKey -> TxKey -> Ordering
$ccompare :: TxKey -> TxKey -> Ordering
$cp1Ord :: Eq TxKey
Ord, (forall x. TxKey -> Rep TxKey x)
-> (forall x. Rep TxKey x -> TxKey) -> Generic TxKey
forall x. Rep TxKey x -> TxKey
forall x. TxKey -> Rep TxKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxKey x -> TxKey
$cfrom :: forall x. TxKey -> Rep TxKey x
Generic, Int -> TxKey -> Int
TxKey -> Int
(Int -> TxKey -> Int) -> (TxKey -> Int) -> Hashable TxKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TxKey -> Int
$chash :: TxKey -> Int
hashWithSalt :: Int -> TxKey -> Int
$chashWithSalt :: Int -> TxKey -> Int
Hashable)

instance Serialize TxKey where
    -- 0x02 · TxHash
    put :: Putter TxKey
put (TxKey h :: TxHash
h) = do
        Putter Word8
putWord8 0x02
        Putter TxHash
forall t. Serialize t => Putter t
put TxHash
h
    get :: Get TxKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x02) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        TxHash -> TxKey
TxKey (TxHash -> TxKey) -> Get TxHash -> Get TxKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get TxHash
forall t. Serialize t => Get t
get

instance Key TxKey
instance KeyValue TxKey TxData

data SpenderKey
    = SpenderKey { SpenderKey -> OutPoint
outputPoint :: !OutPoint }
    | SpenderKeyS { SpenderKey -> TxHash
outputKeyS :: !TxHash }
    deriving (Int -> SpenderKey -> ShowS
[SpenderKey] -> ShowS
SpenderKey -> String
(Int -> SpenderKey -> ShowS)
-> (SpenderKey -> String)
-> ([SpenderKey] -> ShowS)
-> Show SpenderKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpenderKey] -> ShowS
$cshowList :: [SpenderKey] -> ShowS
show :: SpenderKey -> String
$cshow :: SpenderKey -> String
showsPrec :: Int -> SpenderKey -> ShowS
$cshowsPrec :: Int -> SpenderKey -> ShowS
Show, ReadPrec [SpenderKey]
ReadPrec SpenderKey
Int -> ReadS SpenderKey
ReadS [SpenderKey]
(Int -> ReadS SpenderKey)
-> ReadS [SpenderKey]
-> ReadPrec SpenderKey
-> ReadPrec [SpenderKey]
-> Read SpenderKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SpenderKey]
$creadListPrec :: ReadPrec [SpenderKey]
readPrec :: ReadPrec SpenderKey
$creadPrec :: ReadPrec SpenderKey
readList :: ReadS [SpenderKey]
$creadList :: ReadS [SpenderKey]
readsPrec :: Int -> ReadS SpenderKey
$creadsPrec :: Int -> ReadS SpenderKey
Read, SpenderKey -> SpenderKey -> Bool
(SpenderKey -> SpenderKey -> Bool)
-> (SpenderKey -> SpenderKey -> Bool) -> Eq SpenderKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpenderKey -> SpenderKey -> Bool
$c/= :: SpenderKey -> SpenderKey -> Bool
== :: SpenderKey -> SpenderKey -> Bool
$c== :: SpenderKey -> SpenderKey -> Bool
Eq, Eq SpenderKey
Eq SpenderKey =>
(SpenderKey -> SpenderKey -> Ordering)
-> (SpenderKey -> SpenderKey -> Bool)
-> (SpenderKey -> SpenderKey -> Bool)
-> (SpenderKey -> SpenderKey -> Bool)
-> (SpenderKey -> SpenderKey -> Bool)
-> (SpenderKey -> SpenderKey -> SpenderKey)
-> (SpenderKey -> SpenderKey -> SpenderKey)
-> Ord SpenderKey
SpenderKey -> SpenderKey -> Bool
SpenderKey -> SpenderKey -> Ordering
SpenderKey -> SpenderKey -> SpenderKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SpenderKey -> SpenderKey -> SpenderKey
$cmin :: SpenderKey -> SpenderKey -> SpenderKey
max :: SpenderKey -> SpenderKey -> SpenderKey
$cmax :: SpenderKey -> SpenderKey -> SpenderKey
>= :: SpenderKey -> SpenderKey -> Bool
$c>= :: SpenderKey -> SpenderKey -> Bool
> :: SpenderKey -> SpenderKey -> Bool
$c> :: SpenderKey -> SpenderKey -> Bool
<= :: SpenderKey -> SpenderKey -> Bool
$c<= :: SpenderKey -> SpenderKey -> Bool
< :: SpenderKey -> SpenderKey -> Bool
$c< :: SpenderKey -> SpenderKey -> Bool
compare :: SpenderKey -> SpenderKey -> Ordering
$ccompare :: SpenderKey -> SpenderKey -> Ordering
$cp1Ord :: Eq SpenderKey
Ord, (forall x. SpenderKey -> Rep SpenderKey x)
-> (forall x. Rep SpenderKey x -> SpenderKey) -> Generic SpenderKey
forall x. Rep SpenderKey x -> SpenderKey
forall x. SpenderKey -> Rep SpenderKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpenderKey x -> SpenderKey
$cfrom :: forall x. SpenderKey -> Rep SpenderKey x
Generic, Int -> SpenderKey -> Int
SpenderKey -> Int
(Int -> SpenderKey -> Int)
-> (SpenderKey -> Int) -> Hashable SpenderKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: SpenderKey -> Int
$chash :: SpenderKey -> Int
hashWithSalt :: Int -> SpenderKey -> Int
$chashWithSalt :: Int -> SpenderKey -> Int
Hashable)

instance Serialize SpenderKey where
    -- 0x10 · TxHash · Index
    put :: Putter SpenderKey
put (SpenderKey OutPoint {outPointHash :: OutPoint -> TxHash
outPointHash = TxHash
h, outPointIndex :: OutPoint -> Word32
outPointIndex = Word32
i}) = do
        Putter SpenderKey
forall t. Serialize t => Putter t
put (TxHash -> SpenderKey
SpenderKeyS TxHash
h)
        Putter Word32
forall t. Serialize t => Putter t
put Word32
i
    -- 0x10 · TxHash
    put (SpenderKeyS h :: TxHash
h) = do
        Putter Word8
putWord8 0x10
        Putter TxHash
forall t. Serialize t => Putter t
put TxHash
h
    get :: Get SpenderKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x10) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        OutPoint
op <- TxHash -> Word32 -> OutPoint
OutPoint (TxHash -> Word32 -> OutPoint)
-> Get TxHash -> Get (Word32 -> OutPoint)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get TxHash
forall t. Serialize t => Get t
get Get (Word32 -> OutPoint) -> Get Word32 -> Get OutPoint
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
forall t. Serialize t => Get t
get
        SpenderKey -> Get SpenderKey
forall (m :: * -> *) a. Monad m => a -> m a
return (SpenderKey -> Get SpenderKey) -> SpenderKey -> Get SpenderKey
forall a b. (a -> b) -> a -> b
$ OutPoint -> SpenderKey
SpenderKey OutPoint
op

instance Key SpenderKey
instance KeyValue SpenderKey Spender

-- | Unspent output database key.
data UnspentKey
    = UnspentKey { UnspentKey -> OutPoint
unspentKey :: !OutPoint }
    | UnspentKeyS { UnspentKey -> TxHash
unspentKeyS :: !TxHash }
    | UnspentKeyB
    deriving (Int -> UnspentKey -> ShowS
[UnspentKey] -> ShowS
UnspentKey -> String
(Int -> UnspentKey -> ShowS)
-> (UnspentKey -> String)
-> ([UnspentKey] -> ShowS)
-> Show UnspentKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnspentKey] -> ShowS
$cshowList :: [UnspentKey] -> ShowS
show :: UnspentKey -> String
$cshow :: UnspentKey -> String
showsPrec :: Int -> UnspentKey -> ShowS
$cshowsPrec :: Int -> UnspentKey -> ShowS
Show, ReadPrec [UnspentKey]
ReadPrec UnspentKey
Int -> ReadS UnspentKey
ReadS [UnspentKey]
(Int -> ReadS UnspentKey)
-> ReadS [UnspentKey]
-> ReadPrec UnspentKey
-> ReadPrec [UnspentKey]
-> Read UnspentKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnspentKey]
$creadListPrec :: ReadPrec [UnspentKey]
readPrec :: ReadPrec UnspentKey
$creadPrec :: ReadPrec UnspentKey
readList :: ReadS [UnspentKey]
$creadList :: ReadS [UnspentKey]
readsPrec :: Int -> ReadS UnspentKey
$creadsPrec :: Int -> ReadS UnspentKey
Read, UnspentKey -> UnspentKey -> Bool
(UnspentKey -> UnspentKey -> Bool)
-> (UnspentKey -> UnspentKey -> Bool) -> Eq UnspentKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnspentKey -> UnspentKey -> Bool
$c/= :: UnspentKey -> UnspentKey -> Bool
== :: UnspentKey -> UnspentKey -> Bool
$c== :: UnspentKey -> UnspentKey -> Bool
Eq, Eq UnspentKey
Eq UnspentKey =>
(UnspentKey -> UnspentKey -> Ordering)
-> (UnspentKey -> UnspentKey -> Bool)
-> (UnspentKey -> UnspentKey -> Bool)
-> (UnspentKey -> UnspentKey -> Bool)
-> (UnspentKey -> UnspentKey -> Bool)
-> (UnspentKey -> UnspentKey -> UnspentKey)
-> (UnspentKey -> UnspentKey -> UnspentKey)
-> Ord UnspentKey
UnspentKey -> UnspentKey -> Bool
UnspentKey -> UnspentKey -> Ordering
UnspentKey -> UnspentKey -> UnspentKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnspentKey -> UnspentKey -> UnspentKey
$cmin :: UnspentKey -> UnspentKey -> UnspentKey
max :: UnspentKey -> UnspentKey -> UnspentKey
$cmax :: UnspentKey -> UnspentKey -> UnspentKey
>= :: UnspentKey -> UnspentKey -> Bool
$c>= :: UnspentKey -> UnspentKey -> Bool
> :: UnspentKey -> UnspentKey -> Bool
$c> :: UnspentKey -> UnspentKey -> Bool
<= :: UnspentKey -> UnspentKey -> Bool
$c<= :: UnspentKey -> UnspentKey -> Bool
< :: UnspentKey -> UnspentKey -> Bool
$c< :: UnspentKey -> UnspentKey -> Bool
compare :: UnspentKey -> UnspentKey -> Ordering
$ccompare :: UnspentKey -> UnspentKey -> Ordering
$cp1Ord :: Eq UnspentKey
Ord, (forall x. UnspentKey -> Rep UnspentKey x)
-> (forall x. Rep UnspentKey x -> UnspentKey) -> Generic UnspentKey
forall x. Rep UnspentKey x -> UnspentKey
forall x. UnspentKey -> Rep UnspentKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnspentKey x -> UnspentKey
$cfrom :: forall x. UnspentKey -> Rep UnspentKey x
Generic, Int -> UnspentKey -> Int
UnspentKey -> Int
(Int -> UnspentKey -> Int)
-> (UnspentKey -> Int) -> Hashable UnspentKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: UnspentKey -> Int
$chash :: UnspentKey -> Int
hashWithSalt :: Int -> UnspentKey -> Int
$chashWithSalt :: Int -> UnspentKey -> Int
Hashable)

instance Serialize UnspentKey where
    -- 0x09 · TxHash · Index
    put :: Putter UnspentKey
put UnspentKey {unspentKey :: UnspentKey -> OutPoint
unspentKey = OutPoint {outPointHash :: OutPoint -> TxHash
outPointHash = TxHash
h, outPointIndex :: OutPoint -> Word32
outPointIndex = Word32
i}} = do
        Putter Word8
putWord8 0x09
        Putter TxHash
forall t. Serialize t => Putter t
put TxHash
h
        Putter Word32
forall t. Serialize t => Putter t
put Word32
i
    -- 0x09 · TxHash
    put UnspentKeyS {unspentKeyS :: UnspentKey -> TxHash
unspentKeyS = TxHash
t} = do
        Putter Word8
putWord8 0x09
        Putter TxHash
forall t. Serialize t => Putter t
put TxHash
t
    -- 0x09
    put UnspentKeyB = Putter Word8
putWord8 0x09
    get :: Get UnspentKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x09) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        TxHash
h <- Get TxHash
forall t. Serialize t => Get t
get
        Word32
i <- Get Word32
forall t. Serialize t => Get t
get
        UnspentKey -> Get UnspentKey
forall (m :: * -> *) a. Monad m => a -> m a
return (UnspentKey -> Get UnspentKey) -> UnspentKey -> Get UnspentKey
forall a b. (a -> b) -> a -> b
$ OutPoint -> UnspentKey
UnspentKey $WOutPoint :: TxHash -> Word32 -> OutPoint
OutPoint {outPointHash :: TxHash
outPointHash = TxHash
h, outPointIndex :: Word32
outPointIndex = Word32
i}

instance Key UnspentKey
instance KeyValue UnspentKey UnspentVal

toUnspent :: AddrOutKey -> OutVal -> Unspent
toUnspent :: AddrOutKey -> OutVal -> Unspent
toUnspent b :: AddrOutKey
b v :: OutVal
v =
    $WUnspent :: BlockRef
-> OutPoint
-> Word64
-> ShortByteString
-> Maybe Address
-> Unspent
Unspent
        { unspentBlock :: BlockRef
unspentBlock = AddrOutKey -> BlockRef
addrOutKeyB AddrOutKey
b
        , unspentAmount :: Word64
unspentAmount = OutVal -> Word64
outValAmount OutVal
v
        , unspentScript :: ShortByteString
unspentScript = ByteString -> ShortByteString
BSS.toShort (OutVal -> ByteString
outValScript OutVal
v)
        , unspentPoint :: OutPoint
unspentPoint = AddrOutKey -> OutPoint
addrOutKeyP AddrOutKey
b
        , unspentAddress :: Maybe Address
unspentAddress = Either String Address -> Maybe Address
forall a b. Either a b -> Maybe b
eitherToMaybe (ByteString -> Either String Address
scriptToAddressBS (OutVal -> ByteString
outValScript OutVal
v))
        }

-- | Mempool transaction database key.
data MemKey =
    MemKey
    deriving (Int -> MemKey -> ShowS
[MemKey] -> ShowS
MemKey -> String
(Int -> MemKey -> ShowS)
-> (MemKey -> String) -> ([MemKey] -> ShowS) -> Show MemKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MemKey] -> ShowS
$cshowList :: [MemKey] -> ShowS
show :: MemKey -> String
$cshow :: MemKey -> String
showsPrec :: Int -> MemKey -> ShowS
$cshowsPrec :: Int -> MemKey -> ShowS
Show, ReadPrec [MemKey]
ReadPrec MemKey
Int -> ReadS MemKey
ReadS [MemKey]
(Int -> ReadS MemKey)
-> ReadS [MemKey]
-> ReadPrec MemKey
-> ReadPrec [MemKey]
-> Read MemKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MemKey]
$creadListPrec :: ReadPrec [MemKey]
readPrec :: ReadPrec MemKey
$creadPrec :: ReadPrec MemKey
readList :: ReadS [MemKey]
$creadList :: ReadS [MemKey]
readsPrec :: Int -> ReadS MemKey
$creadsPrec :: Int -> ReadS MemKey
Read)

instance Serialize MemKey where
    -- 0x07
    put :: Putter MemKey
put MemKey = Putter Word8
putWord8 0x07
    get :: Get MemKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x07) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        MemKey -> Get MemKey
forall (m :: * -> *) a. Monad m => a -> m a
return MemKey
MemKey

instance Key MemKey
instance KeyValue MemKey [(UnixTime, TxHash)]

-- | Block entry database key.
newtype BlockKey = BlockKey
    { BlockKey -> BlockHash
blockKey :: BlockHash
    } deriving (Int -> BlockKey -> ShowS
[BlockKey] -> ShowS
BlockKey -> String
(Int -> BlockKey -> ShowS)
-> (BlockKey -> String) -> ([BlockKey] -> ShowS) -> Show BlockKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockKey] -> ShowS
$cshowList :: [BlockKey] -> ShowS
show :: BlockKey -> String
$cshow :: BlockKey -> String
showsPrec :: Int -> BlockKey -> ShowS
$cshowsPrec :: Int -> BlockKey -> ShowS
Show, ReadPrec [BlockKey]
ReadPrec BlockKey
Int -> ReadS BlockKey
ReadS [BlockKey]
(Int -> ReadS BlockKey)
-> ReadS [BlockKey]
-> ReadPrec BlockKey
-> ReadPrec [BlockKey]
-> Read BlockKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BlockKey]
$creadListPrec :: ReadPrec [BlockKey]
readPrec :: ReadPrec BlockKey
$creadPrec :: ReadPrec BlockKey
readList :: ReadS [BlockKey]
$creadList :: ReadS [BlockKey]
readsPrec :: Int -> ReadS BlockKey
$creadsPrec :: Int -> ReadS BlockKey
Read, BlockKey -> BlockKey -> Bool
(BlockKey -> BlockKey -> Bool)
-> (BlockKey -> BlockKey -> Bool) -> Eq BlockKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockKey -> BlockKey -> Bool
$c/= :: BlockKey -> BlockKey -> Bool
== :: BlockKey -> BlockKey -> Bool
$c== :: BlockKey -> BlockKey -> Bool
Eq, Eq BlockKey
Eq BlockKey =>
(BlockKey -> BlockKey -> Ordering)
-> (BlockKey -> BlockKey -> Bool)
-> (BlockKey -> BlockKey -> Bool)
-> (BlockKey -> BlockKey -> Bool)
-> (BlockKey -> BlockKey -> Bool)
-> (BlockKey -> BlockKey -> BlockKey)
-> (BlockKey -> BlockKey -> BlockKey)
-> Ord BlockKey
BlockKey -> BlockKey -> Bool
BlockKey -> BlockKey -> Ordering
BlockKey -> BlockKey -> BlockKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BlockKey -> BlockKey -> BlockKey
$cmin :: BlockKey -> BlockKey -> BlockKey
max :: BlockKey -> BlockKey -> BlockKey
$cmax :: BlockKey -> BlockKey -> BlockKey
>= :: BlockKey -> BlockKey -> Bool
$c>= :: BlockKey -> BlockKey -> Bool
> :: BlockKey -> BlockKey -> Bool
$c> :: BlockKey -> BlockKey -> Bool
<= :: BlockKey -> BlockKey -> Bool
$c<= :: BlockKey -> BlockKey -> Bool
< :: BlockKey -> BlockKey -> Bool
$c< :: BlockKey -> BlockKey -> Bool
compare :: BlockKey -> BlockKey -> Ordering
$ccompare :: BlockKey -> BlockKey -> Ordering
$cp1Ord :: Eq BlockKey
Ord, (forall x. BlockKey -> Rep BlockKey x)
-> (forall x. Rep BlockKey x -> BlockKey) -> Generic BlockKey
forall x. Rep BlockKey x -> BlockKey
forall x. BlockKey -> Rep BlockKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockKey x -> BlockKey
$cfrom :: forall x. BlockKey -> Rep BlockKey x
Generic, Int -> BlockKey -> Int
BlockKey -> Int
(Int -> BlockKey -> Int) -> (BlockKey -> Int) -> Hashable BlockKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: BlockKey -> Int
$chash :: BlockKey -> Int
hashWithSalt :: Int -> BlockKey -> Int
$chashWithSalt :: Int -> BlockKey -> Int
Hashable)

instance Serialize BlockKey where
    -- 0x01 · BlockHash
    put :: Putter BlockKey
put (BlockKey h :: BlockHash
h) = do
        Putter Word8
putWord8 0x01
        Putter BlockHash
forall t. Serialize t => Putter t
put BlockHash
h
    get :: Get BlockKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x01) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        BlockHash -> BlockKey
BlockKey (BlockHash -> BlockKey) -> Get BlockHash -> Get BlockKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get BlockHash
forall t. Serialize t => Get t
get

instance Key BlockKey
instance KeyValue BlockKey BlockData

-- | Block height database key.
newtype HeightKey = HeightKey
    { HeightKey -> Word32
heightKey :: BlockHeight
    } deriving (Int -> HeightKey -> ShowS
[HeightKey] -> ShowS
HeightKey -> String
(Int -> HeightKey -> ShowS)
-> (HeightKey -> String)
-> ([HeightKey] -> ShowS)
-> Show HeightKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HeightKey] -> ShowS
$cshowList :: [HeightKey] -> ShowS
show :: HeightKey -> String
$cshow :: HeightKey -> String
showsPrec :: Int -> HeightKey -> ShowS
$cshowsPrec :: Int -> HeightKey -> ShowS
Show, ReadPrec [HeightKey]
ReadPrec HeightKey
Int -> ReadS HeightKey
ReadS [HeightKey]
(Int -> ReadS HeightKey)
-> ReadS [HeightKey]
-> ReadPrec HeightKey
-> ReadPrec [HeightKey]
-> Read HeightKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HeightKey]
$creadListPrec :: ReadPrec [HeightKey]
readPrec :: ReadPrec HeightKey
$creadPrec :: ReadPrec HeightKey
readList :: ReadS [HeightKey]
$creadList :: ReadS [HeightKey]
readsPrec :: Int -> ReadS HeightKey
$creadsPrec :: Int -> ReadS HeightKey
Read, HeightKey -> HeightKey -> Bool
(HeightKey -> HeightKey -> Bool)
-> (HeightKey -> HeightKey -> Bool) -> Eq HeightKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HeightKey -> HeightKey -> Bool
$c/= :: HeightKey -> HeightKey -> Bool
== :: HeightKey -> HeightKey -> Bool
$c== :: HeightKey -> HeightKey -> Bool
Eq, Eq HeightKey
Eq HeightKey =>
(HeightKey -> HeightKey -> Ordering)
-> (HeightKey -> HeightKey -> Bool)
-> (HeightKey -> HeightKey -> Bool)
-> (HeightKey -> HeightKey -> Bool)
-> (HeightKey -> HeightKey -> Bool)
-> (HeightKey -> HeightKey -> HeightKey)
-> (HeightKey -> HeightKey -> HeightKey)
-> Ord HeightKey
HeightKey -> HeightKey -> Bool
HeightKey -> HeightKey -> Ordering
HeightKey -> HeightKey -> HeightKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HeightKey -> HeightKey -> HeightKey
$cmin :: HeightKey -> HeightKey -> HeightKey
max :: HeightKey -> HeightKey -> HeightKey
$cmax :: HeightKey -> HeightKey -> HeightKey
>= :: HeightKey -> HeightKey -> Bool
$c>= :: HeightKey -> HeightKey -> Bool
> :: HeightKey -> HeightKey -> Bool
$c> :: HeightKey -> HeightKey -> Bool
<= :: HeightKey -> HeightKey -> Bool
$c<= :: HeightKey -> HeightKey -> Bool
< :: HeightKey -> HeightKey -> Bool
$c< :: HeightKey -> HeightKey -> Bool
compare :: HeightKey -> HeightKey -> Ordering
$ccompare :: HeightKey -> HeightKey -> Ordering
$cp1Ord :: Eq HeightKey
Ord, (forall x. HeightKey -> Rep HeightKey x)
-> (forall x. Rep HeightKey x -> HeightKey) -> Generic HeightKey
forall x. Rep HeightKey x -> HeightKey
forall x. HeightKey -> Rep HeightKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HeightKey x -> HeightKey
$cfrom :: forall x. HeightKey -> Rep HeightKey x
Generic, Int -> HeightKey -> Int
HeightKey -> Int
(Int -> HeightKey -> Int)
-> (HeightKey -> Int) -> Hashable HeightKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: HeightKey -> Int
$chash :: HeightKey -> Int
hashWithSalt :: Int -> HeightKey -> Int
$chashWithSalt :: Int -> HeightKey -> Int
Hashable)

instance Serialize HeightKey where
    -- 0x03 · BlockHeight
    put :: Putter HeightKey
put (HeightKey height :: Word32
height) = do
        Putter Word8
putWord8 0x03
        Putter Word32
forall t. Serialize t => Putter t
put Word32
height
    get :: Get HeightKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x03) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        Word32 -> HeightKey
HeightKey (Word32 -> HeightKey) -> Get Word32 -> Get HeightKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
forall t. Serialize t => Get t
get

instance Key HeightKey
instance KeyValue HeightKey [BlockHash]

-- | Address balance database key.
data BalKey
    = BalKey
          { BalKey -> Address
balanceKey :: !Address
          }
    | BalKeyS
    deriving (Int -> BalKey -> ShowS
[BalKey] -> ShowS
BalKey -> String
(Int -> BalKey -> ShowS)
-> (BalKey -> String) -> ([BalKey] -> ShowS) -> Show BalKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BalKey] -> ShowS
$cshowList :: [BalKey] -> ShowS
show :: BalKey -> String
$cshow :: BalKey -> String
showsPrec :: Int -> BalKey -> ShowS
$cshowsPrec :: Int -> BalKey -> ShowS
Show, ReadPrec [BalKey]
ReadPrec BalKey
Int -> ReadS BalKey
ReadS [BalKey]
(Int -> ReadS BalKey)
-> ReadS [BalKey]
-> ReadPrec BalKey
-> ReadPrec [BalKey]
-> Read BalKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BalKey]
$creadListPrec :: ReadPrec [BalKey]
readPrec :: ReadPrec BalKey
$creadPrec :: ReadPrec BalKey
readList :: ReadS [BalKey]
$creadList :: ReadS [BalKey]
readsPrec :: Int -> ReadS BalKey
$creadsPrec :: Int -> ReadS BalKey
Read, BalKey -> BalKey -> Bool
(BalKey -> BalKey -> Bool)
-> (BalKey -> BalKey -> Bool) -> Eq BalKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BalKey -> BalKey -> Bool
$c/= :: BalKey -> BalKey -> Bool
== :: BalKey -> BalKey -> Bool
$c== :: BalKey -> BalKey -> Bool
Eq, Eq BalKey
Eq BalKey =>
(BalKey -> BalKey -> Ordering)
-> (BalKey -> BalKey -> Bool)
-> (BalKey -> BalKey -> Bool)
-> (BalKey -> BalKey -> Bool)
-> (BalKey -> BalKey -> Bool)
-> (BalKey -> BalKey -> BalKey)
-> (BalKey -> BalKey -> BalKey)
-> Ord BalKey
BalKey -> BalKey -> Bool
BalKey -> BalKey -> Ordering
BalKey -> BalKey -> BalKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BalKey -> BalKey -> BalKey
$cmin :: BalKey -> BalKey -> BalKey
max :: BalKey -> BalKey -> BalKey
$cmax :: BalKey -> BalKey -> BalKey
>= :: BalKey -> BalKey -> Bool
$c>= :: BalKey -> BalKey -> Bool
> :: BalKey -> BalKey -> Bool
$c> :: BalKey -> BalKey -> Bool
<= :: BalKey -> BalKey -> Bool
$c<= :: BalKey -> BalKey -> Bool
< :: BalKey -> BalKey -> Bool
$c< :: BalKey -> BalKey -> Bool
compare :: BalKey -> BalKey -> Ordering
$ccompare :: BalKey -> BalKey -> Ordering
$cp1Ord :: Eq BalKey
Ord, (forall x. BalKey -> Rep BalKey x)
-> (forall x. Rep BalKey x -> BalKey) -> Generic BalKey
forall x. Rep BalKey x -> BalKey
forall x. BalKey -> Rep BalKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BalKey x -> BalKey
$cfrom :: forall x. BalKey -> Rep BalKey x
Generic, Int -> BalKey -> Int
BalKey -> Int
(Int -> BalKey -> Int) -> (BalKey -> Int) -> Hashable BalKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: BalKey -> Int
$chash :: BalKey -> Int
hashWithSalt :: Int -> BalKey -> Int
$chashWithSalt :: Int -> BalKey -> Int
Hashable)

instance Serialize BalKey where
    -- 0x04 · Address
    put :: Putter BalKey
put BalKey {balanceKey :: BalKey -> Address
balanceKey = Address
a} = do
        Putter Word8
putWord8 0x04
        Putter Address
forall t. Serialize t => Putter t
put Address
a
    -- 0x04
    put BalKeyS = Putter Word8
putWord8 0x04
    get :: Get BalKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x04) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        Address -> BalKey
BalKey (Address -> BalKey) -> Get Address -> Get BalKey
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Address
forall t. Serialize t => Get t
get

instance Key BalKey
instance KeyValue BalKey BalVal

-- | Key for best block in database.
data BestKey =
    BestKey
    deriving (Int -> BestKey -> ShowS
[BestKey] -> ShowS
BestKey -> String
(Int -> BestKey -> ShowS)
-> (BestKey -> String) -> ([BestKey] -> ShowS) -> Show BestKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BestKey] -> ShowS
$cshowList :: [BestKey] -> ShowS
show :: BestKey -> String
$cshow :: BestKey -> String
showsPrec :: Int -> BestKey -> ShowS
$cshowsPrec :: Int -> BestKey -> ShowS
Show, ReadPrec [BestKey]
ReadPrec BestKey
Int -> ReadS BestKey
ReadS [BestKey]
(Int -> ReadS BestKey)
-> ReadS [BestKey]
-> ReadPrec BestKey
-> ReadPrec [BestKey]
-> Read BestKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BestKey]
$creadListPrec :: ReadPrec [BestKey]
readPrec :: ReadPrec BestKey
$creadPrec :: ReadPrec BestKey
readList :: ReadS [BestKey]
$creadList :: ReadS [BestKey]
readsPrec :: Int -> ReadS BestKey
$creadsPrec :: Int -> ReadS BestKey
Read, BestKey -> BestKey -> Bool
(BestKey -> BestKey -> Bool)
-> (BestKey -> BestKey -> Bool) -> Eq BestKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BestKey -> BestKey -> Bool
$c/= :: BestKey -> BestKey -> Bool
== :: BestKey -> BestKey -> Bool
$c== :: BestKey -> BestKey -> Bool
Eq, Eq BestKey
Eq BestKey =>
(BestKey -> BestKey -> Ordering)
-> (BestKey -> BestKey -> Bool)
-> (BestKey -> BestKey -> Bool)
-> (BestKey -> BestKey -> Bool)
-> (BestKey -> BestKey -> Bool)
-> (BestKey -> BestKey -> BestKey)
-> (BestKey -> BestKey -> BestKey)
-> Ord BestKey
BestKey -> BestKey -> Bool
BestKey -> BestKey -> Ordering
BestKey -> BestKey -> BestKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BestKey -> BestKey -> BestKey
$cmin :: BestKey -> BestKey -> BestKey
max :: BestKey -> BestKey -> BestKey
$cmax :: BestKey -> BestKey -> BestKey
>= :: BestKey -> BestKey -> Bool
$c>= :: BestKey -> BestKey -> Bool
> :: BestKey -> BestKey -> Bool
$c> :: BestKey -> BestKey -> Bool
<= :: BestKey -> BestKey -> Bool
$c<= :: BestKey -> BestKey -> Bool
< :: BestKey -> BestKey -> Bool
$c< :: BestKey -> BestKey -> Bool
compare :: BestKey -> BestKey -> Ordering
$ccompare :: BestKey -> BestKey -> Ordering
$cp1Ord :: Eq BestKey
Ord, (forall x. BestKey -> Rep BestKey x)
-> (forall x. Rep BestKey x -> BestKey) -> Generic BestKey
forall x. Rep BestKey x -> BestKey
forall x. BestKey -> Rep BestKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BestKey x -> BestKey
$cfrom :: forall x. BestKey -> Rep BestKey x
Generic, Int -> BestKey -> Int
BestKey -> Int
(Int -> BestKey -> Int) -> (BestKey -> Int) -> Hashable BestKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: BestKey -> Int
$chash :: BestKey -> Int
hashWithSalt :: Int -> BestKey -> Int
$chashWithSalt :: Int -> BestKey -> Int
Hashable)

instance Serialize BestKey where
    -- 0x00 × 32
    put :: Putter BestKey
put BestKey = Putter ByteString
forall t. Serialize t => Putter t
put (Int -> Word8 -> ByteString
BS.replicate 32 0x00)
    get :: Get BestKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (ByteString -> Bool) -> ByteString -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Word8 -> ByteString
BS.replicate 32 0x00) (ByteString -> Get ()) -> Get ByteString -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Int -> Get ByteString
getBytes 32
        BestKey -> Get BestKey
forall (m :: * -> *) a. Monad m => a -> m a
return BestKey
BestKey

instance Key BestKey
instance KeyValue BestKey BlockHash

-- | Key for database version.
data VersionKey =
    VersionKey
    deriving (VersionKey -> VersionKey -> Bool
(VersionKey -> VersionKey -> Bool)
-> (VersionKey -> VersionKey -> Bool) -> Eq VersionKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionKey -> VersionKey -> Bool
$c/= :: VersionKey -> VersionKey -> Bool
== :: VersionKey -> VersionKey -> Bool
$c== :: VersionKey -> VersionKey -> Bool
Eq, Int -> VersionKey -> ShowS
[VersionKey] -> ShowS
VersionKey -> String
(Int -> VersionKey -> ShowS)
-> (VersionKey -> String)
-> ([VersionKey] -> ShowS)
-> Show VersionKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionKey] -> ShowS
$cshowList :: [VersionKey] -> ShowS
show :: VersionKey -> String
$cshow :: VersionKey -> String
showsPrec :: Int -> VersionKey -> ShowS
$cshowsPrec :: Int -> VersionKey -> ShowS
Show, ReadPrec [VersionKey]
ReadPrec VersionKey
Int -> ReadS VersionKey
ReadS [VersionKey]
(Int -> ReadS VersionKey)
-> ReadS [VersionKey]
-> ReadPrec VersionKey
-> ReadPrec [VersionKey]
-> Read VersionKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VersionKey]
$creadListPrec :: ReadPrec [VersionKey]
readPrec :: ReadPrec VersionKey
$creadPrec :: ReadPrec VersionKey
readList :: ReadS [VersionKey]
$creadList :: ReadS [VersionKey]
readsPrec :: Int -> ReadS VersionKey
$creadsPrec :: Int -> ReadS VersionKey
Read, Eq VersionKey
Eq VersionKey =>
(VersionKey -> VersionKey -> Ordering)
-> (VersionKey -> VersionKey -> Bool)
-> (VersionKey -> VersionKey -> Bool)
-> (VersionKey -> VersionKey -> Bool)
-> (VersionKey -> VersionKey -> Bool)
-> (VersionKey -> VersionKey -> VersionKey)
-> (VersionKey -> VersionKey -> VersionKey)
-> Ord VersionKey
VersionKey -> VersionKey -> Bool
VersionKey -> VersionKey -> Ordering
VersionKey -> VersionKey -> VersionKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VersionKey -> VersionKey -> VersionKey
$cmin :: VersionKey -> VersionKey -> VersionKey
max :: VersionKey -> VersionKey -> VersionKey
$cmax :: VersionKey -> VersionKey -> VersionKey
>= :: VersionKey -> VersionKey -> Bool
$c>= :: VersionKey -> VersionKey -> Bool
> :: VersionKey -> VersionKey -> Bool
$c> :: VersionKey -> VersionKey -> Bool
<= :: VersionKey -> VersionKey -> Bool
$c<= :: VersionKey -> VersionKey -> Bool
< :: VersionKey -> VersionKey -> Bool
$c< :: VersionKey -> VersionKey -> Bool
compare :: VersionKey -> VersionKey -> Ordering
$ccompare :: VersionKey -> VersionKey -> Ordering
$cp1Ord :: Eq VersionKey
Ord, (forall x. VersionKey -> Rep VersionKey x)
-> (forall x. Rep VersionKey x -> VersionKey) -> Generic VersionKey
forall x. Rep VersionKey x -> VersionKey
forall x. VersionKey -> Rep VersionKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionKey x -> VersionKey
$cfrom :: forall x. VersionKey -> Rep VersionKey x
Generic, Int -> VersionKey -> Int
VersionKey -> Int
(Int -> VersionKey -> Int)
-> (VersionKey -> Int) -> Hashable VersionKey
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: VersionKey -> Int
$chash :: VersionKey -> Int
hashWithSalt :: Int -> VersionKey -> Int
$chashWithSalt :: Int -> VersionKey -> Int
Hashable)

instance Serialize VersionKey where
    -- 0x0a
    put :: Putter VersionKey
put VersionKey = Putter Word8
putWord8 0x0a
    get :: Get VersionKey
get = do
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> (Word8 -> Bool) -> Word8 -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x0a) (Word8 -> Get ()) -> Get Word8 -> Get ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
getWord8
        VersionKey -> Get VersionKey
forall (m :: * -> *) a. Monad m => a -> m a
return VersionKey
VersionKey

instance Key VersionKey
instance KeyValue VersionKey Word32

data BalVal = BalVal
    { BalVal -> Word64
balValAmount        :: !Word64
    , BalVal -> Word64
balValZero          :: !Word64
    , BalVal -> Word64
balValUnspentCount  :: !Word64
    , BalVal -> Word64
balValTxCount       :: !Word64
    , BalVal -> Word64
balValTotalReceived :: !Word64
    } deriving (Int -> BalVal -> ShowS
[BalVal] -> ShowS
BalVal -> String
(Int -> BalVal -> ShowS)
-> (BalVal -> String) -> ([BalVal] -> ShowS) -> Show BalVal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BalVal] -> ShowS
$cshowList :: [BalVal] -> ShowS
show :: BalVal -> String
$cshow :: BalVal -> String
showsPrec :: Int -> BalVal -> ShowS
$cshowsPrec :: Int -> BalVal -> ShowS
Show, ReadPrec [BalVal]
ReadPrec BalVal
Int -> ReadS BalVal
ReadS [BalVal]
(Int -> ReadS BalVal)
-> ReadS [BalVal]
-> ReadPrec BalVal
-> ReadPrec [BalVal]
-> Read BalVal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BalVal]
$creadListPrec :: ReadPrec [BalVal]
readPrec :: ReadPrec BalVal
$creadPrec :: ReadPrec BalVal
readList :: ReadS [BalVal]
$creadList :: ReadS [BalVal]
readsPrec :: Int -> ReadS BalVal
$creadsPrec :: Int -> ReadS BalVal
Read, BalVal -> BalVal -> Bool
(BalVal -> BalVal -> Bool)
-> (BalVal -> BalVal -> Bool) -> Eq BalVal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BalVal -> BalVal -> Bool
$c/= :: BalVal -> BalVal -> Bool
== :: BalVal -> BalVal -> Bool
$c== :: BalVal -> BalVal -> Bool
Eq, Eq BalVal
Eq BalVal =>
(BalVal -> BalVal -> Ordering)
-> (BalVal -> BalVal -> Bool)
-> (BalVal -> BalVal -> Bool)
-> (BalVal -> BalVal -> Bool)
-> (BalVal -> BalVal -> Bool)
-> (BalVal -> BalVal -> BalVal)
-> (BalVal -> BalVal -> BalVal)
-> Ord BalVal
BalVal -> BalVal -> Bool
BalVal -> BalVal -> Ordering
BalVal -> BalVal -> BalVal
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BalVal -> BalVal -> BalVal
$cmin :: BalVal -> BalVal -> BalVal
max :: BalVal -> BalVal -> BalVal
$cmax :: BalVal -> BalVal -> BalVal
>= :: BalVal -> BalVal -> Bool
$c>= :: BalVal -> BalVal -> Bool
> :: BalVal -> BalVal -> Bool
$c> :: BalVal -> BalVal -> Bool
<= :: BalVal -> BalVal -> Bool
$c<= :: BalVal -> BalVal -> Bool
< :: BalVal -> BalVal -> Bool
$c< :: BalVal -> BalVal -> Bool
compare :: BalVal -> BalVal -> Ordering
$ccompare :: BalVal -> BalVal -> Ordering
$cp1Ord :: Eq BalVal
Ord, (forall x. BalVal -> Rep BalVal x)
-> (forall x. Rep BalVal x -> BalVal) -> Generic BalVal
forall x. Rep BalVal x -> BalVal
forall x. BalVal -> Rep BalVal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BalVal x -> BalVal
$cfrom :: forall x. BalVal -> Rep BalVal x
Generic, Int -> BalVal -> Int
BalVal -> Int
(Int -> BalVal -> Int) -> (BalVal -> Int) -> Hashable BalVal
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: BalVal -> Int
$chash :: BalVal -> Int
hashWithSalt :: Int -> BalVal -> Int
$chashWithSalt :: Int -> BalVal -> Int
Hashable, Get BalVal
Putter BalVal
Putter BalVal -> Get BalVal -> Serialize BalVal
forall t. Putter t -> Get t -> Serialize t
get :: Get BalVal
$cget :: Get BalVal
put :: Putter BalVal
$cput :: Putter BalVal
Serialize, BalVal -> ()
(BalVal -> ()) -> NFData BalVal
forall a. (a -> ()) -> NFData a
rnf :: BalVal -> ()
$crnf :: BalVal -> ()
NFData)

valToBalance :: Address -> BalVal -> Balance
valToBalance :: Address -> BalVal -> Balance
valToBalance a :: Address
a BalVal { balValAmount :: BalVal -> Word64
balValAmount = Word64
v
                      , balValZero :: BalVal -> Word64
balValZero = Word64
z
                      , balValUnspentCount :: BalVal -> Word64
balValUnspentCount = Word64
u
                      , balValTxCount :: BalVal -> Word64
balValTxCount = Word64
t
                      , balValTotalReceived :: BalVal -> Word64
balValTotalReceived = Word64
r
                      } =
    $WBalance :: Address
-> Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> Balance
Balance
        { balanceAddress :: Address
balanceAddress = Address
a
        , balanceAmount :: Word64
balanceAmount = Word64
v
        , balanceZero :: Word64
balanceZero = Word64
z
        , balanceUnspentCount :: Word64
balanceUnspentCount = Word64
u
        , balanceTxCount :: Word64
balanceTxCount = Word64
t
        , balanceTotalReceived :: Word64
balanceTotalReceived = Word64
r
        }

balanceToVal :: Balance -> BalVal
balanceToVal :: Balance -> BalVal
balanceToVal Balance { balanceAmount :: Balance -> Word64
balanceAmount = Word64
v
                     , balanceZero :: Balance -> Word64
balanceZero = Word64
z
                     , balanceUnspentCount :: Balance -> Word64
balanceUnspentCount = Word64
u
                     , balanceTxCount :: Balance -> Word64
balanceTxCount = Word64
t
                     , balanceTotalReceived :: Balance -> Word64
balanceTotalReceived = Word64
r
                     } =
    $WBalVal :: Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> BalVal
BalVal
        { balValAmount :: Word64
balValAmount = Word64
v
        , balValZero :: Word64
balValZero = Word64
z
        , balValUnspentCount :: Word64
balValUnspentCount = Word64
u
        , balValTxCount :: Word64
balValTxCount = Word64
t
        , balValTotalReceived :: Word64
balValTotalReceived = Word64
r
        }

-- | Default balance for an address.
instance Default BalVal where
    def :: BalVal
def =
        $WBalVal :: Word64 -> Word64 -> Word64 -> Word64 -> Word64 -> BalVal
BalVal
            { balValAmount :: Word64
balValAmount = 0
            , balValZero :: Word64
balValZero = 0
            , balValUnspentCount :: Word64
balValUnspentCount = 0
            , balValTxCount :: Word64
balValTxCount = 0
            , balValTotalReceived :: Word64
balValTotalReceived = 0
            }

data UnspentVal = UnspentVal
    { UnspentVal -> BlockRef
unspentValBlock  :: !BlockRef
    , UnspentVal -> Word64
unspentValAmount :: !Word64
    , UnspentVal -> ShortByteString
unspentValScript :: !ShortByteString
    } deriving (Int -> UnspentVal -> ShowS
[UnspentVal] -> ShowS
UnspentVal -> String
(Int -> UnspentVal -> ShowS)
-> (UnspentVal -> String)
-> ([UnspentVal] -> ShowS)
-> Show UnspentVal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnspentVal] -> ShowS
$cshowList :: [UnspentVal] -> ShowS
show :: UnspentVal -> String
$cshow :: UnspentVal -> String
showsPrec :: Int -> UnspentVal -> ShowS
$cshowsPrec :: Int -> UnspentVal -> ShowS
Show, ReadPrec [UnspentVal]
ReadPrec UnspentVal
Int -> ReadS UnspentVal
ReadS [UnspentVal]
(Int -> ReadS UnspentVal)
-> ReadS [UnspentVal]
-> ReadPrec UnspentVal
-> ReadPrec [UnspentVal]
-> Read UnspentVal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnspentVal]
$creadListPrec :: ReadPrec [UnspentVal]
readPrec :: ReadPrec UnspentVal
$creadPrec :: ReadPrec UnspentVal
readList :: ReadS [UnspentVal]
$creadList :: ReadS [UnspentVal]
readsPrec :: Int -> ReadS UnspentVal
$creadsPrec :: Int -> ReadS UnspentVal
Read, UnspentVal -> UnspentVal -> Bool
(UnspentVal -> UnspentVal -> Bool)
-> (UnspentVal -> UnspentVal -> Bool) -> Eq UnspentVal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnspentVal -> UnspentVal -> Bool
$c/= :: UnspentVal -> UnspentVal -> Bool
== :: UnspentVal -> UnspentVal -> Bool
$c== :: UnspentVal -> UnspentVal -> Bool
Eq, Eq UnspentVal
Eq UnspentVal =>
(UnspentVal -> UnspentVal -> Ordering)
-> (UnspentVal -> UnspentVal -> Bool)
-> (UnspentVal -> UnspentVal -> Bool)
-> (UnspentVal -> UnspentVal -> Bool)
-> (UnspentVal -> UnspentVal -> Bool)
-> (UnspentVal -> UnspentVal -> UnspentVal)
-> (UnspentVal -> UnspentVal -> UnspentVal)
-> Ord UnspentVal
UnspentVal -> UnspentVal -> Bool
UnspentVal -> UnspentVal -> Ordering
UnspentVal -> UnspentVal -> UnspentVal
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnspentVal -> UnspentVal -> UnspentVal
$cmin :: UnspentVal -> UnspentVal -> UnspentVal
max :: UnspentVal -> UnspentVal -> UnspentVal
$cmax :: UnspentVal -> UnspentVal -> UnspentVal
>= :: UnspentVal -> UnspentVal -> Bool
$c>= :: UnspentVal -> UnspentVal -> Bool
> :: UnspentVal -> UnspentVal -> Bool
$c> :: UnspentVal -> UnspentVal -> Bool
<= :: UnspentVal -> UnspentVal -> Bool
$c<= :: UnspentVal -> UnspentVal -> Bool
< :: UnspentVal -> UnspentVal -> Bool
$c< :: UnspentVal -> UnspentVal -> Bool
compare :: UnspentVal -> UnspentVal -> Ordering
$ccompare :: UnspentVal -> UnspentVal -> Ordering
$cp1Ord :: Eq UnspentVal
Ord, (forall x. UnspentVal -> Rep UnspentVal x)
-> (forall x. Rep UnspentVal x -> UnspentVal) -> Generic UnspentVal
forall x. Rep UnspentVal x -> UnspentVal
forall x. UnspentVal -> Rep UnspentVal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnspentVal x -> UnspentVal
$cfrom :: forall x. UnspentVal -> Rep UnspentVal x
Generic, Int -> UnspentVal -> Int
UnspentVal -> Int
(Int -> UnspentVal -> Int)
-> (UnspentVal -> Int) -> Hashable UnspentVal
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: UnspentVal -> Int
$chash :: UnspentVal -> Int
hashWithSalt :: Int -> UnspentVal -> Int
$chashWithSalt :: Int -> UnspentVal -> Int
Hashable, Get UnspentVal
Putter UnspentVal
Putter UnspentVal -> Get UnspentVal -> Serialize UnspentVal
forall t. Putter t -> Get t -> Serialize t
get :: Get UnspentVal
$cget :: Get UnspentVal
put :: Putter UnspentVal
$cput :: Putter UnspentVal
Serialize, UnspentVal -> ()
(UnspentVal -> ()) -> NFData UnspentVal
forall a. (a -> ()) -> NFData a
rnf :: UnspentVal -> ()
$crnf :: UnspentVal -> ()
NFData)

unspentToVal :: Unspent -> (OutPoint, UnspentVal)
unspentToVal :: Unspent -> (OutPoint, UnspentVal)
unspentToVal Unspent { unspentBlock :: Unspent -> BlockRef
unspentBlock = BlockRef
b
                     , unspentPoint :: Unspent -> OutPoint
unspentPoint = OutPoint
p
                     , unspentAmount :: Unspent -> Word64
unspentAmount = Word64
v
                     , unspentScript :: Unspent -> ShortByteString
unspentScript = ShortByteString
s
                     } =
    ( OutPoint
p
    , $WUnspentVal :: BlockRef -> Word64 -> ShortByteString -> UnspentVal
UnspentVal
          {unspentValBlock :: BlockRef
unspentValBlock = BlockRef
b, unspentValAmount :: Word64
unspentValAmount = Word64
v, unspentValScript :: ShortByteString
unspentValScript = ShortByteString
s})

valToUnspent :: OutPoint -> UnspentVal -> Unspent
valToUnspent :: OutPoint -> UnspentVal -> Unspent
valToUnspent p :: OutPoint
p UnspentVal { unspentValBlock :: UnspentVal -> BlockRef
unspentValBlock = BlockRef
b
                          , unspentValAmount :: UnspentVal -> Word64
unspentValAmount = Word64
v
                          , unspentValScript :: UnspentVal -> ShortByteString
unspentValScript = ShortByteString
s
                          } =
    $WUnspent :: BlockRef
-> OutPoint
-> Word64
-> ShortByteString
-> Maybe Address
-> Unspent
Unspent
        { unspentBlock :: BlockRef
unspentBlock = BlockRef
b
        , unspentPoint :: OutPoint
unspentPoint = OutPoint
p
        , unspentAmount :: Word64
unspentAmount = Word64
v
        , unspentScript :: ShortByteString
unspentScript = ShortByteString
s
        , unspentAddress :: Maybe Address
unspentAddress = Either String Address -> Maybe Address
forall a b. Either a b -> Maybe b
eitherToMaybe (ByteString -> Either String Address
scriptToAddressBS (ShortByteString -> ByteString
BSS.fromShort ShortByteString
s))
        }