reflex-dom-core-0.5: Functional Reactive Web Apps with Reflex

Safe HaskellNone
LanguageHaskell98

Reflex.Dom.Xhr

Contents

Description

A module for performing asynchronous HTTP calls from JavaScript using the XMLHttpRequest API (essentially AJAX). Despite the name, there is nothing whatsoever specific to XML.

The API has two components:

  • convenient functions for common usecases like GET and POST requests to APIs using JSON.
  • a flexible set of functions for creating and executing arbitrary requests and handling responses.
Synopsis

Common Patterns

Functions that conveniently expose common uses like GET and POST to JSON APIs.

getAndDecode :: (MonadIO m, MonadJSM (Performable m), PerformEvent t m, HasJSContext (Performable m), TriggerEvent t m, FromJSON a) => Event t Text -> m (Event t (Maybe a)) Source #

Simplified interface to GET URLs and return decoded results.

getMay :: (Monad m, Reflex t) => (Event t a -> m (Event t b)) -> Event t (Maybe a) -> m (Event t (Maybe b)) Source #

postJson :: ToJSON a => Text -> a -> XhrRequest Text Source #

Create a POST request from an URL and thing with a JSON representation

decodeXhrResponse :: FromJSON a => XhrResponse -> Maybe a Source #

Convenience function to decode JSON-encoded responses.

General Request API

This is the most general flow for sending XHR requests:

  1. Create an Event stream of XhrRequest records (ie Event t (XhrRequest a)). The records configure the request, and the Event controls when the request or requests are actually sent.
  2. Plug the Event t (XhrRequest a) into one of the functions for performing requests like performRequestAsync.
  3. Consume the resulting stream of XhrResponse events, parsing the body of the response however appropriate. A really common pattern is turning the Event into a Dynamic with holdDyn or a related function.

Here is an example of calling a search API whenever the user types in a text input field and printing the result on the page:

url query = "http://example.com/search?query=" <> query

search queries = do
  responses <- performRequestAsync $ toRequest <$> queries
  return $ view xhrResponse_responseText <$> responses
  where toRequest query = XhrRequest "GET" (url query) def

main = mainWidget $ do
  input <- textInput def
  let queries = updated $ input ^. textInput_value
  results <- search queries
  asText <- holdDyn "No results." $ pack . show <$> results
  dynText asText

XHR Requests

data XhrRequest a Source #

Instances
Functor XhrRequest Source # 
Instance details

Defined in Reflex.Dom.Xhr

Methods

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

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

