web3-0.7.0.0: Ethereum API for Haskell

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

Network.Ethereum.Web3.Provider

Description

Web3 service provider.

Synopsis

Documentation

newtype Web3 a Source #

Any communication with Ethereum node wrapped with Web3 monad

Constructors

Web3 

Instances

Monad Web3 Source # 

Methods

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

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

return :: a -> Web3 a #

fail :: String -> Web3 a #

Functor Web3 Source # 

Methods

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

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

Applicative Web3 Source # 

Methods

pure :: a -> Web3 a #

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

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

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

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

MonadIO Web3 Source # 

Methods

liftIO :: IO a -> Web3 a #

MonadThrow Web3 Source # 

Methods

throwM :: Exception e => e -> Web3 a #

FromJSON a => Remote Web3 (Web3 a) Source # 

Methods

remote_ :: ([Value] -> Web3 ByteString) -> Web3 a

MonadReader (ServerUri, Manager) Web3 Source # 

Methods

ask :: Web3 (ServerUri, Manager) #

local :: ((ServerUri, Manager) -> (ServerUri, Manager)) -> Web3 a -> Web3 a #

reader :: ((ServerUri, Manager) -> a) -> Web3 a #

data Web3Error Source #

Some peace of error response

Constructors

JsonRpcFail !String

JSON-RPC communication error

ParserFail !String

Error in parser state

UserFail !String

Common head for user errors

data Provider Source #

Web3 Provider

Constructors

HttpProvider ServerUri 

Instances

Eq Provider Source # 
Show Provider Source # 
Generic Provider Source # 

Associated Types

type Rep Provider :: * -> * #

Methods

from :: Provider -> Rep Provider x #

to :: Rep Provider x -> Provider #

Default Provider Source # 

Methods

def :: Provider #

type Rep Provider Source # 
type Rep Provider = D1 * (MetaData "Provider" "Network.Ethereum.Web3.Provider" "web3-0.7.0.0-3hRETfypdz0IWrclyn4h7y" False) (C1 * (MetaCons "HttpProvider" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ServerUri)))

runWeb3With :: MonadIO m => Manager -> Provider -> Web3 a -> m (Either Web3Error a) Source #

Web3 monad runner, using the supplied Manager

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

Web3 monad runner

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

Web3 runner for default provider

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

Fork Web3 with the same Provider