web3-0.9.1.0: Web3 API for Haskell.

CopyrightAlexander Krupenkin 2016-2018
LicenseBSD3
Maintainermail@akru.me
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Network.Ethereum.Api.Types

Description

Ethereum generic JSON-RPC types.

Synopsis

Documentation

newtype Quantity Source #

Should be viewed as type to representing QUANTITY in Web3 JSON RPC docs

When encoding QUANTITIES (integers, numbers): encode as hex, prefix with "0x", the most compact representation (slight exception: zero should be represented as "0x0"). Examples:

0x41 (65 in decimal) 0x400 (1024 in decimal) WRONG: 0x (should always have at least one digit - zero is "0x0") WRONG: 0x0400 (no leading zeroes allowed) WRONG: ff (must be prefixed 0x)

Constructors

Quantity 

Fields

Instances
Enum Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Eq Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Integral Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Num Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Ord Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Real Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Show Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

IsString Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Generic Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep Quantity :: Type -> Type #

Methods

from :: Quantity -> Rep Quantity x #

to :: Rep Quantity x -> Quantity #

ToJSON Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

FromJSON Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep Quantity Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep Quantity = D1 (MetaData "Quantity" "Network.Ethereum.Api.Types" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" True) (C1 (MetaCons "Quantity" PrefixI True) (S1 (MetaSel (Just "unQuantity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

data SyncActive Source #

An object with sync status data.

Constructors

SyncActive 

Fields

Instances
Eq SyncActive Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Show SyncActive Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Generic SyncActive Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep SyncActive :: Type -> Type #

ToJSON SyncActive Source # 
Instance details

Defined in Network.Ethereum.Api.Types

FromJSON SyncActive Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep SyncActive Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep SyncActive = D1 (MetaData "SyncActive" "Network.Ethereum.Api.Types" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" False) (C1 (MetaCons "SyncActive" PrefixI True) (S1 (MetaSel (Just "syncStartingBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity) :*: (S1 (MetaSel (Just "syncCurrentBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity) :*: S1 (MetaSel (Just "syncHighestBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity))))

data SyncingState Source #

Sync state pulled by low-level call eth_syncing.

Instances
Eq SyncingState Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Show SyncingState Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Generic SyncingState Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep SyncingState :: Type -> Type #

