{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE TemplateHaskell            #-}
module Network.Ethereum.Api.Types where
import           Data.Aeson                 (FromJSON (..), Options (fieldLabelModifier, omitNothingFields),
                                             ToJSON (..), Value (Bool, String),
                                             defaultOptions, object, (.=))
import           Data.Aeson.TH              (deriveJSON)
import           Data.ByteArray.HexString   (HexString)
import           Data.Char                  (toLower)
import           Data.Default               (Default (..))
import           Data.Solidity.Prim.Address (Address)
import           Data.String                (IsString (..))
import qualified Data.Text                  as T (pack)
import qualified Data.Text.Lazy.Builder     as B (toLazyText)
import qualified Data.Text.Lazy.Builder.Int as B (hexadecimal)
import qualified Data.Text.Read             as R (decimal, hexadecimal)
import           GHC.Generics               (Generic)
import           Lens.Micro                 (over, _head)
newtype Quantity = Quantity { Quantity -> Integer
unQuantity :: Integer }
    deriving (Integer -> Quantity
Quantity -> Quantity
Quantity -> Quantity -> Quantity
(Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity)
-> (Quantity -> Quantity)
-> (Quantity -> Quantity)
-> (Integer -> Quantity)
-> Num Quantity
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Quantity
$cfromInteger :: Integer -> Quantity
signum :: Quantity -> Quantity
$csignum :: Quantity -> Quantity
abs :: Quantity -> Quantity
$cabs :: Quantity -> Quantity
negate :: Quantity -> Quantity
$cnegate :: Quantity -> Quantity
* :: Quantity -> Quantity -> Quantity
$c* :: Quantity -> Quantity -> Quantity
- :: Quantity -> Quantity -> Quantity
$c- :: Quantity -> Quantity -> Quantity
+ :: Quantity -> Quantity -> Quantity
$c+ :: Quantity -> Quantity -> Quantity
Num, Num Quantity
Ord Quantity
Num Quantity
-> Ord Quantity -> (Quantity -> Rational) -> Real Quantity
Quantity -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Quantity -> Rational
$ctoRational :: Quantity -> Rational
$cp2Real :: Ord Quantity
$cp1Real :: Num Quantity
Real, Enum Quantity
Real Quantity
Real Quantity
-> Enum Quantity
-> (Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity -> (Quantity, Quantity))
-> (Quantity -> Quantity -> (Quantity, Quantity))
-> (Quantity -> Integer)
-> Integral Quantity
Quantity -> Integer
Quantity -> Quantity -> (Quantity, Quantity)
Quantity -> Quantity -> Quantity
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Quantity -> Integer
$ctoInteger :: Quantity -> Integer
divMod :: Quantity -> Quantity -> (Quantity, Quantity)
$cdivMod :: Quantity -> Quantity -> (Quantity, Quantity)
quotRem :: Quantity -> Quantity -> (Quantity, Quantity)
$cquotRem :: Quantity -> Quantity -> (Quantity, Quantity)
mod :: Quantity -> Quantity -> Quantity
$cmod :: Quantity -> Quantity -> Quantity
div :: Quantity -> Quantity -> Quantity
$cdiv :: Quantity -> Quantity -> Quantity
rem :: Quantity -> Quantity -> Quantity
$crem :: Quantity -> Quantity -> Quantity
quot :: Quantity -> Quantity -> Quantity
$cquot :: Quantity -> Quantity -> Quantity
$cp2Integral :: Enum Quantity
$cp1Integral :: Real Quantity
Integral, Int -> Quantity
Quantity -> Int
Quantity -> [Quantity]
Quantity -> Quantity
Quantity -> Quantity -> [Quantity]
Quantity -> Quantity -> Quantity -> [Quantity]
(Quantity -> Quantity)
-> (Quantity -> Quantity)
-> (Int -> Quantity)
-> (Quantity -> Int)
-> (Quantity -> [Quantity])
-> (Quantity -> Quantity -> [Quantity])
-> (Quantity -> Quantity -> [Quantity])
-> (Quantity -> Quantity -> Quantity -> [Quantity])
-> Enum Quantity
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Quantity -> Quantity -> Quantity -> [Quantity]
$cenumFromThenTo :: Quantity -> Quantity -> Quantity -> [Quantity]
enumFromTo :: Quantity -> Quantity -> [Quantity]
$cenumFromTo :: Quantity -> Quantity -> [Quantity]
enumFromThen :: Quantity -> Quantity -> [Quantity]
$cenumFromThen :: Quantity -> Quantity -> [Quantity]
enumFrom :: Quantity -> [Quantity]
$cenumFrom :: Quantity -> [Quantity]
fromEnum :: Quantity -> Int
$cfromEnum :: Quantity -> Int
toEnum :: Int -> Quantity
$ctoEnum :: Int -> Quantity
pred :: Quantity -> Quantity
$cpred :: Quantity -> Quantity
succ :: Quantity -> Quantity
$csucc :: Quantity -> Quantity
Enum, Quantity -> Quantity -> Bool
(Quantity -> Quantity -> Bool)
-> (Quantity -> Quantity -> Bool) -> Eq Quantity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Quantity -> Quantity -> Bool
$c/= :: Quantity -> Quantity -> Bool
== :: Quantity -> Quantity -> Bool
$c== :: Quantity -> Quantity -> Bool
Eq, Eq Quantity
Eq Quantity
-> (Quantity -> Quantity -> Ordering)
-> (Quantity -> Quantity -> Bool)
-> (Quantity -> Quantity -> Bool)
-> (Quantity -> Quantity -> Bool)
-> (Quantity -> Quantity -> Bool)
-> (Quantity -> Quantity -> Quantity)
-> (Quantity -> Quantity -> Quantity)
-> Ord Quantity
Quantity -> Quantity -> Bool
Quantity -> Quantity -> Ordering
Quantity -> Quantity -> Quantity
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 :: Quantity -> Quantity -> Quantity
$cmin :: Quantity -> Quantity -> Quantity
max :: Quantity -> Quantity -> Quantity
$cmax :: Quantity -> Quantity -> Quantity
>= :: Quantity -> Quantity -> Bool
$c>= :: Quantity -> Quantity -> Bool
> :: Quantity -> Quantity -> Bool
$c> :: Quantity -> Quantity -> Bool
<= :: Quantity -> Quantity -> Bool
$c<= :: Quantity -> Quantity -> Bool
< :: Quantity -> Quantity -> Bool
$c< :: Quantity -> Quantity -> Bool
compare :: Quantity -> Quantity -> Ordering
$ccompare :: Quantity -> Quantity -> Ordering
$cp1Ord :: Eq Quantity
Ord, (forall x. Quantity -> Rep Quantity x)
-> (forall x. Rep Quantity x -> Quantity) -> Generic Quantity
forall x. Rep Quantity x -> Quantity
forall x. Quantity -> Rep Quantity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Quantity x -> Quantity
$cfrom :: forall x. Quantity -> Rep Quantity x
Generic)
instance Show Quantity where
    show :: Quantity -> String
show = Integer -> String
forall a. Show a => a -> String
show (Integer -> String) -> (Quantity -> Integer) -> Quantity -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Quantity -> Integer
unQuantity
instance IsString Quantity where
    fromString :: String -> Quantity
fromString (Char
'0' : Char
'x' : String
hex) =
        case Reader Integer
forall a. Integral a => Reader a
R.hexadecimal (String -> Text
T.pack String
hex) of
            Right (Integer
x, Text
"") -> Integer -> Quantity
Quantity Integer
x
            Either String (Integer, Text)
_             -> String -> Quantity
forall a. HasCallStack => String -> a
error (String
"Quantity " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
hex String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is not valid hex")
    fromString String
num =
        case Reader Integer
forall a. Integral a => Reader a
R.decimal (String -> Text
T.pack String
num) of
            Right (Integer
x, Text
"") -> Integer -> Quantity
Quantity Integer
x
            Either String (Integer, Text)
_             -> String -> Quantity
forall a. HasCallStack => String -> a
error (String
"Quantity " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
num String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is not valid decimal")
instance ToJSON Quantity where
    toJSON :: Quantity -> Value
toJSON (Quantity Integer
x) =
        let hexValue :: Text
hexValue = Builder -> Text
B.toLazyText (Integer -> Builder
forall a. Integral a => a -> Builder
B.hexadecimal Integer
x)
        in  Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text
"0x" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
hexValue)
instance FromJSON Quantity where
    parseJSON :: Value -> Parser Quantity
parseJSON (String Text
v) =
        case Reader Integer
forall a. Integral a => Reader a
R.hexadecimal Text
v of
            Right (Integer
x, Text
"") -> Quantity -> Parser Quantity
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> Quantity
Quantity Integer
x)
            Either String (Integer, Text)
_             -> String -> Parser Quantity
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Quantity) -> String -> Parser Quantity
forall a b. (a -> b) -> a -> b
$ String
"Quantity " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
v String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" is not valid hex"
    parseJSON Value
