{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.MutationRecord (js_getType, getType, js_getTarget, getTarget, js_getAddedNodes, getAddedNodes, js_getRemovedNodes, getRemovedNodes, js_getPreviousSibling, getPreviousSibling, js_getNextSibling, getNextSibling, js_getAttributeName, getAttributeName, js_getAttributeNamespace, getAttributeNamespace, js_getOldValue, getOldValue, MutationRecord, castToMutationRecord, gTypeMutationRecord) 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) 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[\"type\"]" js_getType :: MutationRecord -> IO JSString -- | getType :: (MonadIO m, FromJSString result) => MutationRecord -> m result getType self = liftIO (fromJSString <$> (js_getType (self))) foreign import javascript unsafe "$1[\"target\"]" js_getTarget :: MutationRecord -> IO (Nullable Node) -- | getTarget :: (MonadIO m) => MutationRecord -> m (Maybe Node) getTarget self = liftIO (nullableToMaybe <$> (js_getTarget (self))) foreign import javascript unsafe "$1[\"addedNodes\"]" js_getAddedNodes :: MutationRecord -> IO (Nullable NodeList) -- | getAddedNodes :: (MonadIO m) => MutationRecord -> m (Maybe NodeList) getAddedNodes self = liftIO (nullableToMaybe <$> (js_getAddedNodes (self))) foreign import javascript unsafe "$1[\"removedNodes\"]" js_getRemovedNodes :: MutationRecord -> IO (Nullable NodeList) -- | getRemovedNodes :: (MonadIO m) => MutationRecord -> m (Maybe NodeList) getRemovedNodes self = liftIO (nullableToMaybe <$> (js_getRemovedNodes (self))) foreign import javascript unsafe "$1[\"previousSibling\"]" js_getPreviousSibling :: MutationRecord -> IO (Nullable Node) -- | getPreviousSibling :: (MonadIO m) => MutationRecord -> m (Maybe Node) getPreviousSibling self = liftIO (nullableToMaybe <$> (js_getPreviousSibling (self))) foreign import javascript unsafe "$1[\"nextSibling\"]" js_getNextSibling :: MutationRecord -> IO (Nullable Node) -- | getNextSibling :: (MonadIO m) => MutationRecord -> m (Maybe Node) getNextSibling self = liftIO (nullableToMaybe <$> (js_getNextSibling (self))) foreign import javascript unsafe "$1[\"attributeName\"]" js_getAttributeName :: MutationRecord -> IO (Nullable JSString) -- | getAttributeName :: (MonadIO m, FromJSString result) => MutationRecord -> m (Maybe result) getAttributeName self = liftIO (fromMaybeJSString <$> (js_getAttributeName (self))) foreign import javascript unsafe "$1[\"attributeNamespace\"]" js_getAttributeNamespace :: MutationRecord -> IO (Nullable JSString) -- | getAttributeNamespace :: (MonadIO m, FromJSString result) => MutationRecord -> m (Maybe result) getAttributeNamespace self = liftIO (fromMaybeJSString <$> (js_getAttributeNamespace (self))) foreign import javascript unsafe "$1[\"oldValue\"]" js_getOldValue :: MutationRecord -> IO (Nullable JSString) -- | getOldValue :: (MonadIO m, FromJSString result) => MutationRecord -> m (Maybe result) getOldValue self = liftIO (fromMaybeJSString <$> (js_getOldValue (self)))