{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.ApplicationCache (js_update, update, js_swapCache, swapCache, js_abort, abort, pattern UNCACHED, pattern IDLE, pattern CHECKING, pattern DOWNLOADING, pattern UPDATEREADY, pattern OBSOLETE, js_getStatus, getStatus, checking, error, noUpdate, downloading, progress, updateReady, cached, obsolete, ApplicationCache, castToApplicationCache, gTypeApplicationCache) 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, castRef) 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 "$1[\"update\"]()" js_update :: JSRef ApplicationCache -> IO () -- | update :: (MonadIO m) => ApplicationCache -> m () update self = liftIO (js_update (unApplicationCache self)) foreign import javascript unsafe "$1[\"swapCache\"]()" js_swapCache :: JSRef ApplicationCache -> IO () -- | swapCache :: (MonadIO m) => ApplicationCache -> m () swapCache self = liftIO (js_swapCache (unApplicationCache self)) foreign import javascript unsafe "$1[\"abort\"]()" js_abort :: JSRef ApplicationCache -> IO () -- | abort :: (MonadIO m) => ApplicationCache -> m () abort self = liftIO (js_abort (unApplicationCache self)) pattern UNCACHED = 0 pattern IDLE = 1 pattern CHECKING = 2 pattern DOWNLOADING = 3 pattern UPDATEREADY = 4 pattern OBSOLETE = 5 foreign import javascript unsafe "$1[\"status\"]" js_getStatus :: JSRef ApplicationCache -> IO Word -- | getStatus :: (MonadIO m) => ApplicationCache -> m Word getStatus self = liftIO (js_getStatus (unApplicationCache self)) -- | checking :: EventName ApplicationCache Event checking = unsafeEventName (toJSString "checking") -- | error :: EventName ApplicationCache UIEvent error = unsafeEventName (toJSString "error") -- | noUpdate :: EventName ApplicationCache Event noUpdate = unsafeEventName (toJSString "noupdate") -- | downloading :: EventName ApplicationCache Event downloading = unsafeEventName (toJSString "downloading") -- | progress :: EventName ApplicationCache ProgressEvent progress = unsafeEventName (toJSString "progress") -- | updateReady :: EventName ApplicationCache Event updateReady = unsafeEventName (toJSString "updateready") -- | cached :: EventName ApplicationCache Event cached = unsafeEventName (toJSString "cached") -- | obsolete :: EventName ApplicationCache Event obsolete = unsafeEventName (toJSString "obsolete")