{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.SVGPolygonElement
       (getPoints, getAnimatedPoints, SVGPolygonElement(..),
        gTypeSVGPolygonElement)
       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/SVGPolygonElement.points Mozilla SVGPolygonElement.points documentation> 
getPoints :: (MonadDOM m) => SVGPolygonElement -> m SVGPointList
getPoints :: forall (m :: * -> *).
MonadDOM m =>
SVGPolygonElement -> m SVGPointList
getPoints SVGPolygonElement
self
  = DOM SVGPointList -> m SVGPointList
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((SVGPolygonElement
self SVGPolygonElement
-> Getting (JSM JSVal) SVGPolygonElement (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter SVGPolygonElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"points") JSM JSVal -> (JSVal -> DOM SVGPointList) -> DOM SVGPointList
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 SVGPointList
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

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