reflex-gadt-api-0.2.2.1: Interact with a GADT API in your reflex-dom application.
Safe HaskellNone
LanguageHaskell2010

Reflex.Dom.GadtApi.WebSocket

Synopsis

Documentation

performWebSocketRequests :: forall req t m. (Prerender t m, Applicative m, FromJSON (Some req), forall a. ToJSON (req a), Has FromJSON req) => WebSocketEndpoint -> Event t (RequesterData req) -> m (Event t (RequesterData (Either Text))) Source #

Opens a websockets connection, takes the output of a RequesterT widget and issues that output as API requests over the socket. The result of this function can be fed back into the requester as responses. For example:

rec (appResult, requests) <- runRequesterT myApplication responses
    responses <- performWebSocketRequests myEndpoint requests

data TaggedRequest Source #

A request tagged with an identifier

Constructors

TaggedRequest Int Value 

Instances

Instances details
Generic TaggedRequest Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

Associated Types

type Rep TaggedRequest :: Type -> Type #

ToJSON TaggedRequest Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

FromJSON TaggedRequest Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

type Rep TaggedRequest Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

type Rep TaggedRequest = D1 ('MetaData "TaggedRequest" "Reflex.Dom.GadtApi.WebSocket" "reflex-gadt-api-0.2.2.1-6YgM3vwno1H7p8HjhK2w8i" 'False) (C1 ('MetaCons "TaggedRequest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))

data TaggedResponse Source #

A response tagged with an identifier matching the one in the TaggedRequest. The identifier is the first argument.

Constructors

TaggedResponse Int Value 

Instances

Instances details
Generic TaggedResponse Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

Associated Types

type Rep TaggedResponse :: Type -> Type #

ToJSON TaggedResponse Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

FromJSON TaggedResponse Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

type Rep TaggedResponse Source # 
Instance details

Defined in Reflex.Dom.GadtApi.WebSocket

type Rep TaggedResponse = D1 ('MetaData "TaggedResponse" "Reflex.Dom.GadtApi.WebSocket" "reflex-gadt-api-0.2.2.1-6YgM3vwno1H7p8HjhK2w8i" 'False) (C1 ('MetaCons "TaggedResponse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))

mkTaggedResponse :: (Monad m, FromJSON (Some f), Has ToJSON f) => TaggedRequest -> (forall a. f a -> m a) -> m (Either String TaggedResponse) Source #

Constructs a response for a given request, and handles the decoding/encoding and tagging steps internal to TaggedRequest and TaggedResponse.

tagRequests :: forall req t m. (Applicative m, FromJSON (Some req), forall a. ToJSON (req a), Has FromJSON req, Monad m, MonadFix m, Reflex t, MonadHold t m) => Event t (RequesterData req) -> Event t TaggedResponse -> m (Event t [TaggedRequest], Event t (RequesterData (Either Text))) Source #

This function transforms a request Event into an Event of TaggedRequests (the indexed wire format used to transmit requests). It expects to receive an Event of TaggedResponse, the corresponding response wire format, which it will transform into an "untagged" response.

  requests  --> |-------------| --> tagged requests
    ↗           |             |                 ↘
Client          | tagRequests |                Server
    ↖           |             |                 ↙
  responses <-- |-------------| <-- tagged responses

This function is provided so that you can use a single websocket for multiple purposes without reimplementing the functionality of performWebSocketRequests. For instance, you might have a websocket split into two "channels," one for these tagged API requests and another for data being pushed from the server.