{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.IntersectionObserverEntry
(newIntersectionObserverEntry, getTime, getRootBounds,
getBoundingClientRect, getIntersectionRect, getIntersectionRatio,
getTarget, IntersectionObserverEntry(..),
gTypeIntersectionObserverEntry)
where
import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, realToFrac, fmap, Show, Read, Eq, Ord, Maybe(..))
import qualified Prelude (error)
import Data.Typeable (Typeable)
import Data.Traversable (mapM)
import Language.Javascript.JSaddle (JSM(..), JSVal(..), JSString, strictEqual, toJSVal, valToStr, valToNumber, valToBool, js, jss, jsf, jsg, function, asyncFunction, new, array, jsUndefined, (!), (!!))
import Data.Int (Int64)
import Data.Word (Word, Word64)
import JSDOM.Types
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Lens.Operators ((^.))
import JSDOM.EventTargetClosures (EventName, unsafeEventName, unsafeEventNameAsync)
import JSDOM.Enums
newIntersectionObserverEntry ::
(MonadDOM m) =>
IntersectionObserverEntryInit -> m IntersectionObserverEntry
newIntersectionObserverEntry :: forall (m :: * -> *).
MonadDOM m =>
IntersectionObserverEntryInit -> m IntersectionObserverEntry
newIntersectionObserverEntry IntersectionObserverEntryInit
intersectionObserverEntryInit
= DOM IntersectionObserverEntry -> m IntersectionObserverEntry
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
(JSVal -> IntersectionObserverEntry
IntersectionObserverEntry (JSVal -> IntersectionObserverEntry)
-> JSM JSVal -> DOM IntersectionObserverEntry
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
JSM JSVal -> [JSM JSVal] -> JSM JSVal
forall constructor args.
(MakeObject constructor, MakeArgs args) =>
constructor -> args -> JSM JSVal
new (String -> JSM JSVal
forall a. ToJSString a => a -> JSM JSVal
jsg String
"IntersectionObserverEntry")
[IntersectionObserverEntryInit -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal IntersectionObserverEntryInit
intersectionObserverEntryInit])
getTime ::
(MonadDOM m) => IntersectionObserverEntry -> m DOMHighResTimeStamp
getTime :: forall (m :: * -> *).
MonadDOM m =>
IntersectionObserverEntry -> m DOMHighResTimeStamp
getTime IntersectionObserverEntry
self = DOM DOMHighResTimeStamp -> m DOMHighResTimeStamp
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IntersectionObserverEntry
self IntersectionObserverEntry
-> Getting (JSM JSVal) IntersectionObserverEntry (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter IntersectionObserverEntry (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"time") JSM JSVal
-> (JSVal -> DOM DOMHighResTimeStamp) -> DOM DOMHighResTimeStamp
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM DOMHighResTimeStamp
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)
getRootBounds ::
(MonadDOM m) => IntersectionObserverEntry -> m DOMRectReadOnly
getRootBounds :: forall (m :: * -> *).
MonadDOM m =>
IntersectionObserverEntry -> m DOMRectReadOnly
getRootBounds IntersectionObserverEntry
self
= DOM DOMRectReadOnly -> m DOMRectReadOnly
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IntersectionObserverEntry
self IntersectionObserverEntry
-> Getting (JSM JSVal) IntersectionObserverEntry (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter IntersectionObserverEntry (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"rootBounds") JSM JSVal -> (JSVal -> DOM DOMRectReadOnly) -> DOM DOMRectReadOnly
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM DOMRectReadOnly
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)
getBoundingClientRect ::
(MonadDOM m) => IntersectionObserverEntry -> m DOMRectReadOnly
getBoundingClientRect :: forall (m :: * -> *).
MonadDOM m =>
IntersectionObserverEntry -> m DOMRectReadOnly
getBoundingClientRect IntersectionObserverEntry
self
= DOM DOMRectReadOnly -> m DOMRectReadOnly
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
((IntersectionObserverEntry
self IntersectionObserverEntry
-> Getting (JSM JSVal) IntersectionObserverEntry (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter IntersectionObserverEntry (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"boundingClientRect") JSM JSVal -> (JSVal -> DOM DOMRectReadOnly) -> DOM DOMRectReadOnly
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM DOMRectReadOnly
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)
getIntersectionRect ::
(MonadDOM m) => IntersectionObserverEntry -> m DOMRectReadOnly
getIntersectionRect :: forall (m :: * -> *).
MonadDOM m =>
IntersectionObserverEntry -> m DOMRectReadOnly
getIntersectionRect IntersectionObserverEntry
self
= DOM DOMRectReadOnly -> m DOMRectReadOnly
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IntersectionObserverEntry
self IntersectionObserverEntry
-> Getting (JSM JSVal) IntersectionObserverEntry (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter IntersectionObserverEntry (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"intersectionRect") JSM JSVal -> (JSVal -> DOM DOMRectReadOnly) -> DOM DOMRectReadOnly
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM DOMRectReadOnly
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)
getIntersectionRatio ::
(MonadDOM m) => IntersectionObserverEntry -> m Double
getIntersectionRatio :: forall (m :: * -> *).
MonadDOM m =>
IntersectionObserverEntry -> m DOMHighResTimeStamp
getIntersectionRatio IntersectionObserverEntry
self
= DOM DOMHighResTimeStamp -> m DOMHighResTimeStamp
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IntersectionObserverEntry
self IntersectionObserverEntry
-> Getting (JSM JSVal) IntersectionObserverEntry (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter IntersectionObserverEntry (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"intersectionRatio") JSM JSVal
-> (JSVal -> DOM DOMHighResTimeStamp) -> DOM DOMHighResTimeStamp
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM DOMHighResTimeStamp
forall value. ToJSVal value => value -> DOM DOMHighResTimeStamp
valToNumber)
getTarget :: (MonadDOM m) => IntersectionObserverEntry -> m Element
getTarget :: forall (m :: * -> *).
MonadDOM m =>
IntersectionObserverEntry -> m Element
getTarget IntersectionObserverEntry
self
= DOM Element -> m Element
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IntersectionObserverEntry
self IntersectionObserverEntry
-> Getting (JSM JSVal) IntersectionObserverEntry (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter IntersectionObserverEntry (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"target") JSM JSVal -> (JSVal -> DOM Element) -> DOM Element
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM Element
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)