FromJSON SyncingState Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep SyncingState Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep SyncingState = D1 (MetaData "SyncingState" "Network.Ethereum.Api.Types" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" False) (C1 (MetaCons "Syncing" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SyncActive)) :+: C1 (MetaCons "NotSyncing" PrefixI False) (U1 :: Type -> Type))

data Change Source #

Changes pulled by low-level call eth_getFilterChanges, eth_getLogs, and eth_getFilterLogs

Constructors

Change 

Fields

Instances
Eq Change Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Methods

(==) :: Change -> Change -> Bool #

(/=) :: Change -> Change -> Bool #

Show Change Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Generic Change Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep Change :: Type -> Type #

Methods

from :: Change -> Rep Change x #

to :: Rep Change x -> Change #

ToJSON Change Source # 
Instance details

Defined in Network.Ethereum.Api.Types

FromJSON Change Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep Change Source # 
Instance details

Defined in Network.Ethereum.Api.Types

data Call Source #

The contract call params.

Constructors

Call 

Fields

  • callFrom :: !(Maybe Address)

    DATA, 20 Bytes - The address the transaction is send from.

  • callTo :: !(Maybe Address)

    DATA, 20 Bytes - (optional when creating new contract) The address the transaction is directed to.

  • callGas :: !(Maybe Quantity)

    QUANTITY - (optional, default: 3000000) Integer of the gas provided for the transaction execution. It will return unused gas.

  • callGasPrice :: !(Maybe Quantity)

    QUANTITY - (optional, default: To-Be-Determined) Integer of the gasPrice used for each paid gas.

  • callValue :: !(Maybe Quantity)

    QUANTITY - (optional) Integer of the value sent with this transaction.

  • callData :: !(Maybe HexString)

    DATA - The compiled code of a contract OR the hash of the invoked method signature and encoded parameters.

  • callNonce :: !(Maybe Quantity)

    QUANTITY - (optional) Integer of a nonce. This allows to overwrite your own pending transactions that use the same nonce.

Instances
Eq Call Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Methods

(==) :: Call -> Call -> Bool #

(/=) :: Call -> Call -> Bool #

Show Call Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Methods

showsPrec :: Int -> Call -> ShowS #

show :: Call -> String #

showList :: [Call] -> ShowS #

Generic Call Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep Call :: Type -> Type #

Methods

from :: Call -> Rep Call x #

to :: Rep Call x -> Call #

ToJSON Call Source # 
Instance details

Defined in Network.Ethereum.Api.Types

FromJSON Call Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Default Call Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Methods

def :: Call #

type Rep Call Source # 
Instance details

Defined in Network.Ethereum.Api.Types

data DefaultBlock Source #

The state of blockchain for contract call.

Instances
Eq DefaultBlock Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Ord DefaultBlock Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Show DefaultBlock Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Generic DefaultBlock Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep DefaultBlock :: Type -> Type #

ToJSON DefaultBlock Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep DefaultBlock Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep DefaultBlock = D1 (MetaData "DefaultBlock" "Network.Ethereum.Api.Types" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" False) ((C1 (MetaCons "BlockWithNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Quantity)) :+: C1 (MetaCons "Earliest" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Latest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Pending" PrefixI False) (U1 :: Type -> Type)))

data Filter e Source #

Low-level event filter data structure.

Constructors

Filter 

Fields

  • filterAddress :: !(Maybe [Address])

    DATA|Array, 20 Bytes - (optional) Contract address or a list of addresses from which logs should originate.

  • filterFromBlock :: !DefaultBlock

    QUANTITY|TAG - (optional, default: "latest") Integer block number, or "latest" for the last mined block or "pending", "earliest" for not yet mined transactions.

  • filterToBlock :: !DefaultBlock

    QUANTITY|TAG - (optional, default: "latest") Integer block number, or "latest" for the last mined block or "pending", "earliest" for not yet mined transactions.

  • filterTopics :: !(Maybe [Maybe HexString])

    Array of DATA, - (optional) Array of 32 Bytes DATA topics. Topics are order-dependent. Each topic can also be an array of DATA with "or" options.

Instances
Eq (Filter e) Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Methods

(==) :: Filter e -> Filter e -> Bool #

(/=) :: Filter e -> Filter e -> Bool #

Show (Filter e) Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Methods

showsPrec :: Int -> Filter e -> ShowS #

show :: Filter e -> String #

showList :: [Filter e] -> ShowS #

Generic (Filter e) Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep (Filter e) :: Type -> Type #

Methods

from :: Filter e -> Rep (Filter e) x #

to :: Rep (Filter e) x -> Filter e #

ToJSON (Filter e) Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Default (Filter Transfer) Source # 
Instance details

Defined in Network.Ethereum.Ens.Registry

Methods

def :: Filter Transfer #

Default (Filter NewTTL) Source # 
Instance details

Defined in Network.Ethereum.Ens.Registry

Methods

def :: Filter NewTTL #

Default (Filter NewResolver) Source # 
Instance details

Defined in Network.Ethereum.Ens.Registry

Default (Filter NewOwner) Source # 
Instance details

Defined in Network.Ethereum.Ens.Registry

Methods

def :: Filter NewOwner #

Default (Filter PubkeyChanged) Source # 
Instance details

Defined in Network.Ethereum.Ens.PublicResolver

Default (Filter NameChanged) Source # 
Instance details

Defined in Network.Ethereum.Ens.PublicResolver

Default (Filter ContentChanged) Source # 
Instance details

Defined in Network.Ethereum.Ens.PublicResolver

Default (Filter AddrChanged) Source # 
Instance details

Defined in Network.Ethereum.Ens.PublicResolver

Default (Filter ABIChanged) Source # 
Instance details

Defined in Network.Ethereum.Ens.PublicResolver

type Rep (Filter e) Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep (Filter e) = D1 (MetaData "Filter" "Network.Ethereum.Api.Types" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" False) (C1 (MetaCons "Filter" PrefixI True) ((S1 (MetaSel (Just "filterAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Address])) :*: S1 (MetaSel (Just "filterFromBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DefaultBlock)) :*: (S1 (MetaSel (Just "filterToBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DefaultBlock) :*: S1 (MetaSel (Just "filterTopics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Maybe HexString])))))

data TxReceipt Source #

The Receipt of a Transaction

Constructors

TxReceipt 

Fields

Instances
Show TxReceipt Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Generic TxReceipt Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep TxReceipt :: Type -> Type #

ToJSON TxReceipt Source # 
Instance details

Defined in Network.Ethereum.Api.Types

FromJSON TxReceipt Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep TxReceipt Source # 
Instance details

Defined in Network.Ethereum.Api.Types

data Transaction Source #

Transaction information.

Constructors

Transaction 

Fields

Instances
Eq Transaction Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Show Transaction Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Generic Transaction Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep Transaction :: Type -> Type #

ToJSON Transaction Source # 
Instance details

Defined in Network.Ethereum.Api.Types

FromJSON Transaction Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep Transaction Source # 
Instance details

Defined in Network.Ethereum.Api.Types

data Block Source #

Block information.

Constructors

Block 

Fields

Instances
Show Block Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 
Instance details

Defined in Network.Ethereum.Api.Types

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

ToJSON Block Source # 
Instance details

Defined in Network.Ethereum.Api.Types

FromJSON Block Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep Block Source # 
Instance details

Defined in Network.Ethereum.Api.Types

type Rep Block = D1 (MetaData "Block" "Network.Ethereum.Api.Types" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" False) (C1 (MetaCons "Block" PrefixI True) ((((S1 (MetaSel (Just "blockNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Quantity)) :*: S1 (MetaSel (Just "blockHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HexString))) :*: (S1 (MetaSel (Just "blockParentHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HexString) :*: S1 (MetaSel (Just "blockNonce") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HexString)))) :*: ((S1 (MetaSel (Just "blockSha3Uncles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HexString) :*: S1 (MetaSel (Just "blockLogsBloom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HexString))) :*: (S1 (MetaSel (Just "blockTransactionsRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HexString) :*: (S1 (MetaSel (Just "blockStateRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HexString) :*: S1 (MetaSel (Just "blockReceiptRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HexString)))))) :*: (((S1 (MetaSel (Just "blockMiner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Address) :*: S1 (MetaSel (Just "blockDifficulty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity)) :*: (S1 (MetaSel (Just "blockTotalDifficulty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity) :*: (S1 (MetaSel (Just "blockExtraData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HexString) :*: S1 (MetaSel (Just "blockSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity)))) :*: ((S1 (MetaSel (Just "blockGasLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity) :*: S1 (MetaSel (Just "blockGasUsed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity)) :*: (S1 (MetaSel (Just "blockTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Quantity) :*: (S1 (MetaSel (Just "blockTransactions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Transaction]) :*: S1 (MetaSel (Just "blockUncles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [HexString])))))))