_ = String -> Parser Quantity
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Quantity should be a JSON String"
data SyncActive = SyncActive
    { SyncActive -> Quantity
syncStartingBlock :: !Quantity
    
    , SyncActive -> Quantity
syncCurrentBlock  :: !Quantity
    
    , SyncActive -> Quantity
syncHighestBlock  :: !Quantity
    
    }
    deriving (SyncActive -> SyncActive -> Bool
(SyncActive -> SyncActive -> Bool)
-> (SyncActive -> SyncActive -> Bool) -> Eq SyncActive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SyncActive -> SyncActive -> Bool
$c/= :: SyncActive -> SyncActive -> Bool
== :: SyncActive -> SyncActive -> Bool
$c== :: SyncActive -> SyncActive -> Bool
Eq, (forall x. SyncActive -> Rep SyncActive x)
-> (forall x. Rep SyncActive x -> SyncActive) -> Generic SyncActive
forall x. Rep SyncActive x -> SyncActive
forall x. SyncActive -> Rep SyncActive x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SyncActive x -> SyncActive
$cfrom :: forall x. SyncActive -> Rep SyncActive x
Generic, Int -> SyncActive -> ShowS
[SyncActive] -> ShowS
SyncActive -> String
(Int -> SyncActive -> ShowS)
-> (SyncActive -> String)
-> ([SyncActive] -> ShowS)
-> Show SyncActive
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SyncActive] -> ShowS
$cshowList :: [SyncActive] -> ShowS
show :: SyncActive -> String
$cshow :: SyncActive -> String
showsPrec :: Int -> SyncActive -> ShowS
$cshowsPrec :: Int -> SyncActive -> ShowS
Show)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = over _head toLower . drop 4 }) ''SyncActive)
data SyncingState = Syncing SyncActive
    | NotSyncing
    deriving (SyncingState -> SyncingState -> Bool
(SyncingState -> SyncingState -> Bool)
-> (SyncingState -> SyncingState -> Bool) -> Eq SyncingState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SyncingState -> SyncingState -> Bool
$c/= :: SyncingState -> SyncingState -> Bool
== :: SyncingState -> SyncingState -> Bool
$c== :: SyncingState -> SyncingState -> Bool
Eq, (forall x. SyncingState -> Rep SyncingState x)
-> (forall x. Rep SyncingState x -> SyncingState)
-> Generic SyncingState
forall x. Rep SyncingState x -> SyncingState
forall x. SyncingState -> Rep SyncingState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SyncingState x -> SyncingState
$cfrom :: forall x. SyncingState -> Rep SyncingState x
Generic, Int -> SyncingState -> ShowS
[SyncingState] -> ShowS
SyncingState -> String
(Int -> SyncingState -> ShowS)
-> (SyncingState -> String)
-> ([SyncingState] -> ShowS)
-> Show SyncingState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SyncingState] -> ShowS
$cshowList :: [SyncingState] -> ShowS
show :: SyncingState -> String
$cshow :: SyncingState -> String
showsPrec :: Int -> SyncingState -> ShowS
$cshowsPrec :: Int -> SyncingState -> ShowS
Show)
instance FromJSON SyncingState where
    parseJSON :: Value -> Parser SyncingState
