{-# LANGUAGE ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.XMLHttpRequest ( module Generated , XHRError(..) , js_send , send , sendString , sendArrayBuffer , sendBlob , sendDocument , sendFormData ) where import Control.Monad.IO.Class (MonadIO(..)) import Control.Exception (Exception(..), throwIO, onException) import GHCJS.Types (JSVal) import GHCJS.Marshal.Internal (PToJSVal(..)) import GHCJS.Foreign (jsNull) import GHCJS.DOM.Types import GHCJS.DOM.JSFFI.Generated.XMLHttpRequest as Generated hiding (js_send, send) import GHCJS.DOM.JSFFI.Generated.XMLHttpRequestEventTarget as Generated data XHRError = XHRError | XHRAborted deriving (Show, Eq) instance Exception XHRError throwXHRError 0 = return () throwXHRError 1 = throwIO XHRAborted throwXHRError 2 = throwIO XHRError foreign import javascript interruptible "h$dom$sendXHR($1, $2, $c);" js_send :: XMLHttpRequest -> JSVal -> IO Int -- | send :: (MonadIO m) => XMLHttpRequest -> m () send self = liftIO $ (js_send self jsNull >>= throwXHRError) `onException` abort self -- | sendString :: (MonadIO m, ToJSString str) => XMLHttpRequest -> str -> m () sendString self str = liftIO $ (js_send self (pToJSVal str) >>= throwXHRError) `onException` abort self -- | sendArrayBuffer :: (MonadIO m, IsArrayBufferView view) => XMLHttpRequest -> view -> m () sendArrayBuffer self view = liftIO $ (js_send self (unArrayBufferView $ toArrayBufferView view) >>= throwXHRError) `onException` abort self -- | sendBlob :: (MonadIO m, IsBlob blob) => XMLHttpRequest -> blob -> m () sendBlob self blob = liftIO $ (js_send self (unBlob $ toBlob blob) >>= throwXHRError) `onException` abort self -- | sendDocument :: (MonadIO m, IsDocument doc) => XMLHttpRequest -> doc -> m () sendDocument self doc = liftIO $ (js_send self (unDocument $ toDocument doc) >>= throwXHRError) `onException` abort self -- | sendFormData :: (MonadIO m) => XMLHttpRequest -> FormData -> m () sendFormData self formData = liftIO $ (js_send self (unFormData formData) >>= throwXHRError) `onException` abort self