{-# LANGUAGE PatternSynonyms, ForeignFunctionInterface, JavaScriptFFI #-} module GHCJS.DOM.JSFFI.Generated.SVGFEDropShadowElement (js_setStdDeviation, setStdDeviation, js_getIn1, getIn1, js_getDx, getDx, js_getDy, getDy, js_getStdDeviationX, getStdDeviationX, js_getStdDeviationY, getStdDeviationY, SVGFEDropShadowElement, castToSVGFEDropShadowElement, gTypeSVGFEDropShadowElement) 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, castRef) 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[\"setStdDeviation\"]($2, $3)" js_setStdDeviation :: JSRef SVGFEDropShadowElement -> Float -> Float -> IO () -- | setStdDeviation :: (MonadIO m) => SVGFEDropShadowElement -> Float -> Float -> m () setStdDeviation self stdDeviationX stdDeviationY = liftIO (js_setStdDeviation (unSVGFEDropShadowElement self) stdDeviationX stdDeviationY) foreign import javascript unsafe "$1[\"in1\"]" js_getIn1 :: JSRef SVGFEDropShadowElement -> IO (JSRef SVGAnimatedString) -- | getIn1 :: (MonadIO m) => SVGFEDropShadowElement -> m (Maybe SVGAnimatedString) getIn1 self = liftIO ((js_getIn1 (unSVGFEDropShadowElement self)) >>= fromJSRef) foreign import javascript unsafe "$1[\"dx\"]" js_getDx :: JSRef SVGFEDropShadowElement -> IO (JSRef SVGAnimatedNumber) -- | getDx :: (MonadIO m) => SVGFEDropShadowElement -> m (Maybe SVGAnimatedNumber) getDx self = liftIO ((js_getDx (unSVGFEDropShadowElement self)) >>= fromJSRef) foreign import javascript unsafe "$1[\"dy\"]" js_getDy :: JSRef SVGFEDropShadowElement -> IO (JSRef SVGAnimatedNumber) -- | getDy :: (MonadIO m) => SVGFEDropShadowElement -> m (Maybe SVGAnimatedNumber) getDy self = liftIO ((js_getDy (unSVGFEDropShadowElement self)) >>= fromJSRef) foreign import javascript unsafe "$1[\"stdDeviationX\"]" js_getStdDeviationX :: JSRef SVGFEDropShadowElement -> IO (JSRef SVGAnimatedNumber) -- | getStdDeviationX :: (MonadIO m) => SVGFEDropShadowElement -> m (Maybe SVGAnimatedNumber) getStdDeviationX self = liftIO ((js_getStdDeviationX (unSVGFEDropShadowElement self)) >>= fromJSRef) foreign import javascript unsafe "$1[\"stdDeviationY\"]" js_getStdDeviationY :: JSRef SVGFEDropShadowElement -> IO (JSRef SVGAnimatedNumber) -- | getStdDeviationY :: (MonadIO m) => SVGFEDropShadowElement -> m (Maybe SVGAnimatedNumber) getStdDeviationY self = liftIO ((js_getStdDeviationY (unSVGFEDropShadowElement self)) >>= fromJSRef)