parseJSON (Bool Bool
_) = SyncingState -> Parser SyncingState
forall (f :: * -> *) a. Applicative f => a -> f a
pure SyncingState
NotSyncing
    parseJSON Value
v        = SyncActive -> SyncingState
Syncing (SyncActive -> SyncingState)
-> Parser SyncActive -> Parser SyncingState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser SyncActive
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
data Change = Change
    { Change -> Maybe Quantity
changeLogIndex         :: !(Maybe Quantity)
    
    , Change -> Maybe Quantity
changeTransactionIndex :: !(Maybe Quantity)
    
    , Change -> Maybe HexString
changeTransactionHash  :: !(Maybe HexString)
    
    , Change -> Maybe HexString
changeBlockHash        :: !(Maybe HexString)
    
    , Change -> Maybe Quantity
changeBlockNumber      :: !(Maybe Quantity)
    
    , Change -> Address
changeAddress          :: !Address
    
    , Change -> HexString
changeData             :: !HexString
    
    , Change -> [HexString]
changeTopics           :: ![HexString]
    
    }
    deriving (Change -> Change -> Bool
(Change -> Change -> Bool)
-> (Change -> Change -> Bool) -> Eq Change
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Change -> Change -> Bool
$c/= :: Change -> Change -> Bool
== :: Change -> Change -> Bool
$c== :: Change -> Change -> Bool
Eq, Int -> Change -> ShowS
[Change] -> ShowS
Change -> String
(Int -> Change -> ShowS)
-> (Change -> String) -> ([Change] -> ShowS) -> Show Change
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Change] -> ShowS
$cshowList :: [Change] -> ShowS
show :: Change -> String
$cshow :: Change -> String
showsPrec :: Int -> Change -> ShowS
$cshowsPrec :: Int -> Change -> ShowS
Show, (forall x. Change -> Rep Change x)
-> (forall x. Rep Change x -> Change) -> Generic Change
forall x. Rep Change x -> Change
forall x. Change -> Rep Change x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Change x -> Change
$cfrom :: forall x. Change -> Rep Change x
Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = over _head toLower . drop 6 }) ''Change)
data Call = Call
    { Call -> Maybe Address
callFrom     :: !(Maybe Address)
    
    , Call -> Maybe Address
callTo       :: !(Maybe Address)
    
    , Call -> Maybe Quantity
callGas      :: !(Maybe Quantity)
    
    , Call -> Maybe Quantity
callGasPrice :: !(Maybe Quantity)
    
    , Call -> Maybe Quantity
callValue    :: !(Maybe Quantity)
    
    , Call -> Maybe HexString
callData     :: !(Maybe HexString)
    
    , Call -> Maybe Quantity
callNonce    :: !(Maybe Quantity)
    
    }
    deriving (Call -> Call -> Bool
(Call -> Call -> Bool) -> (Call -> Call -> Bool) -> Eq Call
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Call -> Call -> Bool
$c/= :: Call -> Call -> Bool
== :: Call -> Call -> Bool
$c== :: Call -> Call -> Bool
Eq, Int -> Call -> ShowS
[Call] -> ShowS
Call -> String
(Int -> Call -> ShowS)
-> (Call -> String) -> ([Call] -> ShowS) -> Show Call
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Call] -> ShowS
$cshowList :: [Call] -> ShowS
show :: Call -> String
$cshow :: Call -> String
showsPrec :: Int -> Call -> ShowS
$cshowsPrec :: Int -> Call -> ShowS
Show, (forall x. Call -> Rep Call x)
-> (forall x. Rep Call x -> Call) -> Generic Call
forall x. Rep Call x -> Call
forall x. Call -> Rep Call x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Call x -> Call
$cfrom :: forall x. Call -> Rep Call x
Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = over _head toLower . drop 4
    , omitNothingFields = True }) ''Call)
