Copyright | Alexander Krupenkin 2016-2018 |
---|---|
License | BSD3 |
Maintainer | mail@akru.me |
Stability | experimental |
Portability | unportable |
Safe Haskell | None |
Language | Haskell2010 |
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.
- data Web3 a
- runWeb3 :: MonadIO m => Web3 a -> m (Either Web3Error a)
- sendTx :: Method a => Call -> a -> Web3 TxHash
- data Call = Call {}
- data EventAction
- event :: DecodeEvent i ni e => Filter e -> (e -> ReaderT Change Web3 EventAction) -> Web3 (Async ())
- event' :: DecodeEvent i ni e => Filter e -> (e -> ReaderT Change Web3 EventAction) -> Web3 ()
- data Address
- data Bytes :: *
- type BytesN n = SizedByteArray n Bytes
- data IntN (n :: Nat)
- data UIntN (n :: Nat)
- data ListN (n :: Nat) a :: Nat -> * -> *
- module Network.Ethereum.Unit
Monad as base of any Ethereum node communication
Any communication with Ethereum node wrapped with Web3
monad
Basic transaction sending
sendTx
is used to submit a state changing transaction.
The contract call params
Basic event listening
data EventAction Source #
Event callback control response
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
Ethereum account address
Simplest Byte Array
type BytesN n = SizedByteArray n Bytes Source #
(KnownNat n, (<=) n 256) => Bounded (IntN n) Source # | |
Enum (IntN n) Source # | |
Eq (IntN n) Source # | |
(KnownNat n, (<=) n 256) => Integral (IntN n) Source # | |
(KnownNat n, (<=) n 256) => Num (IntN n) Source # | |
Ord (IntN n) Source # | |
(KnownNat n, (<=) n 256) => Real (IntN n) Source # | |
(KnownNat n, (<=) n 256) => Show (IntN n) Source # | |
Generic (IntN n) Source # | |
Bits (IntN n) Source # | |
(<=) n 256 => ABIGet (IntN n) Source # | |
(<=) n 256 => ABIPut (IntN n) Source # | |
(<=) n 256 => ABIType (IntN n) Source # | |
type Rep (IntN n) Source # | |
data UIntN (n :: Nat) Source #
(KnownNat n, (<=) n 256) => Bounded (UIntN n) Source # | |
Enum (UIntN n) Source # | |
Eq (UIntN n) Source # | |
(KnownNat n, (<=) n 256) => Integral (UIntN n) Source # | |
Num (UIntN n) Source # | |
Ord (UIntN n) Source # | |
(KnownNat n, (<=) n 256) => Real (UIntN n) Source # | |
(KnownNat n, (<=) n 256) => Show (UIntN n) Source # | |
Generic (UIntN n) Source # | |
Bits (UIntN n) Source # | |
(<=) n 256 => ABIGet (UIntN n) Source # | |
(<=) n 256 => ABIPut (UIntN n) Source # | |
(<=) n 256 => ABIType (UIntN n) Source # | |
type Rep (UIntN n) Source # | |
Metric unit system
module Network.Ethereum.Unit