{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.EventSource (js_newEventSource, newEventSource, js_close, close, pattern CONNECTING, pattern OPEN, pattern CLOSED, js_getUrl, getUrl, js_getWithCredentials, getWithCredentials, js_getReadyState, getReadyState, open, message, error, EventSource, castToEventSource, gTypeEventSource) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord) import Data.Typeable (Typeable) import GHCJS.Types (JSRef(..), JSString) import GHCJS.Foreign (jsNull) import GHCJS.Foreign.Callback (syncCallback, asyncCallback, syncCallback1, asyncCallback1, syncCallback2, asyncCallback2, OnBlocked(..)) import GHCJS.Marshal (ToJSRef(..), FromJSRef(..)) import GHCJS.Marshal.Pure (PToJSRef(..), PFromJSRef(..)) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int64) import Data.Word (Word, Word64) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName) import GHCJS.DOM.Enums foreign import javascript unsafe "new window[\"EventSource\"]($1,\n$2)" js_newEventSource :: JSString -> Nullable Dictionary -> IO EventSource -- | newEventSource :: (MonadIO m, ToJSString url, IsDictionary eventSourceInit) => url -> Maybe eventSourceInit -> m EventSource newEventSource url eventSourceInit = liftIO (js_newEventSource (toJSString url) (maybeToNullable (fmap toDictionary eventSourceInit))) foreign import javascript unsafe "$1[\"close\"]()" js_close :: EventSource -> IO () -- | close :: (MonadIO m) => EventSource -> m () close self = liftIO (js_close (self)) pattern CONNECTING = 0 pattern OPEN = 1 pattern CLOSED = 2 foreign import javascript unsafe "$1[\"url\"]" js_getUrl :: EventSource -> IO JSString -- | getUrl :: (MonadIO m, FromJSString result) => EventSource -> m result getUrl self = liftIO (fromJSString <$> (js_getUrl (self))) foreign import javascript unsafe "($1[\"withCredentials\"] ? 1 : 0)" js_getWithCredentials :: EventSource -> IO Bool -- | getWithCredentials :: (MonadIO m) => EventSource -> m Bool getWithCredentials self = liftIO (js_getWithCredentials (self)) foreign import javascript unsafe "$1[\"readyState\"]" js_getReadyState :: EventSource -> IO Word -- | getReadyState :: (MonadIO m) => EventSource -> m Word getReadyState self = liftIO (js_getReadyState (self)) -- | open :: EventName EventSource Event open = unsafeEventName (toJSString "open") -- | message :: EventName EventSource MessageEvent message = unsafeEventName (toJSString "message") -- | error :: EventName EventSource UIEvent error = unsafeEventName (toJSString "error")