Eq a => Eq (XhrRequest a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

Methods

(==) :: XhrRequest a -> XhrRequest a -> Bool #

(/=) :: XhrRequest a -> XhrRequest a -> Bool #

Ord a => Ord (XhrRequest a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

Read a => Read (XhrRequest a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

Show a => Show (XhrRequest a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

data XhrRequestConfig a Source #

Instances
Functor XhrRequestConfig Source # 
Instance details

Defined in Reflex.Dom.Xhr

Methods

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

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

Eq a => Eq (XhrRequestConfig a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

Ord a => Ord (XhrRequestConfig a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

Read a => Read (XhrRequestConfig a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

Show a => Show (XhrRequestConfig a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

a ~ () => Default (XhrRequestConfig a) Source # 
Instance details

Defined in Reflex.Dom.Xhr

Methods

def :: XhrRequestConfig a #

xhrRequest :: Text -> Text -> XhrRequestConfig a -> XhrRequest a Source #

Construct a request object from method, URL, and config record.

Performing Requests

performMkRequestAsync :: (MonadJSM (Performable m), HasJSContext (Performable m), PerformEvent t m, TriggerEvent t m, IsXhrPayload a) => Event t (Performable m (XhrRequest a)) -> m (Event t XhrResponse) Source #

Given Event with an action that creates a request, build and issue the request when the Event fires. Returns Event of corresponding response.

performMkRequestsAsync :: (MonadJSM (Performable m), HasJSContext (Performable m), PerformEvent t m, TriggerEvent t m, Traversable f, IsXhrPayload a) => Event t (Performable m (f (XhrRequest a))) -> m (Event t (f XhrResponse)) Source #

Builds and issues a collection of requests when the supplied Event fires. When ALL requests from a given firing complete, the results are collected and returned via the return Event.

performRequestAsync :: (MonadJSM (Performable m), HasJSContext (Performable m), PerformEvent t m, TriggerEvent t m, IsXhrPayload a) => Event t (XhrRequest a) -> m (Event t XhrResponse) Source #

Given Event of request, issue them when the Event fires. Returns Event of corresponding response.

performRequestAsyncWithError :: (MonadJSM (Performable m), HasJSContext (Performable m), PerformEvent t m, TriggerEvent t m, IsXhrPayload a) => Event t (XhrRequest a) -> m (Event t (Either XhrException XhrResponse)) Source #

Given Event of requests, issue them when the Event fires. Returns Event of corresponding responses.

The request is processed asynchronously, therefore handling does not block or cause a delay while creating the connection.

performRequestsAsync :: (MonadJSM (Performable m), HasJSContext (Performable m), PerformEvent t m, TriggerEvent t m, Traversable f, IsXhrPayload a) => Event t (f (XhrRequest a)) -> m (Event t (f XhrResponse)) Source #

Issues a collection of requests when the supplied Event fires. When ALL requests from a given firing complete, the results are collected and returned via the return Event.

performRequestsAsyncWithError :: (MonadJSM (Performable m), HasJSContext (Performable m), PerformEvent t m, TriggerEvent t m, Traversable f, IsXhrPayload a) => Event t (f (XhrRequest a)) -> m (Event t (f (Either XhrException XhrResponse))) Source #

Issues a collection of requests when the supplied Event fires. When ALL requests from a given firing complete, the results are collected and returned via the return Event.

The requests are processed asynchronously, therefore handling does not block or cause a delay while creating the connection.

Order of request execution and completion is not guaranteed, but order of creation and the collection result is preserved.

XHR Responses

Deprecated

xhrResponse_body :: Lens' XhrResponse (Maybe Text) Source #

Deprecated: Use xhrResponse_response or xhrResponse_responseText instead.

_xhrResponse_body :: XhrResponse -> Maybe Text Source #

Deprecated: Use _xhrResponse_response or _xhrResponse_responseText instead.

Error Handling

class IsXhrPayload a where Source #

Minimal complete definition

sendXhrPayload

Methods

sendXhrPayload :: MonadJSM m => XMLHttpRequest -> a -> m () Source #

Instances
IsXhrPayload () Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

Methods

sendXhrPayload :: MonadJSM m => XMLHttpRequest -> () -> m () Source #

IsXhrPayload String Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

IsXhrPayload ByteString Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

IsXhrPayload Text Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

IsXhrPayload ArrayBuffer Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

IsXhrPayload Blob Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

IsXhrPayload Document Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

IsXhrPayload FormData Source # 
Instance details

Defined in Reflex.Dom.Xhr.Foreign

JavaScript XMLHttpRequest Objects

XMLHttpRequest is the type of JavaScript's underlying runtime objects that represent XHR requests.

Chances are you shouldn't need these in day-to-day code.

Constructors

newXMLHttpRequestWithError Source #

Arguments

:: (HasJSContext m, MonadJSM m, IsXhrPayload a) 
=> XhrRequest a

The request to make.

-> (Either XhrException XhrResponse -> JSM ())

A continuation to be called once a response comes back, or in case of error.

-> m XMLHttpRequest

The XHR request, which could for example be aborted.

Make a new asyncronous XHR request. This does not block (it forks), and returns an XHR object immediately (which you can use to abort the XHR connection), and will pass an exception (XhrException) to the continuation if the connection cannot be made (or is aborted).

Fields

xmlHttpRequestOpen :: (ToJSString method, ToJSString url, ToJSString user, ToJSString password, MonadJSM m) => XMLHttpRequest -> method -> url -> Bool -> user -> password -> m () Source #

xmlHttpRequestSetRequestHeader :: (ToJSString header, ToJSString value, MonadJSM m) => XMLHttpRequest -> header -> value -> m () Source #