{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.SVGPathSegLinetoVerticalRel
       (setY, getY, SVGPathSegLinetoVerticalRel(..),
        gTypeSVGPathSegLinetoVerticalRel)
       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/SVGPathSegLinetoVerticalRel.y Mozilla SVGPathSegLinetoVerticalRel.y documentation> 
setY ::
     (MonadDOM m) => SVGPathSegLinetoVerticalRel -> Float -> m ()
setY :: SVGPathSegLinetoVerticalRel -> Float -> m ()
setY SVGPathSegLinetoVerticalRel
self Float
val = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (SVGPathSegLinetoVerticalRel
self SVGPathSegLinetoVerticalRel
-> Getting (DOM ()) SVGPathSegLinetoVerticalRel (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. [Char]
-> JSM JSVal
-> forall o. MakeObject o => IndexPreservingGetter o (DOM ())
forall name val.
(ToJSString name, ToJSVal val) =>
name
-> val
-> forall o. MakeObject o => IndexPreservingGetter o (DOM ())
jss [Char]
"y" (Float -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Float
val))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGPathSegLinetoVerticalRel.y Mozilla SVGPathSegLinetoVerticalRel.y documentation> 
getY :: (MonadDOM m) => SVGPathSegLinetoVerticalRel -> m Float
getY :: SVGPathSegLinetoVerticalRel -> m Float
getY SVGPathSegLinetoVerticalRel
self
  = DOM Float -> m Float
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double -> Float) -> JSM Double -> DOM Float
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((SVGPathSegLinetoVerticalRel
self SVGPathSegLinetoVerticalRel
-> Getting (JSM JSVal) SVGPathSegLinetoVerticalRel (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char]
-> IndexPreservingGetter SVGPathSegLinetoVerticalRel (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"y") JSM JSVal -> (JSVal -> JSM Double) -> JSM Double
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM Double
forall value. ToJSVal value => value -> JSM Double
valToNumber))