{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE JavaScriptFFI #-} -- For HasCallStack compatibility {-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-} module GHCJS.DOM.JSFFI.Generated.Animation (js_newAnimation, newAnimation, js_getEffect, getEffect, getEffectUnsafe, getEffectUnchecked, js_getTimeline, getTimeline, getTimelineUnsafe, getTimelineUnchecked, Animation(..), gTypeAnimation) 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, jsUndefined) 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 Data.Traversable (mapM) 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[\"Animation\"]($1, $2)" js_newAnimation :: Optional AnimationEffect -> Optional AnimationTimeline -> IO Animation -- | newAnimation :: (MonadIO m, IsAnimationEffect effect, IsAnimationTimeline timeline) => Maybe effect -> Maybe timeline -> m Animation newAnimation effect timeline = liftIO (js_newAnimation (maybeToOptional (fmap toAnimationEffect effect)) (maybeToOptional (fmap toAnimationTimeline timeline))) foreign import javascript unsafe "$1[\"effect\"]" js_getEffect :: Animation -> IO (Nullable AnimationEffect) -- | getEffect :: (MonadIO m) => Animation -> m (Maybe AnimationEffect) getEffect self = liftIO (nullableToMaybe <$> (js_getEffect self)) -- | getEffectUnsafe :: (MonadIO m, HasCallStack) => Animation -> m AnimationEffect getEffectUnsafe self = liftIO ((nullableToMaybe <$> (js_getEffect self)) >>= maybe (Prelude.error "Nothing to return") return) -- | getEffectUnchecked :: (MonadIO m) => Animation -> m AnimationEffect getEffectUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getEffect self)) foreign import javascript unsafe "$1[\"timeline\"]" js_getTimeline :: Animation -> IO (Nullable AnimationTimeline) -- | getTimeline :: (MonadIO m) => Animation -> m (Maybe AnimationTimeline) getTimeline self = liftIO (nullableToMaybe <$> (js_getTimeline self)) -- | getTimelineUnsafe :: (MonadIO m, HasCallStack) => Animation -> m AnimationTimeline getTimelineUnsafe self = liftIO ((nullableToMaybe <$> (js_getTimeline self)) >>= maybe (Prelude.error "Nothing to return") return) -- | getTimelineUnchecked :: (MonadIO m) => Animation -> m AnimationTimeline getTimelineUnchecked self = liftIO (fromJust . nullableToMaybe <$> (js_getTimeline self))