web3-0.7.0.0: Ethereum API for Haskell

CopyrightAlexander Krupenkin 2016-2018
LicenseBSD3
Maintainermail@akru.me
Stabilityexperimental
Portabilityunportable
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

Monad as base of any Ethereum node communication

data Web3 a Source #

Any communication with Ethereum node wrapped with Web3 monad

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 #

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

Web3 runner for default provider

Basic transaction sending

sendTx Source #

Arguments

:: Method a 
=> Call

Call configuration

-> a

method data

-> Web3 TxHash 

sendTx is used to submit a state changing transaction.

data Call Source #

The contract call params

Basic event listening

data EventAction Source #

Event callback control response

Constructors

ContinueEvent

Continue to listen events

TerminateEvent

Terminate event listener

event :: DecodeEvent i ni e => Filter e -> (e -> ReaderT Change Web3 EventAction) -> Web3 (Async ()) Source #

Run 'event\'' one block at a time.

event' :: DecodeEvent i ni e => Filter e -> (e -> ReaderT Change Web3 EventAction) -> Web3 () Source #

Same as event, but does not immediately spawn a new thread.

Primitive data types

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 # 
Generic Address Source # 

Associated Types

type Code Address :: [[*]] #

ABIGet Address Source # 
ABIPut Address Source # 
ABIType Address Source # 
type Rep Address Source # 
type Rep Address = D1 * (MetaData "Address" "Network.Ethereum.ABI.Prim.Address" "web3-0.7.0.0-3hRETfypdz0IWrclyn4h7y" True) (C1 * (MetaCons "Address" PrefixI True) (S1 * (MetaSel (Just Symbol "unAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (UIntN 160))))
type Code Address Source # 

data Bytes :: * #

Simplest Byte Array

Instances

Eq Bytes 

Methods

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

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

Ord Bytes 

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

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

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

Show Bytes 

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Semigroup Bytes 

Methods

(<>) :: Bytes -> Bytes -> Bytes #

sconcat :: NonEmpty Bytes -> Bytes #

stimes :: Integral b => b -> Bytes -> Bytes #

Monoid Bytes 

Methods

mempty :: Bytes #

mappend :: Bytes -> Bytes -> Bytes #

mconcat :: [Bytes] -> Bytes #

NormalForm Bytes 

Methods

toNormalForm :: Bytes -> () #

NFData Bytes 

Methods

rnf :: Bytes -> () #

ByteArray Bytes 

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, Bytes) #

ByteArrayAccess Bytes 

Methods

length :: Bytes -> Int #

withByteArray :: Bytes -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Bytes -> Ptr p -> IO () #

data IntN (n :: Nat) Source #

Instances

(KnownNat n, (<=) n 256) => Bounded (IntN n) Source # 

Methods

minBound :: IntN n #

maxBound :: IntN n #

Enum (IntN n) Source # 

Methods

succ :: IntN n -> IntN n #

pred :: IntN n -> IntN n #

toEnum :: Int -> IntN n #

fromEnum :: IntN n -> Int #

enumFrom :: IntN n -> [IntN n] #

enumFromThen :: IntN n -> IntN n -> [IntN n] #

enumFromTo :: IntN n -> IntN n -> [IntN n] #

enumFromThenTo :: IntN n -> IntN n -> IntN n -> [IntN n] #

Eq (IntN n) Source # 

Methods

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

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

(KnownNat n, (<=) n 256) => Integral (IntN n) Source # 

Methods

quot :: IntN n -> IntN n -> IntN n #

rem :: IntN n -> IntN n -> IntN n #

div :: IntN n -> IntN n -> IntN n #

mod :: IntN n -> IntN n -> IntN n #

quotRem :: IntN n -> IntN n -> (IntN n, IntN n) #

divMod :: IntN n -> IntN n -> (IntN n, IntN n) #

toInteger :: IntN n -> Integer #

(KnownNat n, (<=) n 256) => Num (IntN n) Source # 

Methods

(+) :: IntN n -> IntN n -> IntN n #

(-) :: IntN n -> IntN n -> IntN n #

(*) :: IntN n -> IntN n -> IntN n #

negate :: IntN n -> IntN n #

abs :: IntN n -> IntN n #

signum :: IntN n -> IntN n #

fromInteger :: Integer -> IntN n #

Ord (IntN n) Source # 

Methods

compare :: IntN n -> IntN n -> Ordering #

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

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

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

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

max :: IntN n -> IntN n -> IntN n #

min :: IntN n -> IntN n -> IntN n #

(KnownNat n, (<=) n 256) => Real (IntN n) Source # 

Methods

toRational :: IntN n -> Rational #

(KnownNat n, (<=) n 256) => Show (IntN n) Source # 

Methods

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

show :: IntN n -> String #

showList :: [IntN n] -> ShowS #

Generic (IntN n) Source # 

Associated Types

type Rep (IntN n) :: * -> * #

Methods

from :: IntN n -> Rep (IntN n) x #

to :: Rep (IntN n) x -> IntN n #

Bits (IntN n) Source # 

Methods

(.&.) :: IntN n -> IntN n -> IntN n #

(.|.) :: IntN n -> IntN n -> IntN n #

xor :: IntN n -> IntN n -> IntN n #

complement :: IntN n -> IntN n #

shift :: IntN n -> Int -> IntN n #

rotate :: IntN n -> Int -> IntN n #

zeroBits :: IntN n #

bit :: Int -> IntN n #

setBit :: IntN n -> Int -> IntN n #

clearBit :: IntN n -> Int -> IntN n #

complementBit :: IntN n -> Int -> IntN n #

testBit :: IntN n -> Int -> Bool #

bitSizeMaybe :: IntN n -> Maybe Int #

bitSize :: IntN n -> Int #

isSigned :: IntN n -> Bool #

shiftL :: IntN n -> Int -> IntN n #

unsafeShiftL :: IntN n -> Int -> IntN n #

shiftR :: IntN n -> Int -> IntN n #

unsafeShiftR :: IntN n -> Int -> IntN n #

rotateL :: IntN n -> Int -> IntN n #

rotateR :: IntN n -> Int -> IntN n #

popCount :: IntN n -> Int #

(<=) n 256 => ABIGet (IntN n) Source # 

Methods

abiGet :: Get (IntN n) Source #

(<=) n 256 => ABIPut (IntN n) Source # 

Methods

abiPut :: Putter (IntN n) Source #

(<=) n 256 => ABIType (IntN n) Source # 

Methods

isDynamic :: Proxy * (IntN n) -> Bool Source #

type Rep (IntN n) Source # 
type Rep (IntN n) = D1 * (MetaData "IntN" "Network.Ethereum.ABI.Prim.Int" "web3-0.7.0.0-3hRETfypdz0IWrclyn4h7y" True) (C1 * (MetaCons "IntN" PrefixI True) (S1 * (MetaSel (Just Symbol "unIntN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word256)))

data UIntN (n :: Nat) Source #

Instances

(KnownNat n, (<=) n 256) => Bounded (UIntN n) Source # 

Methods

minBound :: UIntN n #

maxBound :: UIntN n #

Enum (UIntN n) Source # 

Methods

succ :: UIntN n -> UIntN n #

pred :: UIntN n -> UIntN n #

toEnum :: Int -> UIntN n #

fromEnum :: UIntN n -> Int #

enumFrom :: UIntN n -> [UIntN n] #

enumFromThen :: UIntN n -> UIntN n -> [UIntN n] #

enumFromTo :: UIntN n -> UIntN n -> [UIntN n] #

enumFromThenTo :: UIntN n -> UIntN n -> UIntN n -> [UIntN n] #

Eq (UIntN n) Source # 

Methods

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

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

(KnownNat n, (<=) n 256) => Integral (UIntN n) Source # 

Methods

quot :: UIntN n -> UIntN n -> UIntN n #

rem :: UIntN n -> UIntN n -> UIntN n #

div :: UIntN n -> UIntN n -> UIntN n #

mod :: UIntN n -> UIntN n -> UIntN n #

quotRem :: UIntN n -> UIntN n -> (UIntN n, UIntN n) #

divMod :: UIntN n -> UIntN n -> (UIntN n, UIntN n) #

toInteger :: UIntN n -> Integer #

Num (UIntN n) Source # 

Methods

(+) :: UIntN n -> UIntN n -> UIntN n #

(-) :: UIntN n -> UIntN n -> UIntN n #

(*) :: UIntN n -> UIntN n -> UIntN n #

negate :: UIntN n -> UIntN n #

abs :: UIntN n -> UIntN n #

signum :: UIntN n -> UIntN n #

fromInteger :: Integer -> UIntN n #

Ord (UIntN n) Source # 

Methods

compare :: UIntN n -> UIntN n -> Ordering #

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

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

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

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

max :: UIntN n -> UIntN n -> UIntN n #

min :: UIntN n -> UIntN n -> UIntN n #

(KnownNat n, (<=) n 256) => Real (UIntN n) Source # 

Methods

toRational :: UIntN n -> Rational #

(KnownNat n, (<=) n 256) => Show (UIntN n) Source # 

Methods

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

show :: UIntN n -> String #

showList :: [UIntN n] -> ShowS #

Generic (UIntN n) Source # 

Associated Types

type Rep (UIntN n) :: * -> * #

Methods

from :: UIntN n -> Rep (UIntN n) x #

to :: Rep (UIntN n) x -> UIntN n #

Bits (UIntN n) Source # 

Methods

(.&.) :: UIntN n -> UIntN n -> UIntN n #

(.|.) :: UIntN n -> UIntN n -> UIntN n #

xor :: UIntN n -> UIntN n -> UIntN n #

complement :: UIntN n -> UIntN n #

shift :: UIntN n -> Int -> UIntN n #

rotate :: UIntN n -> Int -> UIntN n #

zeroBits :: UIntN n #

bit :: Int -> UIntN n #

setBit :: UIntN n -> Int -> UIntN n #

clearBit :: UIntN n -> Int -> UIntN n #

complementBit :: UIntN n -> Int -> UIntN n #

testBit :: UIntN n -> Int -> Bool #

bitSizeMaybe :: UIntN n -> Maybe Int #

bitSize :: UIntN n -> Int #

isSigned :: UIntN n -> Bool #

shiftL :: UIntN n -> Int -> UIntN n #

unsafeShiftL :: UIntN n -> Int -> UIntN n #

shiftR :: UIntN n -> Int -> UIntN n #

unsafeShiftR :: UIntN n -> Int -> UIntN n #

rotateL :: UIntN n -> Int -> UIntN n #

rotateR :: UIntN n -> Int -> UIntN n #

popCount :: UIntN n -> Int #

(<=) n 256 => ABIGet (UIntN n) Source # 

Methods

abiGet :: Get (UIntN n) Source #

(<=) n 256 => ABIPut (UIntN n) Source # 

Methods

abiPut :: Putter (UIntN n) Source #

(<=) n 256 => ABIType (UIntN n) Source # 

Methods

isDynamic :: Proxy * (UIntN n) -> Bool Source #

type Rep (UIntN n) Source # 
type Rep (UIntN n) = D1 * (MetaData "UIntN" "Network.Ethereum.ABI.Prim.Int" "web3-0.7.0.0-3hRETfypdz0IWrclyn4h7y" True) (C1 * (MetaCons "UIntN" PrefixI True) (S1 * (MetaSel (Just Symbol "unUIntN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word256)))

data ListN (n :: Nat) a :: Nat -> * -> * #

A Typed-level sized List equivalent to [a]

Instances

Eq a => Eq (ListN n a) 

Methods

(==) :: ListN n a -> ListN n a -> Bool #

(/=) :: ListN n a -> ListN n a -> Bool #

Ord a => Ord (ListN n a) 

Methods

compare :: ListN n a -> ListN n a -> Ordering #

(<) :: ListN n a -> ListN n a -> Bool #

(<=) :: ListN n a -> ListN n a -> Bool #

(>) :: ListN n a -> ListN n a -> Bool #

(>=) :: ListN n a -> ListN n a -> Bool #

max :: ListN n a -> ListN n a -> ListN n a #

min :: ListN n a -> ListN n a -> ListN n a #

Show a => Show (ListN n a) 

Methods

showsPrec :: Int -> ListN n a -> ShowS #

show :: ListN n a -> String #

showList :: [ListN n a] -> ShowS #

Generic (ListN n a) 

Associated Types

type Rep (ListN n a) :: * -> * #

Methods

from :: ListN n a -> Rep (ListN n a) x #

to :: Rep (ListN n a) x -> ListN n a #

NormalForm a => NormalForm (ListN n a) 

Methods

toNormalForm :: ListN n a -> () #

type Rep (ListN n a) 
type Rep (ListN n a) = D1 * (MetaData "ListN" "Basement.Sized.List" "basement-0.0.7-AsRzReOE7L68EDipEfgoG3" True) (C1 * (MetaCons "ListN" PrefixI True) (S1 * (MetaSel (Just Symbol "unListN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [a])))
type Item (ListN n a) # 
type Item (ListN n a) = a

Metric unit system