instance Default Call where
    def :: Call
def = Maybe Address
-> Maybe Address
-> Maybe Quantity
-> Maybe Quantity
-> Maybe Quantity
-> Maybe HexString
-> Maybe Quantity
-> Call
Call Maybe Address
forall a. Maybe a
Nothing Maybe Address
forall a. Maybe a
Nothing (Quantity -> Maybe Quantity
forall a. a -> Maybe a
Just Quantity
3000000) Maybe Quantity
forall a. Maybe a
Nothing (Quantity -> Maybe Quantity
forall a. a -> Maybe a
Just Quantity
0) Maybe HexString
forall a. Maybe a
Nothing Maybe Quantity
forall a. Maybe a
Nothing
data DefaultBlock = BlockWithNumber Quantity
    | Earliest
    | Latest
    | Pending
    deriving (DefaultBlock -> DefaultBlock -> Bool
(DefaultBlock -> DefaultBlock -> Bool)
-> (DefaultBlock -> DefaultBlock -> Bool) -> Eq DefaultBlock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefaultBlock -> DefaultBlock -> Bool
$c/= :: DefaultBlock -> DefaultBlock -> Bool
== :: DefaultBlock -> DefaultBlock -> Bool
$c== :: DefaultBlock -> DefaultBlock -> Bool
Eq, Int -> DefaultBlock -> ShowS
[DefaultBlock] -> ShowS
DefaultBlock -> String
(Int -> DefaultBlock -> ShowS)
-> (DefaultBlock -> String)
-> ([DefaultBlock] -> ShowS)
-> Show DefaultBlock
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DefaultBlock] -> ShowS
$cshowList :: [DefaultBlock] -> ShowS
show :: DefaultBlock -> String
$cshow :: DefaultBlock -> String
showsPrec :: Int -> DefaultBlock -> ShowS
$cshowsPrec :: Int -> DefaultBlock -> ShowS
Show, (forall x. DefaultBlock -> Rep DefaultBlock x)
-> (forall x. Rep DefaultBlock x -> DefaultBlock)
-> Generic DefaultBlock
forall x. Rep DefaultBlock x -> DefaultBlock
forall x. DefaultBlock -> Rep DefaultBlock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DefaultBlock x -> DefaultBlock
$cfrom :: forall x. DefaultBlock -> Rep DefaultBlock x
Generic)
instance ToJSON DefaultBlock where
    toJSON :: DefaultBlock -> Value
