{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE JavaScriptFFI #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} module GHCJS.DOM.JSFFI.Generated.StyleSheetList (js_item, item, item_, itemUnsafe, itemUnchecked, js__get, _get, _get_, _getUnsafe, _getUnchecked, js_getLength, getLength, StyleSheetList(..), gTypeStyleSheetList) where import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, fmap, Show, Read, Eq, Ord) import qualified Prelude (error) import Data.Typeable (Typeable) import GHCJS.Types (JSVal(..), JSString) import GHCJS.Foreign (jsNull) import GHCJS.Foreign.Callback (syncCallback, asyncCallback, syncCallback1, asyncCallback1, syncCallback2, asyncCallback2, OnBlocked(..)) import GHCJS.Marshal (ToJSVal(..), FromJSVal(..)) import GHCJS.Marshal.Pure (PToJSVal(..), PFromJSVal(..)) import Control.Monad (void) import Control.Monad.IO.Class (MonadIO(..)) import Data.Int (Int64) import Data.Word (Word, Word64) import Data.Maybe (fromJust) import GHCJS.DOM.Types import Control.Applicative ((<$>)) import GHCJS.DOM.EventTargetClosures (EventName, unsafeEventName) import GHCJS.DOM.JSFFI.Generated.Enums foreign import javascript unsafe "$1[\"item\"]($2)" js_item :: StyleSheetList -> Word -> IO (Nullable StyleSheet) -- | item :: (MonadIO m) => StyleSheetList -> Word -> m (Maybe StyleSheet) item self index = liftIO (nullableToMaybe <$> (js_item (self) index)) -- | item_ :: (MonadIO m) => StyleSheetList -> Word -> m () item_ self index = liftIO (void (js_item (self) index)) -- | itemUnsafe :: (MonadIO m, HasCallStack) => StyleSheetList -> Word -> m StyleSheet itemUnsafe self index = liftIO ((nullableToMaybe <$> (js_item (self) index)) >>= maybe (Prelude.error "Nothing to return") return) -- | itemUnchecked :: (MonadIO m) => StyleSheetList -> Word -> m StyleSheet itemUnchecked self index = liftIO (fromJust . nullableToMaybe <$> (js_item (self) index)) foreign import javascript unsafe "$1[\"_get\"]($2)" js__get :: StyleSheetList -> JSString -> IO (Nullable CSSStyleSheet) -- | _get :: (MonadIO m, ToJSString name) => StyleSheetList -> name -> m (Maybe CSSStyleSheet) _get self name = liftIO (nullableToMaybe <$> (js__get (self) (toJSString name))) -- | _get_ :: (MonadIO m, ToJSString name) => StyleSheetList -> name -> m () _get_ self name = liftIO (void (js__get (self) (toJSString name))) -- | _getUnsafe :: (MonadIO m, ToJSString name, HasCallStack) => StyleSheetList -> name -> m CSSStyleSheet _getUnsafe self name = liftIO ((nullableToMaybe <$> (js__get (self) (toJSString name))) >>= maybe (Prelude.error "Nothing to return") return) -- | _getUnchecked :: (MonadIO m, ToJSString name) => StyleSheetList -> name -> m CSSStyleSheet _getUnchecked self name = liftIO (fromJust . nullableToMaybe <$> (js__get (self) (toJSString name))) foreign import javascript unsafe "$1[\"length\"]" js_getLength :: StyleSheetList -> IO Word -- | getLength :: (MonadIO m) => StyleSheetList -> m Word getLength self = liftIO (js_getLength (self))