{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.SVGFESpecularLightingElement
       (getIn1, getSurfaceScale, getSpecularConstant, getSpecularExponent,
        SVGFESpecularLightingElement(..),
        gTypeSVGFESpecularLightingElement)
       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

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFESpecularLightingElement.in1 Mozilla SVGFESpecularLightingElement.in1 documentation> 
getIn1 ::
       (MonadDOM m) => SVGFESpecularLightingElement -> m SVGAnimatedString
getIn1 :: SVGFESpecularLightingElement -> m SVGAnimatedString
getIn1 SVGFESpecularLightingElement
self = DOM SVGAnimatedString -> m SVGAnimatedString
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((SVGFESpecularLightingElement
self SVGFESpecularLightingElement
-> Getting (JSM JSVal) SVGFESpecularLightingElement (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char]
-> IndexPreservingGetter SVGFESpecularLightingElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"in1") JSM JSVal
-> (JSVal -> DOM SVGAnimatedString) -> DOM SVGAnimatedString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM SVGAnimatedString
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFESpecularLightingElement.surfaceScale Mozilla SVGFESpecularLightingElement.surfaceScale documentation> 
getSurfaceScale ::
                (MonadDOM m) => SVGFESpecularLightingElement -> m SVGAnimatedNumber
getSurfaceScale :: SVGFESpecularLightingElement -> m SVGAnimatedNumber
getSurfaceScale SVGFESpecularLightingElement
self
  = DOM SVGAnimatedNumber -> m SVGAnimatedNumber
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((SVGFESpecularLightingElement
self SVGFESpecularLightingElement
-> Getting (JSM JSVal) SVGFESpecularLightingElement (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char]
-> IndexPreservingGetter SVGFESpecularLightingElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"surfaceScale") JSM JSVal
-> (JSVal -> DOM SVGAnimatedNumber) -> DOM SVGAnimatedNumber
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM SVGAnimatedNumber
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFESpecularLightingElement.specularConstant Mozilla SVGFESpecularLightingElement.specularConstant documentation> 
getSpecularConstant ::
                    (MonadDOM m) => SVGFESpecularLightingElement -> m SVGAnimatedNumber
getSpecularConstant :: SVGFESpecularLightingElement -> m SVGAnimatedNumber
getSpecularConstant SVGFESpecularLightingElement
self
  = DOM SVGAnimatedNumber -> m SVGAnimatedNumber
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((SVGFESpecularLightingElement
self SVGFESpecularLightingElement
-> Getting (JSM JSVal) SVGFESpecularLightingElement (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char]
-> IndexPreservingGetter SVGFESpecularLightingElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"specularConstant") JSM JSVal
-> (JSVal -> DOM SVGAnimatedNumber) -> DOM SVGAnimatedNumber
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM SVGAnimatedNumber
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFESpecularLightingElement.specularExponent Mozilla SVGFESpecularLightingElement.specularExponent documentation> 
getSpecularExponent ::
                    (MonadDOM m) => SVGFESpecularLightingElement -> m SVGAnimatedNumber
getSpecularExponent :: SVGFESpecularLightingElement -> m SVGAnimatedNumber
getSpecularExponent SVGFESpecularLightingElement
self
  = DOM SVGAnimatedNumber -> m SVGAnimatedNumber
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((SVGFESpecularLightingElement
self SVGFESpecularLightingElement
-> Getting (JSM JSVal) SVGFESpecularLightingElement (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char]
-> IndexPreservingGetter SVGFESpecularLightingElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"specularExponent") JSM JSVal
-> (JSVal -> DOM SVGAnimatedNumber) -> DOM SVGAnimatedNumber
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM SVGAnimatedNumber
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)