Safe Haskell | None |
---|---|
Language | Haskell98 |
- data XMLHttpRequest
- data XhrRequest = XhrRequest {}
- data XhrRequestConfig = XhrRequestConfig {}
- data XhrResponse = XhrResponse {}
- data XhrResponseBody
- data XhrResponseType
- data XhrException
- _xhrResponse_body :: XhrResponse -> Maybe Text
- xhrResponse_body :: Lens XhrResponse XhrResponse (Maybe Text) (Maybe Text)
- xhrRequest :: String -> String -> XhrRequestConfig -> XhrRequest
- newXMLHttpRequest :: (HasWebView m, MonadIO m, HasPostGui t h m) => XhrRequest -> (XhrResponse -> h ()) -> m XMLHttpRequest
- newXMLHttpRequestWithError :: (HasWebView m, MonadIO m, HasPostGui t h m) => XhrRequest -> (Either XhrException XhrResponse -> h ()) -> m XMLHttpRequest
- performRequestAsync :: MonadWidget t m => Event t XhrRequest -> m (Event t XhrResponse)
- performRequestAsyncWithError :: MonadWidget t m => Event t XhrRequest -> m (Event t (Either XhrException XhrResponse))
- performRequestsAsync :: (Traversable f, MonadWidget t m) => Event t (f XhrRequest) -> m (Event t (f XhrResponse))
- performRequestsAsyncWithError :: (Traversable f, MonadWidget t m) => Event t (f XhrRequest) -> m (Event t (f (Either XhrException XhrResponse)))
- getAndDecode :: (FromJSON a, MonadWidget t m) => Event t String -> m (Event t (Maybe a))
- postJson :: ToJSON a => String -> a -> XhrRequest
- getMay :: MonadWidget t m => (Event t a -> m (Event t b)) -> Event t (Maybe a) -> m (Event t (Maybe b))
- decodeText :: FromJSON a => Text -> Maybe a
- decodeXhrResponse :: FromJSON a => XhrResponse -> Maybe a
- xmlHttpRequestGetReadyState :: XMLHttpRequest -> IO Word
- xmlHttpRequestGetResponseText :: XMLHttpRequest -> IO (Maybe Text)
- xmlHttpRequestGetStatus :: XMLHttpRequest -> IO Word
- xmlHttpRequestGetStatusText :: XMLHttpRequest -> IO Text
- xmlHttpRequestNew :: WebView -> IO XMLHttpRequest
- xmlHttpRequestOnreadystatechange :: XMLHttpRequest -> IO () -> IO ()
- xmlHttpRequestOpen :: XMLHttpRequest -> String -> String -> Bool -> String -> String -> IO ()
- xmlHttpRequestSend :: XMLHttpRequest -> Maybe String -> IO ()
- xmlHttpRequestSetRequestHeader :: XMLHttpRequest -> String -> String -> IO ()
- xmlHttpRequestSetResponseType :: XMLHttpRequest -> String -> IO ()
Documentation
data XhrResponse Source
data XhrResponseBody Source
data XhrResponseType Source
data XhrException Source
_xhrResponse_body :: XhrResponse -> Maybe Text Source
Deprecated: Use _xhrResponse_response or _xhrResponse_responseText instead.
xhrResponse_body :: Lens XhrResponse XhrResponse (Maybe Text) (Maybe Text) Source
Deprecated: Use xhrResponse_response or xhrResponse_responseText instead.
xhrRequest :: String -> String -> XhrRequestConfig -> XhrRequest Source
Construct a request object from method, URL, and config record.
newXMLHttpRequest :: (HasWebView m, MonadIO m, HasPostGui t h m) => XhrRequest -> (XhrResponse -> h ()) -> m XMLHttpRequest Source
newXMLHttpRequestWithError Source
:: (HasWebView m, MonadIO m, HasPostGui t h m) | |
=> XhrRequest | The request to make. |
-> (Either XhrException XhrResponse -> h ()) | 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).
performRequestAsync :: MonadWidget t m => Event t XhrRequest -> m (Event t XhrResponse) Source
performRequestAsyncWithError :: MonadWidget t m => Event t XhrRequest -> 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 :: (Traversable f, MonadWidget t m) => Event t (f XhrRequest) -> m (Event t (f XhrResponse)) Source
performRequestsAsyncWithError :: (Traversable f, MonadWidget t m) => Event t (f XhrRequest) -> 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.
getAndDecode :: (FromJSON a, MonadWidget t m) => Event t String -> m (Event t (Maybe a)) Source
Simplified interface to GET URLs and return decoded results.
postJson :: ToJSON a => String -> a -> XhrRequest Source
Create a POST request from an URL and thing with a JSON representation
getMay :: MonadWidget t m => (Event t a -> m (Event t b)) -> Event t (Maybe a) -> m (Event t (Maybe b)) Source
decodeText :: FromJSON a => Text -> Maybe a Source
decodeXhrResponse :: FromJSON a => XhrResponse -> Maybe a Source
Convenience function to decode JSON-encoded responses.
xmlHttpRequestOnreadystatechange :: XMLHttpRequest -> IO () -> IO () Source
xmlHttpRequestOpen :: XMLHttpRequest -> String -> String -> Bool -> String -> String -> IO () Source
xmlHttpRequestSend :: XMLHttpRequest -> Maybe String -> IO () Source
xmlHttpRequestSetRequestHeader :: XMLHttpRequest -> String -> String -> IO () Source
xmlHttpRequestSetResponseType :: XMLHttpRequest -> String -> IO () Source