web3-0.7.2.0: Ethereum API for Haskell

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

Network.Ethereum.Web3.Types

Description

Ethereum generic JSON-RPC types.

Synopsis

Documentation

type Hash = BytesN 32 Source #

32 byte type synonym for transaction and block hashes.

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 # 
Eq Quantity Source # 
Fractional Quantity Source # 
Num Quantity Source # 
Ord Quantity Source # 
Read Quantity Source # 
Real Quantity Source # 
Show Quantity Source # 
IsString Quantity Source # 
Generic Quantity Source # 

Associated Types

type Rep Quantity :: * -> * #

Methods

from :: Quantity -> Rep Quantity x #

to :: Rep Quantity x -> Quantity #

ToJSON Quantity Source # 
FromJSON Quantity Source # 
UnitSpec Quantity Source # 

Methods

divider :: RealFrac b => proxy Quantity -> b Source #

name :: proxy Quantity -> Text Source #

Unit Quantity Source # 
type Rep Quantity Source # 
type Rep Quantity = D1 * (MetaData "Quantity" "Network.Ethereum.Web3.Types" "web3-0.7.2.0-LjNsc1nEIVHITkoHXqMDYx" True) (C1 * (MetaCons "Quantity" PrefixI True) (S1 * (MetaSel (Just Symbol "unQuantity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Integer)))

data SyncActive Source #

An object with sync status data.

Constructors

SyncActive 

Fields

data SyncingState Source #

Sync state pulled by low-level call eth_syncing.

data Change Source #

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

Constructors

Change 

Fields

  • changeLogIndex :: !Quantity

    QUANTITY - integer of the log index position in the block. null when its pending log.

  • changeTransactionIndex :: !Quantity

    QUANTITY - integer of the transactions index position log was created from. null when its pending log.

  • changeTransactionHash :: !Hash

    DATA, 32 Bytes - hash of the transactions this log was created from. null when its pending log.

  • changeBlockHash :: !Hash

    DATA, 32 Bytes - hash of the block where this log was in. null when its pending. null when its pending log.

  • changeBlockNumber :: !Quantity

    QUANTITY - the block number where this log was in. null when its pending. null when its pending log.

  • changeAddress :: !Address

    DATA, 20 Bytes - address from which this log originated.

  • changeData :: !Bytes

    DATA - contains one or more 32 Bytes non-indexed arguments of the log.

  • changeTopics :: ![BytesN 32]

    Array of DATA - Array of 0 to 4 32 Bytes DATA of indexed log arguments. (In solidity: The first topic is the hash of the signature of the event (e.g. Deposit(address, bytes32, uint256)), except you declared the event with the anonymous specifier.)

Instances

Eq Change Source # 

Methods

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

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

Show Change Source # 
Generic Change Source # 

Associated Types

type Rep Change :: * -> * #

Methods

from :: Change -> Rep Change x #

to :: Rep Change x -> Change #

ToJSON Change Source # 
FromJSON Change Source # 
type Rep Change Source # 

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 Bytes)

    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 # 

Methods

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

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

Show Call Source # 

Methods

showsPrec :: Int -> Call -> ShowS #

show :: Call -> String #

showList :: [Call] -> ShowS #

Generic Call Source # 

Associated Types

type Rep Call :: * -> * #

Methods

from :: Call -> Rep Call x #

to :: Rep Call x -> Call #

ToJSON Call Source # 
FromJSON Call Source # 
Default Call Source # 

Methods

def :: Call #

type Rep Call Source # 

data DefaultBlock Source #

The state of blockchain for contract call.

Instances

Eq DefaultBlock Source # 
Ord DefaultBlock Source # 
Show DefaultBlock Source # 
Generic DefaultBlock Source # 

Associated Types

type Rep DefaultBlock :: * -> * #

ToJSON DefaultBlock Source # 
type Rep DefaultBlock Source # 
type Rep DefaultBlock = D1 * (MetaData "DefaultBlock" "Network.Ethereum.Web3.Types" "web3-0.7.2.0-LjNsc1nEIVHITkoHXqMDYx" False) ((:+:) * ((:+:) * (C1 * (MetaCons "BlockWithNumber" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Quantity))) (C1 * (MetaCons "Earliest" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Latest" PrefixI False) (U1 *)) (C1 * (MetaCons "Pending" PrefixI False) (U1 *))))

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 (BytesN 32)])

    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. Topics are order-dependent. A transaction with a log with topics [A, B] will be matched by the following topic filters: * [] "anything" * [A] "A in first position (and anything after)" * [null, B] "anything in first position AND B in second position (and anything after)" * [A, B] "A in first position AND B in second position (and anything after)" * [[A, B], [A, B]] "(A OR B) in first position AND (A OR B) in second position (and anything after)"

Instances

Eq (Filter e) Source # 

Methods

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

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

Show (Filter e) Source # 

Methods

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

show :: Filter e -> String #

showList :: [Filter e] -> ShowS #

Generic (Filter e) Source # 

Associated Types

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

Methods

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

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

ToJSON (Filter e) Source # 
type Rep (Filter e) Source # 
type Rep (Filter e) = D1 * (MetaData "Filter" "Network.Ethereum.Web3.Types" "web3-0.7.2.0-LjNsc1nEIVHITkoHXqMDYx" False) (C1 * (MetaCons "Filter" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "filterAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Address]))) (S1 * (MetaSel (Just Symbol "filterFromBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DefaultBlock))) ((:*:) * (S1 * (MetaSel (Just Symbol "filterToBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DefaultBlock)) (S1 * (MetaSel (Just Symbol "filterTopics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Maybe (BytesN 32)]))))))

