web3-0.7.0.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

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.0.0-3hRETfypdz0IWrclyn4h7y" True) (C1 * (MetaCons "Quantity" PrefixI True) (S1 * (MetaSel (Just Symbol "unQuantity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Integer)))

newtype BlockNumber Source #

Constructors

BlockNumber Integer 

Instances

Eq BlockNumber Source # 
Num BlockNumber Source # 
Ord BlockNumber Source # 
Read BlockNumber Source # 
Show BlockNumber Source # 
Generic BlockNumber Source # 

Associated Types

type Rep BlockNumber :: * -> * #

ToJSON BlockNumber Source # 
FromJSON BlockNumber Source # 
type Rep BlockNumber Source # 
type Rep BlockNumber = D1 * (MetaData "BlockNumber" "Network.Ethereum.Web3.Types" "web3-0.7.0.0-3hRETfypdz0IWrclyn4h7y" True) (C1 * (MetaCons "BlockNumber" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Integer)))

data Change Source #

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

Instances

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

data Filter e Source #

Low-level event filter data structure

Instances

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.0.0-3hRETfypdz0IWrclyn4h7y" False) (C1 * (MetaCons "Filter" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "filterAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Address))) (S1 * (MetaSel (Just Symbol "filterTopics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Maybe Bytes])))) ((:*:) * (S1 * (MetaSel (Just Symbol "filterFromBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DefaultBlock)) (S1 * (MetaSel (Just Symbol "filterToBlock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * DefaultBlock)))))

data Transaction Source #

Transaction information

Constructors

Transaction 

Fields

  • txHash :: !Bytes

    DATA, 32 Bytes - hash of the transaction.

  • txNonce :: !Quantity

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

  • txBlockHash :: !Bytes

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

  • txBlockNumber :: !BlockNumber

    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

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.0.0-3hRETfypdz0IWrclyn4h7y" False) (C1 * (MetaCons "Block" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "blockNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * BlockNumber)) (S1 * (MetaSel (Just Symbol "blockHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "blockParentHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "blockNonce") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bytes))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "blockSha3Uncles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "blockLogsBloom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes))) ((:*:) * (S1 * (MetaSel (Just Symbol "blockTransactionsRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes)) ((:*:) * (S1 * (MetaSel (Just Symbol "blockStateRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes)) (S1 * (MetaSel (Just Symbol "blockReceiptRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bytes))))))) ((:*:) * ((:*:) * ((:*:) * (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 * [Bytes]))))))))