toJSON (BlockWithNumber Quantity
bn) = Quantity -> Value
forall a. ToJSON a => a -> Value
toJSON Quantity
bn
    toJSON DefaultBlock
parameter            = String -> Value
forall a. ToJSON a => a -> Value
toJSON (String -> Value)
-> (DefaultBlock -> String) -> DefaultBlock -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter String String Char Char -> (Char -> Char) -> ShowS
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter String String Char Char
forall s a. Cons s s a a => Traversal' s a
_head Char -> Char
toLower ShowS -> (DefaultBlock -> String) -> DefaultBlock -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DefaultBlock -> String
forall a. Show a => a -> String
show (DefaultBlock -> Value) -> DefaultBlock -> Value
forall a b. (a -> b) -> a -> b
$ DefaultBlock
parameter
data Filter e = Filter
    { Filter e -> Maybe [Address]
filterAddress   :: !(Maybe [Address])
    
    , Filter e -> DefaultBlock
filterFromBlock :: !DefaultBlock
    
    , Filter e -> DefaultBlock
filterToBlock   :: !DefaultBlock
    
    , Filter e -> Maybe [Maybe HexString]
filterTopics    :: !(Maybe [Maybe HexString])
    
    }
    deriving (Filter e -> Filter e -> Bool
(Filter e -> Filter e -> Bool)
-> (Filter e -> Filter e -> Bool) -> Eq (Filter e)
forall e. Filter e -> Filter e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Filter e -> Filter e -> Bool
$c/= :: forall e. Filter e -> Filter e -> Bool
== :: Filter e -> Filter e -> Bool
$c== :: forall e. Filter e -> Filter e -> Bool
Eq, Int -> Filter e -> ShowS
[Filter e] -> ShowS
Filter e -> String
(Int -> Filter e -> ShowS)
-> (Filter e -> String) -> ([Filter e] -> ShowS) -> Show (Filter e)
forall e. Int -> Filter e -> ShowS
forall e. [Filter e] -> ShowS
forall e. Filter e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Filter e] -> ShowS
$cshowList :: forall e. [Filter e] -> ShowS
show :: Filter e -> String
$cshow :: forall e. Filter e -> String
showsPrec :: Int -> Filter e -> ShowS
$cshowsPrec :: forall e. Int -> Filter e -> ShowS
Show, (forall x. Filter e -> Rep (Filter e) x)
-> (forall x. Rep (Filter e) x -> Filter e) -> Generic (Filter e)
forall x. Rep (Filter e) x -> Filter e
forall x. Filter e -> Rep (Filter e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (Filter e) x -> Filter e
forall e x. Filter e -> Rep (Filter e) x
$cto :: forall e x. Rep (Filter e) x -> Filter e
$cfrom :: forall e x. Filter e -> Rep (Filter e) x
Generic)
instance ToJSON (Filter e) where
    toJSON :: Filter e -> Value
toJSON Filter e
f = [Pair] -> Value
object [ Text
"address"   Text -> Maybe [Address] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Filter e -> Maybe [Address]
forall e. Filter e -> Maybe [Address]
filterAddress Filter e
f
                      , Text
"fromBlock" Text -> DefaultBlock -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Filter e -> DefaultBlock
forall e. Filter e -> DefaultBlock
filterFromBlock Filter e
f
                      , Text
"toBlock"   Text -> DefaultBlock -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Filter e -> DefaultBlock
forall e. Filter e -> DefaultBlock
filterToBlock Filter e
f
                      , Text
"topics"    Text -> Maybe [Maybe HexString] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Filter e -> Maybe [Maybe HexString]
forall e. Filter e -> Maybe [Maybe HexString]
filterTopics Filter e
f ]
instance Ord DefaultBlock where
    compare :: DefaultBlock -> DefaultBlock -> Ordering