data TxReceipt Source #

The Receipt of a Transaction

Constructors

TxReceipt 

Fields

Instances

Show TxReceipt Source # 
Generic TxReceipt Source # 

Associated Types

type Rep TxReceipt :: * -> * #

ToJSON TxReceipt Source # 
FromJSON TxReceipt Source # 
type Rep TxReceipt Source # 

data Transaction Source #

Transaction information.

Constructors

Transaction 

Fields

  • txHash :: !Hash

    DATA, 32 Bytes - hash of the transaction.

  • txNonce :: !Quantity

    QUANTITY - the number of transactions made by the sender prior to this one.

  • txBlockHash :: !Hash

    DATA, 32 Bytes - hash of the block where this transaction was in. null when its pending.

  • txBlockNumber :: !Quantity

    QUANTITY - block number where this transaction was in. null when its pending.

  • txTransactionIndex :: !Quantity

    QUANTITY - integer of the transactions index position in the block. null when its pending.

  • txFrom :: !Address

    DATA, 20 Bytes - address of the sender.

  • txTo :: !(Maybe Address)

    DATA, 20 Bytes - address of the receiver. null when its a contract creation transaction.

  • txValue :: !Quantity

    QUANTITY - value transferred in Wei.

  • txGasPrice :: !Quantity

    QUANTITY - gas price provided by the sender in Wei.

  • txGas :: !Quantity

    QUANTITY - gas provided by the sender.

  • txInput :: !Bytes

    DATA - the data send along with the transaction.

Instances

Eq Transaction Source # 
Show Transaction Source # 
Generic Transaction Source # 

Associated Types

type Rep Transaction :: * -> * #

ToJSON Transaction Source # 
FromJSON Transaction Source # 
type Rep Transaction Source # 

data Block Source #

Block information.

Constructors

Block 

Fields

Instances

Show Block Source # 

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 

Associated Types

type Rep Block :: * -> * #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

ToJSON Block Source # 
FromJSON Block Source # 
type Rep Block Source # 
type Rep Block = D1 * (MetaData "Block" "Network.Ethereum.Web3.Types" "web3-0.7.2.0-LjNsc1nEIVHITkoHXqMDYx" False) (C1 * (MetaCons "Block" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "blockNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Quantity)) (S1 * (MetaSel (Just Symbol "blockHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Hash))) ((:*:) * (S1 * (MetaSel (Just Symbol "blockParentHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Hash)) (S1 * (MetaSel (Just Symbol "blockNonce") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bytes))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "blockSha3Uncles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (BytesN 32))) (S1 * (MetaSel (Just Symbol "blockLogsBloom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "blockTransactionsRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (BytesN 32))) ((:*:) * (S1 * (MetaSel (Just Symbol "blockStateRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (BytesN 32))) (S1 * (MetaSel (Just Symbol "blockReceiptRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (BytesN 32)))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "blockMiner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Address)) (S1 * (MetaSel (Just Symbol "blockDifficulty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Quantity))) ((:*:) * (S1 * (MetaSel (Just Symbol "blockTotalDifficulty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Quantity)) ((:*:) * (S1 * (MetaSel (Just Symbol "blockExtraData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "blockSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Quantity))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "blockGasLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Quantity)) (S1 * (MetaSel (Just Symbol "blockGasUsed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Quantity))) ((:*:) * (S1 * (MetaSel (Just Symbol "blockTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Quantity)) ((:*:) * (S1 * (MetaSel (Just Symbol "blockTransactions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Transaction])) (S1 * (MetaSel (Just Symbol "blockUncles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Hash]))))))))