{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.SVGGlyphRefElement
       (setGlyphRef, getGlyphRef, setFormat, getFormat, setX, getX, setY,
        getY, setDx, getDx, setDy, getDy, SVGGlyphRefElement(..),
        gTypeSVGGlyphRefElement)
       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/SVGGlyphRefElement.glyphRef Mozilla SVGGlyphRefElement.glyphRef documentation> 
setGlyphRef ::
            (MonadDOM m, ToJSString val) => SVGGlyphRefElement -> val -> m ()
setGlyphRef :: forall (m :: * -> *) val.
(MonadDOM m, ToJSString val) =>
SVGGlyphRefElement -> val -> m ()
setGlyphRef SVGGlyphRefElement
self val
val
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (DOM ()) SVGGlyphRefElement (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. String
-> 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 String
"glyphRef" (val -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal val
val))

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

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.format Mozilla SVGGlyphRefElement.format documentation> 
setFormat ::
          (MonadDOM m, ToJSString val) => SVGGlyphRefElement -> val -> m ()
setFormat :: forall (m :: * -> *) val.
(MonadDOM m, ToJSString val) =>
SVGGlyphRefElement -> val -> m ()
setFormat SVGGlyphRefElement
self val
val = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (DOM ()) SVGGlyphRefElement (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. String
-> 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 String
"format" (val -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal val
val))

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

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.x Mozilla SVGGlyphRefElement.x documentation> 
setX :: (MonadDOM m) => SVGGlyphRefElement -> Float -> m ()
setX :: forall (m :: * -> *).
MonadDOM m =>
SVGGlyphRefElement -> Float -> m ()
setX SVGGlyphRefElement
self Float
val = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (DOM ()) SVGGlyphRefElement (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. String
-> 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 String
"x" (Float -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Float
val))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.x Mozilla SVGGlyphRefElement.x documentation> 
getX :: (MonadDOM m) => SVGGlyphRefElement -> m Float
getX :: forall (m :: * -> *). MonadDOM m => SVGGlyphRefElement -> m Float
getX SVGGlyphRefElement
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
<$> ((SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (JSM JSVal) SVGGlyphRefElement (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter SVGGlyphRefElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"x") JSM JSVal -> (JSVal -> JSM Double) -> JSM Double
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM Double
forall value. ToJSVal value => value -> JSM Double
valToNumber))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.y Mozilla SVGGlyphRefElement.y documentation> 
setY :: (MonadDOM m) => SVGGlyphRefElement -> Float -> m ()
setY :: forall (m :: * -> *).
MonadDOM m =>
SVGGlyphRefElement -> Float -> m ()
setY SVGGlyphRefElement
self Float
val = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (DOM ()) SVGGlyphRefElement (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. String
-> 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 String
"y" (Float -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Float
val))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.y Mozilla SVGGlyphRefElement.y documentation> 
getY :: (MonadDOM m) => SVGGlyphRefElement -> m Float
getY :: forall (m :: * -> *). MonadDOM m => SVGGlyphRefElement -> m Float
getY SVGGlyphRefElement
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
<$> ((SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (JSM JSVal) SVGGlyphRefElement (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter SVGGlyphRefElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"y") JSM JSVal -> (JSVal -> JSM Double) -> JSM Double
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM Double
forall value. ToJSVal value => value -> JSM Double
valToNumber))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.dx Mozilla SVGGlyphRefElement.dx documentation> 
setDx :: (MonadDOM m) => SVGGlyphRefElement -> Float -> m ()
setDx :: forall (m :: * -> *).
MonadDOM m =>
SVGGlyphRefElement -> Float -> m ()
setDx SVGGlyphRefElement
self Float
val = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (DOM ()) SVGGlyphRefElement (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. String
-> 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 String
"dx" (Float -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Float
val))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.dx Mozilla SVGGlyphRefElement.dx documentation> 
getDx :: (MonadDOM m) => SVGGlyphRefElement -> m Float
getDx :: forall (m :: * -> *). MonadDOM m => SVGGlyphRefElement -> m Float
getDx SVGGlyphRefElement
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
<$> ((SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (JSM JSVal) SVGGlyphRefElement (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter SVGGlyphRefElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"dx") JSM JSVal -> (JSVal -> JSM Double) -> JSM Double
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM Double
forall value. ToJSVal value => value -> JSM Double
valToNumber))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.dy Mozilla SVGGlyphRefElement.dy documentation> 
setDy :: (MonadDOM m) => SVGGlyphRefElement -> Float -> m ()
setDy :: forall (m :: * -> *).
MonadDOM m =>
SVGGlyphRefElement -> Float -> m ()
setDy SVGGlyphRefElement
self Float
val = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (DOM ()) SVGGlyphRefElement (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. String
-> 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 String
"dy" (Float -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Float
val))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/SVGGlyphRefElement.dy Mozilla SVGGlyphRefElement.dy documentation> 
getDy :: (MonadDOM m) => SVGGlyphRefElement -> m Float
getDy :: forall (m :: * -> *). MonadDOM m => SVGGlyphRefElement -> m Float
getDy SVGGlyphRefElement
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
<$> ((SVGGlyphRefElement
self SVGGlyphRefElement
-> Getting (JSM JSVal) SVGGlyphRefElement (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter SVGGlyphRefElement (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"dy") JSM JSVal -> (JSVal -> JSM Double) -> JSM Double
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM Double
forall value. ToJSVal value => value -> JSM Double
valToNumber))