Safe Haskell | None |
---|---|
Language | Haskell98 |
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
- 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))
- getMay :: (Monad m, Reflex t) => (Event t a -> m (Event t b)) -> Event t (Maybe a) -> m (Event t (Maybe b))
- postJson :: ToJSON a => Text -> a -> XhrRequest Text
- decodeXhrResponse :: FromJSON a => XhrResponse -> Maybe a
- decodeText :: FromJSON a => Text -> Maybe a
- data XhrRequest a = XhrRequest {}
- data XhrRequestConfig a = XhrRequestConfig {
- _xhrRequestConfig_headers :: Map Text Text
- _xhrRequestConfig_user :: Maybe Text
- _xhrRequestConfig_password :: Maybe Text
- _xhrRequestConfig_responseType :: Maybe XhrResponseType
- _xhrRequestConfig_sendData :: a
- _xhrRequestConfig_withCredentials :: Bool
- _xhrRequestConfig_responseHeaders :: XhrResponseHeaders
- xhrRequest :: Text -> Text -> XhrRequestConfig a -> XhrRequest a
- xhrRequestConfig_headers :: forall a. Lens' (XhrRequestConfig a) (Map Text Text)
- xhrRequestConfig_password :: forall a. Lens' (XhrRequestConfig a) (Maybe Text)
- xhrRequestConfig_responseType :: forall a. Lens' (XhrRequestConfig a) (Maybe XhrResponseType)
- xhrRequestConfig_sendData :: forall a a. Lens (XhrRequestConfig a) (XhrRequestConfig a) a a
- xhrRequestConfig_user :: forall a. Lens' (XhrRequestConfig a) (Maybe Text)
- xhrRequestConfig_withCredentials :: forall a. Lens' (XhrRequestConfig a) Bool
- xhrRequestConfig_responseHeaders :: forall a. Lens' (XhrRequestConfig a) XhrResponseHeaders
- xhrRequest_config :: forall a a. Lens (XhrRequest a) (XhrRequest a) (XhrRequestConfig a) (XhrRequestConfig a)
- xhrRequest_method :: forall a. Lens' (XhrRequest a) Text
- xhrRequest_url :: forall a. Lens' (XhrRequest a) Text
- 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)
- 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))
- performRequestAsync :: (MonadJSM (Performable m), HasJSContext (Performable m), PerformEvent t m, TriggerEvent t m, IsXhrPayload a) => Event t (XhrRequest a) -> m (Event t XhrResponse)
- 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))
- 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))
- 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)))
- data XhrResponse = XhrResponse {}
- data XhrResponseBody
- data XhrResponseHeaders
- = OnlyHeaders (Set Text)
- | AllHeaders
- data XhrResponseType
- xhrResponse_response :: Lens' XhrResponse (Maybe XhrResponseBody)
- xhrResponse_responseText :: Lens' XhrResponse (Maybe Text)
- xhrResponse_status :: Lens' XhrResponse Word
- xhrResponse_statusText :: Lens' XhrResponse Text
- xhrResponse_headers :: Lens' XhrResponse (Map Text Text)
- xhrResponse_body :: Lens' XhrResponse (Maybe Text)
- _xhrResponse_body :: XhrResponse -> Maybe Text
- data XhrException
- class IsXhrPayload a where
- data XMLHttpRequest
- newXMLHttpRequest :: (HasJSContext m, MonadJSM m, IsXhrPayload a) => XhrRequest a -> (XhrResponse -> JSM ()) -> m XMLHttpRequest
- newXMLHttpRequestWithError :: (HasJSContext m, MonadJSM m, IsXhrPayload a) => XhrRequest a -> (Either XhrException XhrResponse -> JSM ()) -> m XMLHttpRequest
- xmlHttpRequestGetReadyState :: MonadJSM m => XMLHttpRequest -> m Word
- xmlHttpRequestGetResponseText :: (FromJSString result, MonadJSM m) => XMLHttpRequest -> m (Maybe result)
- xmlHttpRequestGetStatus :: MonadJSM m => XMLHttpRequest -> m Word
- xmlHttpRequestGetStatusText :: MonadJSM m => FromJSString result => XMLHttpRequest -> m result
- xmlHttpRequestNew :: MonadJSM m => m XMLHttpRequest
- xmlHttpRequestOnreadystatechange :: XMLHttpRequest -> EventM XMLHttpRequest Event () -> JSM (JSM ())
- xmlHttpRequestOpen :: (ToJSString method, ToJSString url, ToJSString user, ToJSString password, MonadJSM m) => XMLHttpRequest -> method -> url -> Bool -> user -> password -> m ()
- xmlHttpRequestSetRequestHeader :: (ToJSString header, ToJSString value, MonadJSM m) => XMLHttpRequest -> header -> value -> m ()
- xmlHttpRequestSetResponseType :: MonadJSM m => XMLHttpRequest -> XMLHttpRequestResponseType -> m ()
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:
- Create an
Event
stream ofXhrRequest
records (ieEvent t (XhrRequest a)
). The records configure the request, and theEvent
controls when the request or requests are actually sent. - Plug the
Event t (XhrRequest a)
into one of the functions for performing requests likeperformRequestAsync
. - Consume the resulting stream of
XhrResponse
events, parsing the body of the response however appropriate. A really common pattern is turning theEvent
into aDynamic
withholdDyn
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
data XhrRequestConfig a Source #
Instances
xhrRequest :: Text -> Text -> XhrRequestConfig a -> XhrRequest a Source #
Construct a request object from method, URL, and config record.
xhrRequestConfig_headers :: forall a. Lens' (XhrRequestConfig a) (Map Text Text) Source #
xhrRequestConfig_password :: forall a. Lens' (XhrRequestConfig a) (Maybe Text) Source #
xhrRequestConfig_responseType :: forall a. Lens' (XhrRequestConfig a) (Maybe XhrResponseType) Source #
xhrRequestConfig_sendData :: forall a a. Lens (XhrRequestConfig a) (XhrRequestConfig a) a a Source #
xhrRequestConfig_user :: forall a. Lens' (XhrRequestConfig a) (Maybe Text) Source #
xhrRequestConfig_withCredentials :: forall a. Lens' (XhrRequestConfig a) Bool Source #
xhrRequestConfig_responseHeaders :: forall a. Lens' (XhrRequestConfig a) XhrResponseHeaders Source #
xhrRequest_config :: forall a a. Lens (XhrRequest a) (XhrRequest a) (XhrRequestConfig a) (XhrRequestConfig a) Source #
xhrRequest_method :: forall a. Lens' (XhrRequest a) Text Source #
xhrRequest_url :: forall a. Lens' (XhrRequest a) Text Source #
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
data XhrResponse Source #
data XhrResponseBody Source #
data XhrResponseHeaders Source #
OnlyHeaders (Set Text) | Parse a subset of headers from the XHR Response |
AllHeaders | Parse all headers from the XHR Response |
Instances
Eq XhrResponseHeaders Source # | |
Defined in Reflex.Dom.Xhr (==) :: XhrResponseHeaders -> XhrResponseHeaders -> Bool # (/=) :: XhrResponseHeaders -> XhrResponseHeaders -> Bool # | |
Ord XhrResponseHeaders Source # | |
Defined in Reflex.Dom.Xhr compare :: XhrResponseHeaders -> XhrResponseHeaders -> Ordering # (<) :: XhrResponseHeaders -> XhrResponseHeaders -> Bool # (<=) :: XhrResponseHeaders -> XhrResponseHeaders -> Bool # (>) :: XhrResponseHeaders -> XhrResponseHeaders -> Bool # (>=) :: XhrResponseHeaders -> XhrResponseHeaders -> Bool # max :: XhrResponseHeaders -> XhrResponseHeaders -> XhrResponseHeaders # min :: XhrResponseHeaders -> XhrResponseHeaders -> XhrResponseHeaders # | |
Read XhrResponseHeaders Source # | |
Defined in Reflex.Dom.Xhr | |
Show XhrResponseHeaders Source # | |
Defined in Reflex.Dom.Xhr showsPrec :: Int -> XhrResponseHeaders -> ShowS # show :: XhrResponseHeaders -> String # showList :: [XhrResponseHeaders] -> ShowS # | |
Default XhrResponseHeaders Source # | |
Defined in Reflex.Dom.Xhr |
data XhrResponseType Source #
Instances
Eq XhrResponseType Source # | |
Defined in Reflex.Dom.Xhr.ResponseType (==) :: XhrResponseType -> XhrResponseType -> Bool # (/=) :: XhrResponseType -> XhrResponseType -> Bool # | |
Ord XhrResponseType Source # | |
Defined in Reflex.Dom.Xhr.ResponseType compare :: XhrResponseType -> XhrResponseType -> Ordering # (<) :: XhrResponseType -> XhrResponseType -> Bool # (<=) :: XhrResponseType -> XhrResponseType -> Bool # (>) :: XhrResponseType -> XhrResponseType -> Bool # (>=) :: XhrResponseType -> XhrResponseType -> Bool # max :: XhrResponseType -> XhrResponseType -> XhrResponseType # min :: XhrResponseType -> XhrResponseType -> XhrResponseType # | |
Read XhrResponseType Source # | |
Defined in Reflex.Dom.Xhr.ResponseType | |
Show XhrResponseType Source # | |
Defined in Reflex.Dom.Xhr.ResponseType showsPrec :: Int -> XhrResponseType -> ShowS # show :: XhrResponseType -> String # showList :: [XhrResponseType] -> ShowS # |
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
data XhrException Source #
Instances
Eq XhrException Source # | |
Defined in Reflex.Dom.Xhr.Exception (==) :: XhrException -> XhrException -> Bool # (/=) :: XhrException -> XhrException -> Bool # | |
Ord XhrException Source # | |
Defined in Reflex.Dom.Xhr.Exception compare :: XhrException -> XhrException -> Ordering # (<) :: XhrException -> XhrException -> Bool # (<=) :: XhrException -> XhrException -> Bool # (>) :: XhrException -> XhrException -> Bool # (>=) :: XhrException -> XhrException -> Bool # max :: XhrException -> XhrException -> XhrException # min :: XhrException -> XhrException -> XhrException # | |
Read XhrException Source # | |
Defined in Reflex.Dom.Xhr.Exception readsPrec :: Int -> ReadS XhrException # readList :: ReadS [XhrException] # | |
Show XhrException Source # | |
Defined in Reflex.Dom.Xhr.Exception showsPrec :: Int -> XhrException -> ShowS # show :: XhrException -> String # showList :: [XhrException] -> ShowS # | |
Exception XhrException Source # | |
Defined in Reflex.Dom.Xhr.Exception |
class IsXhrPayload a where Source #
sendXhrPayload :: MonadJSM m => XMLHttpRequest -> a -> m () Source #
Instances
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.
data XMLHttpRequest #
Functions for this inteface are in JSDOM.XMLHttpRequest. Base interface functions are in:
Instances
PToJSVal XMLHttpRequest | |
Defined in JSDOM.Types pToJSVal :: XMLHttpRequest -> JSVal # | |
PFromJSVal XMLHttpRequest | |
Defined in JSDOM.Types pFromJSVal :: JSVal -> XMLHttpRequest # | |
ToJSVal XMLHttpRequest | |
Defined in JSDOM.Types toJSVal :: XMLHttpRequest -> JSM JSVal # toJSValListOf :: [XMLHttpRequest] -> JSM JSVal # | |
FromJSVal XMLHttpRequest | |
Defined in JSDOM.Types fromJSVal :: JSVal -> JSM (Maybe XMLHttpRequest) # fromJSValUnchecked :: JSVal -> JSM XMLHttpRequest # fromJSValListOf :: JSVal -> JSM (Maybe [XMLHttpRequest]) # fromJSValUncheckedListOf :: JSVal -> JSM [XMLHttpRequest] # | |
MakeObject XMLHttpRequest | |
Defined in JSDOM.Types makeObject :: XMLHttpRequest -> JSM Object # | |
IsGObject XMLHttpRequest | |
Defined in JSDOM.Types typeGType :: XMLHttpRequest -> JSM GType | |
IsEventTarget XMLHttpRequest | |
Defined in JSDOM.Types | |
IsXMLHttpRequestEventTarget XMLHttpRequest | |
Defined in JSDOM.Types |
Constructors
newXMLHttpRequest :: (HasJSContext m, MonadJSM m, IsXhrPayload a) => XhrRequest a -> (XhrResponse -> JSM ()) -> m XMLHttpRequest Source #
newXMLHttpRequestWithError Source #
:: (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
xmlHttpRequestGetReadyState :: MonadJSM m => XMLHttpRequest -> m Word Source #
xmlHttpRequestGetResponseText :: (FromJSString result, MonadJSM m) => XMLHttpRequest -> m (Maybe result) Source #
xmlHttpRequestGetStatus :: MonadJSM m => XMLHttpRequest -> m Word Source #
xmlHttpRequestGetStatusText :: MonadJSM m => FromJSString result => XMLHttpRequest -> m result Source #
xmlHttpRequestNew :: MonadJSM m => m XMLHttpRequest Source #
xmlHttpRequestOnreadystatechange :: XMLHttpRequest -> EventM XMLHttpRequest Event () -> JSM (JSM ()) Source #
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 #
xmlHttpRequestSetResponseType :: MonadJSM m => XMLHttpRequest -> XMLHttpRequestResponseType -> m () Source #