web3-0.6.0.0: Ethereum API for Haskell

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

Network.Ethereum.Web3

Contents

Description

An Ethereum node offers a RPC interface. This interface gives Ðapp’s access to the Ethereum blockchain and functionality that the node provides, such as compiling smart contract code. It uses a subset of the JSON-RPC 2.0 specification (no support for notifications or named parameters) as serialisation protocol and is available over HTTP and IPC (unix domain sockets on linux/OSX and named pipe’s on Windows).

Web3 Haskell library currently use JSON-RPC over HTTP to access node functionality.

Synopsis

Web3 monad and service provider

data Web3 a b Source #

Any communication with Ethereum node wrapped with Web3 monad

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 #

class Provider a where Source #

Ethereum node service provider

Minimal complete definition

rpcUri

Methods

rpcUri :: Web3 a String Source #

JSON-RPC provider URI, default: localhost:8545

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

forkWeb3 :: Web3 a () -> Web3 a ThreadId Source #

Fork Web3 with the same Provider

runWeb3' :: MonadIO m => Web3 a b -> m (Either Web3Error b) Source #

Web3 monad runner

runWeb3 :: MonadIO m => Web3 DefaultProvider b -> m (Either Web3Error b) Source #

Web3 runner for default provider

Contract actions

data EventAction Source #

Event callback control response

Constructors

ContinueEvent

Continue to listen events

TerminateEvent

Terminate event listener

class ABIEncoding a => Event a where Source #

Contract event listener

Minimal complete definition

eventFilter

Methods

eventFilter :: a -> Address -> Filter Source #

Event filter structure used by low-level subscription methods

event :: Provider p => Address -> (a -> ReaderT Change (Web3 p) EventAction) -> Web3 p ThreadId Source #

Start an event listener for given contract Address and callback

class ABIEncoding a => Method a where Source #

Contract method caller

Methods

sendTx :: (Provider p, Unit b) => Address -> b -> a -> Web3 p TxHash Source #

Send a transaction for given contract Address, value and input data

call :: (Provider p, ABIEncoding b) => Address -> DefaultBlock -> a -> Web3 p b Source #

Constant call given contract Address in mode and given input data

Instances

data NoMethod Source #

Dummy method for sending transaction without method call

Constructors

NoMethod 

nopay :: Wei Source #

Zero value is used to send transaction without money

Ethereum data types

newtype BytesN n Source #

Fixed length byte array

Constructors

BytesN 

Fields

Instances

Eq (BytesN n) Source # 

Methods

(==) :: BytesN n -> BytesN n -> Bool #

(/=) :: BytesN n -> BytesN n -> Bool #

Ord (BytesN n) Source # 

Methods

compare :: BytesN n -> BytesN n -> Ordering #

(<) :: BytesN n -> BytesN n -> Bool #

(<=) :: BytesN n -> BytesN n -> Bool #

(>) :: BytesN n -> BytesN n -> Bool #

(>=) :: BytesN n -> BytesN n -> Bool #

max :: BytesN n -> BytesN n -> BytesN n #

min :: BytesN n -> BytesN n -> BytesN n #

KnownNat n => Show (BytesN n) Source # 

Methods

showsPrec :: Int -> BytesN n -> ShowS #

show :: BytesN n -> String #

showList :: [BytesN n] -> ShowS #

KnownNat n => ABIEncoding (BytesN n) Source # 

data Address Source #

Ethereum account address

Instances

Eq Address Source # 

Methods

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

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

Ord Address Source # 
Show Address Source # 
IsString Address Source # 

Methods

fromString :: String -> Address #

Generic Address Source # 

Associated Types

type Rep Address :: * -> * #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

ToJSON Address Source # 
FromJSON Address Source # 
ABIEncoding Address Source # 
type Rep Address Source # 
type Rep Address = D1 (MetaData "Address" "Network.Ethereum.Web3.Address" "web3-0.6.0.0-45FzcRUPCX9CwPtRdKwGnS" True) (C1 (MetaCons "Address" PrefixI True) (S1 (MetaSel (Just Symbol "unAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

Ethereum unit conversion utils