{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.SVGFilterPrimitiveStandardAttributes
       (getX, getY, getWidth, getHeight, getResult,
        SVGFilterPrimitiveStandardAttributes(..),
        gTypeSVGFilterPrimitiveStandardAttributes,
        IsSVGFilterPrimitiveStandardAttributes,
        toSVGFilterPrimitiveStandardAttributes)
       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/SVGFilterPrimitiveStandardAttributes.x Mozilla SVGFilterPrimitiveStandardAttributes.x documentation> 
getX ::
     (MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
       self -> m SVGAnimatedLength
getX :: forall (m :: * -> *) self.
(MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
self -> m SVGAnimatedLength
getX self
self
  = DOM SVGAnimatedLength -> m SVGAnimatedLength
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((self -> SVGFilterPrimitiveStandardAttributes
forall o.
IsSVGFilterPrimitiveStandardAttributes o =>
o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes self
self) SVGFilterPrimitiveStandardAttributes
-> Getting
     (JSM JSVal) SVGFilterPrimitiveStandardAttributes (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter
     SVGFilterPrimitiveStandardAttributes (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"x") JSM JSVal
-> (JSVal -> DOM SVGAnimatedLength) -> DOM SVGAnimatedLength
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 SVGAnimatedLength
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFilterPrimitiveStandardAttributes.y Mozilla SVGFilterPrimitiveStandardAttributes.y documentation> 
getY ::
     (MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
       self -> m SVGAnimatedLength
getY :: forall (m :: * -> *) self.
(MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
self -> m SVGAnimatedLength
getY self
self
  = DOM SVGAnimatedLength -> m SVGAnimatedLength
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((self -> SVGFilterPrimitiveStandardAttributes
forall o.
IsSVGFilterPrimitiveStandardAttributes o =>
o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes self
self) SVGFilterPrimitiveStandardAttributes
-> Getting
     (JSM JSVal) SVGFilterPrimitiveStandardAttributes (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter
     SVGFilterPrimitiveStandardAttributes (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"y") JSM JSVal
-> (JSVal -> DOM SVGAnimatedLength) -> DOM SVGAnimatedLength
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 SVGAnimatedLength
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFilterPrimitiveStandardAttributes.width Mozilla SVGFilterPrimitiveStandardAttributes.width documentation> 
getWidth ::
         (MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
           self -> m SVGAnimatedLength
getWidth :: forall (m :: * -> *) self.
(MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
self -> m SVGAnimatedLength
getWidth self
self
  = DOM SVGAnimatedLength -> m SVGAnimatedLength
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((self -> SVGFilterPrimitiveStandardAttributes
forall o.
IsSVGFilterPrimitiveStandardAttributes o =>
o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes self
self) SVGFilterPrimitiveStandardAttributes
-> Getting
     (JSM JSVal) SVGFilterPrimitiveStandardAttributes (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter
     SVGFilterPrimitiveStandardAttributes (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"width") JSM JSVal
-> (JSVal -> DOM SVGAnimatedLength) -> DOM SVGAnimatedLength
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 SVGAnimatedLength
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFilterPrimitiveStandardAttributes.height Mozilla SVGFilterPrimitiveStandardAttributes.height documentation> 
getHeight ::
          (MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
            self -> m SVGAnimatedLength
getHeight :: forall (m :: * -> *) self.
(MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
self -> m SVGAnimatedLength
getHeight self
self
  = DOM SVGAnimatedLength -> m SVGAnimatedLength
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((self -> SVGFilterPrimitiveStandardAttributes
forall o.
IsSVGFilterPrimitiveStandardAttributes o =>
o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes self
self) SVGFilterPrimitiveStandardAttributes
-> Getting
     (JSM JSVal) SVGFilterPrimitiveStandardAttributes (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter
     SVGFilterPrimitiveStandardAttributes (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"height") JSM JSVal
-> (JSVal -> DOM SVGAnimatedLength) -> DOM SVGAnimatedLength
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 SVGAnimatedLength
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGFilterPrimitiveStandardAttributes.result Mozilla SVGFilterPrimitiveStandardAttributes.result documentation> 
getResult ::
          (MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
            self -> m SVGAnimatedString
getResult :: forall (m :: * -> *) self.
(MonadDOM m, IsSVGFilterPrimitiveStandardAttributes self) =>
self -> m SVGAnimatedString
getResult self
self
  = DOM SVGAnimatedString -> m SVGAnimatedString
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((self -> SVGFilterPrimitiveStandardAttributes
forall o.
IsSVGFilterPrimitiveStandardAttributes o =>
o -> SVGFilterPrimitiveStandardAttributes
toSVGFilterPrimitiveStandardAttributes self
self) SVGFilterPrimitiveStandardAttributes
-> Getting
     (JSM JSVal) SVGFilterPrimitiveStandardAttributes (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String
-> IndexPreservingGetter
     SVGFilterPrimitiveStandardAttributes (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"result") JSM JSVal
-> (JSVal -> DOM SVGAnimatedString) -> DOM SVGAnimatedString
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 SVGAnimatedString
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)