{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE JavaScriptFFI #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} module GHCJS.DOM.JSFFI.Generated.DataCue (js_newDataCue, newDataCue, js_newDataCue', newDataCue', js_setData, setData, js_getData, getData, getDataUnsafe, getDataUnchecked, js_setValue, setValue, js_getValue, getValue, js_getType, getType, DataCue(..), gTypeDataCue) 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 "new window[\"WebKitDataCue\"]()" js_newDataCue :: IO DataCue -- | newDataCue :: (MonadIO m) => m DataCue newDataCue = liftIO (js_newDataCue) foreign import javascript unsafe "new window[\"WebKitDataCue\"]($1,\n$2, $3, $4)" js_newDataCue' :: Double -> Double -> JSVal -> JSString -> IO DataCue -- | newDataCue' :: (MonadIO m, ToJSString type') => Double -> Double -> JSVal -> type' -> m DataCue newDataCue' startTime endTime value type' = liftIO (js_newDataCue' startTime endTime value (toJSString type')) foreign import javascript unsafe "$1[\"data\"] = $2;" js_setData :: DataCue -> Nullable ArrayBuffer -> IO () -- | setData :: (MonadIO m, IsArrayBuffer val) => DataCue -> Maybe val -> m () setData self val = liftIO (js_setData (self) (maybeToNullable (fmap toArrayBuffer val))) foreign import javascript unsafe "$1[\"data\"]" js_getData :: DataCue -> IO (Nullable ArrayBuffer) -- | getData :: (MonadIO m) => DataCue -> m (Maybe ArrayBuffer) getData self = liftIO (nullableToMaybe <$> (js_getData (self))) -- | getDataUnsafe :: (MonadIO m, HasCallStack) => DataCue -> m ArrayBuffer getDataUnsafe self = liftIO ((nullableToMaybe <$> (js_getData (self))) >>= maybe (Prelude.error "Nothing to return") return) -- | getDataUnchecked :: (MonadIO m) => DataCue -> m ArrayBuffer getDataUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getData (self))) foreign import javascript unsafe "$1[\"value\"] = $2;" js_setValue :: DataCue -> JSVal -> IO () -- | setValue :: (MonadIO m) => DataCue -> JSVal -> m () setValue self val = liftIO (js_setValue (self) val) foreign import javascript unsafe "$1[\"value\"]" js_getValue :: DataCue -> IO JSVal -- | getValue :: (MonadIO m) => DataCue -> m JSVal getValue self = liftIO (js_getValue (self)) foreign import javascript unsafe "$1[\"type\"]" js_getType :: DataCue -> IO JSString -- | getType :: (MonadIO m, FromJSString result) => DataCue -> m result getType self = liftIO (fromJSString <$> (js_getType (self)))