{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.SVGURIReference
       (getHref, SVGURIReference(..), gTypeSVGURIReference,
        IsSVGURIReference, toSVGURIReference)
       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/SVGURIReference.href Mozilla SVGURIReference.href documentation> 
getHref ::
        (MonadDOM m, IsSVGURIReference self) => self -> m SVGAnimatedString
getHref :: self -> m SVGAnimatedString
getHref self
self
  = DOM SVGAnimatedString -> m SVGAnimatedString
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((self -> SVGURIReference
forall o. IsSVGURIReference o => o -> SVGURIReference
toSVGURIReference self
self) SVGURIReference
-> Getting (JSM JSVal) SVGURIReference (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter SVGURIReference (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"href") 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)