haskoin-0.0.2: Implementation of the Bitcoin protocol.

Safe HaskellNone

Network.Haskoin.Stratum

Contents

Synopsis

Types

Bitcoin

data Balance Source

Balance information.

Constructors

Balance 

Fields

balConfirmed :: Word64

Confirmed balance.

balUnconfirmed :: Word64

Unconfirmed balance.

Instances

data Coin Source

Bitcoin outpoint information.

Constructors

Coin 

Fields

coinOutPoint :: OutPoint

Coin data.

coinTxHeight :: TxHeight

Transaction information.

coinValue :: Word64

Output vale.

Instances

data TxHeight Source

Transaction height and ID pair. Used in history responses.

Constructors

TxHeight 

Fields

txHeightBlock :: Word

Block height.

txHeightId :: Hash256

Transaction id.

Stratum data

data StratumQuery Source

Stratum Request data. To be placed inside JSON request.

JSON-RPC data for Stratum

type MessageStratum = Message StratumNotif StratumResponse Value StringSource

Message from Stratum JSON-RPC server.

type NotifStratum = Request StratumNotifSource

JSON-RPC notification with Stratum payload.

type RequestStratum = Request StratumQuerySource

JSON-RPC request with Stratum payload.

type ResponseStratum = Response StratumResponse Value StringSource

JSON-RPC response with Stratum payload.

type ResultStratum = Result StratumResponse Value StringSource

Stratum result in JSON-RPC response.

Stratum Session for JSON-RPC Conduit

type StratumSession = Session RequestStratum StratumResponse Value String StratumNotifSource

Session type for JSON-RPC conduit.

Functions

toRequestSource

Arguments

:: StratumQuery

Stratum request data.

-> Int

JSON-RPC request id.

-> RequestStratum

Returns JSON-RPC request object.

Create a JSON-RPC request from a Stratum request.

parseResultSource

Arguments

:: StratumQuery

StratumQuery used in corresponding request.

-> ResultValue

Result from JSON-RPC response

-> Parser ResultStratum

Returns Aeson parser.

Parse result from JSON-RPC response into a Stratum response.

parseNotifSource

Arguments

:: RequestValue

Request to parse.

-> Parser NotifStratum

Parser to Stratum request format

Parse notification from JSON-RPC request into Stratum format.

newStratumReq :: MonadIO m => StratumSession -> StratumQuery -> m IntSource

Helper function for Network.Haskoin.JSONRPC.Conduit

Generic JSON-RPC Conduit

Types

data Session q r e v j Source

Session state.

Functions

initSessionSource

Arguments

:: MonadIO m 
=> Maybe (RequestParser j)

Parse incoming requests and notifications. Keep connection open.

-> m (Session q r e v j) 

Create initial session.

newReqSource

Arguments

:: MonadIO m 
=> Session q r e v j

Session state.

-> (Int -> q)

Request builder.

-> ResponseParser r e v

Parser for response.

-> m Int

Output ID of sent request.

Send a new request. Goes to a channel that is read from reqSource.

newNotifSource

Arguments

:: MonadIO m 
=> Session q r e v j

Session state.

-> q

Request to send to the network.

-> m ()

No meaningful output.

New notification, or request with no id tracking.

reqSourceSource

Arguments

:: (MonadIO m, ToJSON q) 
=> Session q r e v j

Session state.

-> Source m ByteString

Source with serialized requests.

Source of requests to send to the network.

resConduitSource

Arguments

:: MonadIO m 
=> Session q r e v j

Session state.

-> Conduit ByteString m (Either String (Message j r e v))

Returns Conduit with parsed data or parsing errors.

Conduit that parses messages from network.

Generic JSON-RPC Messages

Types

type Method = TextSource

JSON-RPC method name.

type ErrorValue = Error Value StringSource

JSON-RPC error object with default JSON values.

type RequestValue = Request ValueSource

JSON-RPC request with default JSON values.

type ResponseValue = Response Value Value StringSource

JSON-RPC response with default JSON values.

type MessageValue = Message Value Value Value StringSource

JSON-RPC request or response with default JSON values.

type ResultValue = Result Value Value StringSource

JSON-RPC result with default JSON values.

data Id Source

JSON-RPC id in text or integer form.

Constructors

IntId

Id in integer form.

Fields

intId :: Int
 
TxtId

Id in string form (discouraged).

Fields

txtId :: Text
 

Instances

Eq Id 
Show Id 
ToJSON Id 
FromJSON Id 

type Result r e v = Either (Error e v) rSource

JSON-RPC result.

data Error e v Source

JSON-RPC error object in v1 or v2 format. Sent inside a JSONRes in case of error.

Constructors

ErrObj

Error object in JSON-RPC version 2 format.

Fields

errCode :: Int

Integer error code.

errMsg :: String

Error message.

errData :: Maybe e

Optional error object.

ErrVal

Error object in JSON-RPC version 1 format.

Fields

errVal :: v

Usually String.

Instances

(Eq e, Eq v) => Eq (Error e v) 
(Show e, Show v) => Show (Error e v) 
(ToJSON e, ToJSON v) => ToJSON (Error e v) 
(FromJSON e, FromJSON v) => FromJSON (Error e v) 

Messages

data Request j Source

JSON-RPC request on notification.

Constructors

Request 

Fields

reqMethod :: Method

Request method.

reqParams :: Maybe j

Request parameters. Should be Object or Array.

reqId :: Maybe Id

Request id. Nothing for notifications.

Instances

Eq j => Eq (Request j) 
Show j => Show (Request j) 
ToJSON j => ToJSON (Request j) 
FromJSON j => FromJSON (Request j) 

data Response r e v Source

JSON-RPC response or error.

Constructors

Response 

Fields

resResult :: Result r e v

Result or error.

resId :: Maybe Id

Result id.

Instances

(Eq r, Eq e, Eq v) => Eq (Response r e v) 
(Show r, Show e, Show v) => Show (Response r e v) 
(ToJSON r, ToJSON e, ToJSON v) => ToJSON (Response r e v) 
(FromJSON r, FromJSON e, FromJSON v) => FromJSON (Response r e v) 

data Message j r e v Source

JSON-RPC message, can contain request or response.

Constructors

MsgRequest (Request j)

Request message container.

MsgResponse (Response r e v)

response message container.

Instances

(Eq j, Eq r, Eq e, Eq v) => Eq (Message j r e v) 
(Show j, Show r, Show e, Show v) => Show (Message j r e v) 
(ToJSON j, ToJSON r, ToJSON e, ToJSON v) => ToJSON (Message j r e v) 
(FromJSON j, FromJSON r, FromJSON e, FromJSON v) => FromJSON (Message j r e v) 

Errors

errParse :: ToJSON e => Maybe e -> Error e vSource

Parse error in JSON-RPC v2 format. Provide optional error object.

errReq :: ToJSON e => Maybe e -> Error e vSource

Request error in JSON-RPC v2 format. Provide optional error object.

errMeth :: ToJSON e => Maybe e -> Error e vSource

Unknown method error in JSON-RPC v2 format. Provide optional error object.

errParams :: ToJSON e => Maybe e -> Error e vSource

Invalid parameters error in JSON-RPC v2 format. Provide optional error object.

errInternal :: ToJSON e => Maybe e -> Error e vSource

Internal error in JSON-RPC v2 format. Provide optional error object.

errStr :: Error e Value -> StringSource

Get string from error object.

Helpers

leftStr :: Either (Error e Value) r -> Either String rSource

Map Left error objects to strings.

numericId :: Id -> Either String IntSource

Force an id into a number or fail if not possible.