web3-0.6.0.0: Ethereum API for Haskell

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

Network.Ethereum.Web3.Types

Description

Commonly used types and instances.

Synopsis

Documentation

newtype Web3 a b Source #

Any communication with Ethereum node wrapped with Web3 monad

Constructors

Web3 

Fields

Instances

Monad (Web3 a) Source # 

Methods

(>>=) :: Web3 a a -> (a -> Web3 a b) -> Web3 a b #

(>>) :: Web3 a a -> Web3 a b -> Web3 a b #

return :: a -> Web3 a a #

fail :: String -> Web3 a a #

Functor (Web3 a) Source # 

Methods

fmap :: (a -> b) -> Web3 a a -> Web3 a b #

(<$) :: a -> Web3 a b -> Web3 a a #

Applicative (Web3 a) Source # 

Methods

pure :: a -> Web3 a a #

(<*>) :: Web3 a (a -> b) -> Web3 a a -> Web3 a b #

(*>) :: Web3 a a -> Web3 a b -> Web3 a b #

(<*) :: Web3 a a -> Web3 a b -> Web3 a a #

MonadIO (Web3 a) Source # 

Methods

liftIO :: IO a -> Web3 a a #

data Web3Error Source #

Some peace of error response

Constructors

JsonRpcFail !RpcError

JSON-RPC communication error

ParserFail !String

Error in parser state

UserFail !String

Common head for user errors

data RpcError Source #

JSON-RPC error message

Constructors

RpcError 

Fields

data Filter Source #

Low-level event filter data structure

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

Constructors

Call 

type TxHash = Text Source #

Transaction hash text string

data Transaction Source #

Transaction information

Constructors

Transaction 

Fields

  • txHash :: !TxHash

    DATA, 32 Bytes - hash of the transaction.

  • txNonce :: !Text

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

  • txBlockHash :: !Text

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

  • txBlockNumber :: !Text

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

  • txTransactionIndex :: !Text

    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 :: !Text

    QUANTITY - value transferred in Wei.

  • txGasPrice :: !Text

    QUANTITY - gas price provided by the sender in Wei.

  • txGas :: !Text

    QUANTITY - gas provided by the sender.

  • txInput :: !Text

    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.6.0.0-45FzcRUPCX9CwPtRdKwGnS" False) (C1 (MetaCons "Block" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "blockNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "blockHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "blockParentHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "blockNonce") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "blockSha3Uncles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "blockLogsBloom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "blockTransactionsRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "blockStateRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "blockReceiptRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "blockMiner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Address)) (S1 (MetaSel (Just Symbol "blockDifficulty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "blockTotalDifficulty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "blockExtraData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "blockSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "blockGasLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "blockGasUsed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "blockTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "blockTransactions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Transaction])) (S1 (MetaSel (Just Symbol "blockUncles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))))))))