compare DefaultBlock
Pending DefaultBlock
Pending                         = Ordering
EQ
    compare DefaultBlock
Latest DefaultBlock
Latest                           = Ordering
EQ
    compare DefaultBlock
Earliest DefaultBlock
Earliest                       = Ordering
EQ
    compare (BlockWithNumber Quantity
a) (BlockWithNumber Quantity
b) = Quantity -> Quantity -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Quantity
a Quantity
b
    compare DefaultBlock
_ DefaultBlock
Pending                               = Ordering
LT
    compare DefaultBlock
Pending DefaultBlock
Latest                          = Ordering
GT
    compare DefaultBlock
_ DefaultBlock
Latest                                = Ordering
LT
    compare DefaultBlock
Earliest DefaultBlock
_                              = Ordering
LT
    compare DefaultBlock
a DefaultBlock
b                                     = case DefaultBlock -> DefaultBlock -> Ordering
forall a. Ord a => a -> a -> Ordering
compare DefaultBlock
b DefaultBlock
a of
                                                        Ordering
LT -> Ordering
GT
                                                        Ordering
GT -> Ordering
LT
                                                        Ordering
EQ -> Ordering
EQ
data TxReceipt = TxReceipt
    { TxReceipt -> HexString
receiptTransactionHash   :: !HexString
    
    , TxReceipt -> Quantity
receiptTransactionIndex  :: !Quantity
    
    , TxReceipt -> Maybe HexString
receiptBlockHash         :: !(Maybe HexString)
    
    , TxReceipt -> Maybe Quantity
receiptBlockNumber       :: !(Maybe Quantity)
    
    , TxReceipt -> Quantity
receiptCumulativeGasUsed :: !Quantity
    
    , TxReceipt -> Quantity
receiptGasUsed           :: !Quantity
    
    , TxReceipt -> Maybe Address
receiptContractAddress   :: !(Maybe Address)
    
    , TxReceipt -> [Change]
receiptLogs              :: ![Change]
    
    , TxReceipt -> HexString
receiptLogsBloom         :: !HexString
    
    , TxReceipt -> Maybe Quantity
receiptStatus            :: !(Maybe Quantity)
    
    }
    deriving (Int -> TxReceipt -> ShowS
[TxReceipt] -> ShowS
TxReceipt -> String
(Int -> TxReceipt -> ShowS)
-> (TxReceipt -> String)
-> ([TxReceipt] -> ShowS)
-> Show TxReceipt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxReceipt] -> ShowS
$cshowList :: [TxReceipt] -> ShowS
show :: TxReceipt -> String
$cshow :: TxReceipt -> String
showsPrec :: Int -> TxReceipt -> ShowS
$cshowsPrec :: Int -> TxReceipt -> ShowS
Show, (forall x. TxReceipt -> Rep TxReceipt x)
-> (forall x. Rep TxReceipt x -> TxReceipt) -> Generic TxReceipt
forall x. Rep TxReceipt x -> TxReceipt
forall x. TxReceipt -> Rep TxReceipt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxReceipt x -> TxReceipt
$cfrom :: forall x. TxReceipt -> Rep TxReceipt x
Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = over _head toLower . drop 7 }) ''TxReceipt)
data Transaction = Transaction
    { Transaction -> HexString
txHash             :: !HexString
    
    , Transaction -> Quantity
txNonce            :: !Quantity
    
    , Transaction -> Maybe HexString
txBlockHash        :: !(Maybe HexString)
    
    , Transaction -> Maybe Quantity
txBlockNumber      :: !(Maybe Quantity)
    
    , Transaction -> Maybe Quantity
txTransactionIndex :: !(Maybe Quantity)
    
    , Transaction -> Address
txFrom             :: !Address
    
    , Transaction -> Maybe Address
txTo               :: !(Maybe Address)
    
    , Transaction -> Quantity
txValue            :: !Quantity
    
    , Transaction -> Quantity
txGasPrice         :: !Quantity
    
    , Transaction -> Quantity
txGas              :: !Quantity
    
    , Transaction -> HexString
txInput            :: !HexString
    
    }
    deriving (Transaction -> Transaction -> Bool
(Transaction -> Transaction -> Bool)
-> (Transaction -> Transaction -> Bool) -> Eq Transaction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transaction -> Transaction -> Bool
$c/= :: Transaction -> Transaction -> Bool
== :: Transaction -> Transaction -> Bool
$c== :: Transaction -> Transaction -> Bool
Eq, Int -> Transaction -> ShowS
[Transaction] -> ShowS
Transaction -> String
(Int -> Transaction -> ShowS)
-> (Transaction -> String)
-> ([Transaction] -> ShowS)
-> Show Transaction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transaction] -> ShowS
$cshowList :: [Transaction] -> ShowS
show :: Transaction -> String
$cshow :: Transaction -> String
showsPrec :: Int -> Transaction -> ShowS
$cshowsPrec :: Int -> Transaction -> ShowS
Show, (forall x. Transaction -> Rep Transaction x)
-> (forall x. Rep Transaction x -> Transaction)
-> Generic Transaction
forall x. Rep Transaction x -> Transaction
forall x. Transaction -> Rep Transaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Transaction x -> Transaction
$cfrom :: forall x. Transaction -> Rep Transaction x
Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = over _head toLower . drop 2 }) ''Transaction)
type Block = BlockT Transaction
data BlockT tx = Block
    { BlockT tx -> Maybe Quantity
blockNumber           :: !(Maybe Quantity)
    
    , BlockT tx -> Maybe HexString
blockHash             :: !(Maybe HexString)
    
    , BlockT tx -> HexString
blockParentHash       :: !HexString
    
    , BlockT tx -> Maybe HexString
blockNonce            :: !(Maybe HexString)
    
    , BlockT tx -> HexString
blockSha3Uncles       :: !HexString
    
    , BlockT tx -> Maybe HexString
blockLogsBloom        :: !(Maybe HexString)
    
    , BlockT tx -> HexString
blockTransactionsRoot :: !HexString
    
    , BlockT tx -> HexString
blockStateRoot        :: !HexString
    
    , BlockT tx -> Maybe HexString
blockReceiptsRoot     :: !(Maybe HexString)
    
    , BlockT tx -> Address
blockMiner            :: !Address
    
    , BlockT tx -> Quantity
blockDifficulty       :: !Quantity
    
    , BlockT tx -> Quantity
blockTotalDifficulty  :: !Quantity
    
    ,         :: !HexString
    
    , BlockT tx -> Quantity
blockSize             :: !Quantity
    
    , BlockT tx -> Quantity
blockGasLimit         :: !Quantity
    
    , BlockT tx -> Quantity
blockGasUsed          :: !Quantity
    
    , BlockT tx -> Quantity
blockTimestamp        :: !Quantity
    
    , BlockT tx -> [tx]
blockTransactions     :: ![tx]
    
    , BlockT tx -> [HexString]
blockUncles           :: ![HexString]
    
    }
    deriving (Int -> BlockT tx -> ShowS
[BlockT tx] -> ShowS
BlockT tx -> String
(Int -> BlockT tx -> ShowS)
-> (BlockT tx -> String)
-> ([BlockT tx] -> ShowS)
-> Show (BlockT tx)
forall tx. Show tx => Int -> BlockT tx -> ShowS
forall tx. Show tx => [BlockT tx] -> ShowS
forall tx. Show tx => BlockT tx -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockT tx] -> ShowS
$cshowList :: forall tx. Show tx => [BlockT tx] -> ShowS
show :: BlockT tx -> String
$cshow :: forall tx. Show tx => BlockT tx -> String
showsPrec :: Int -> BlockT tx -> ShowS
$cshowsPrec :: forall tx. Show tx => Int -> BlockT tx -> ShowS
Show, (forall x. BlockT tx -> Rep (BlockT tx) x)
-> (forall x. Rep (BlockT tx) x -> BlockT tx)
-> Generic (BlockT tx)
forall x. Rep (BlockT tx) x -> BlockT tx
forall x. BlockT tx -> Rep (BlockT tx) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall tx x. Rep (BlockT tx) x -> BlockT tx
forall tx x. BlockT tx -> Rep (BlockT tx) x
$cto :: forall tx x. Rep (BlockT tx) x -> BlockT tx
$cfrom :: forall tx x. BlockT tx -> Rep (BlockT tx) x
Generic)
$(deriveJSON (defaultOptions
    { fieldLabelModifier = over _head toLower . drop 5 }) ''BlockT)