{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.CSSStyleDeclaration
(getPropertyValue, getPropertyValue_, getPropertyCSSValue,
getPropertyCSSValue_, getPropertyCSSValueUnsafe,
getPropertyCSSValueUnchecked, removeProperty, removeProperty_,
getPropertyPriority, getPropertyPriority_,
getPropertyPriorityUnsafe, getPropertyPriorityUnchecked,
setProperty, item, item_, getPropertyShorthand,
getPropertyShorthand_, getPropertyShorthandUnsafe,
getPropertyShorthandUnchecked, isPropertyImplicit,
isPropertyImplicit_, setCssText, getCssText, getLength,
getParentRule, getParentRuleUnsafe, getParentRuleUnchecked,
CSSStyleDeclaration(..), gTypeCSSStyleDeclaration)
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
getPropertyValue ::
(MonadDOM m, ToJSString propertyName, FromJSString result) =>
CSSStyleDeclaration -> propertyName -> m result
getPropertyValue self propertyName
= liftDOM
((self ^. jsf "getPropertyValue" [toJSVal propertyName]) >>=
fromJSValUnchecked)
getPropertyValue_ ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> propertyName -> m ()
getPropertyValue_ self propertyName
= liftDOM
(void (self ^. jsf "getPropertyValue" [toJSVal propertyName]))
getPropertyCSSValue ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> propertyName -> m (Maybe CSSValue)
getPropertyCSSValue self propertyName
= liftDOM
((self ^. jsf "getPropertyCSSValue" [toJSVal propertyName]) >>=
fromJSVal)
getPropertyCSSValue_ ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> propertyName -> m ()
getPropertyCSSValue_ self propertyName
= liftDOM
(void (self ^. jsf "getPropertyCSSValue" [toJSVal propertyName]))
getPropertyCSSValueUnsafe ::
(MonadDOM m, ToJSString propertyName, HasCallStack) =>
CSSStyleDeclaration -> propertyName -> m CSSValue
getPropertyCSSValueUnsafe self propertyName
= liftDOM
(((self ^. jsf "getPropertyCSSValue" [toJSVal propertyName]) >>=
fromJSVal)
>>= maybe (Prelude.error "Nothing to return") return)
getPropertyCSSValueUnchecked ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> propertyName -> m CSSValue
getPropertyCSSValueUnchecked self propertyName
= liftDOM
((self ^. jsf "getPropertyCSSValue" [toJSVal propertyName]) >>=
fromJSValUnchecked)
removeProperty ::
(MonadDOM m, ToJSString propertyName, FromJSString result) =>
CSSStyleDeclaration -> propertyName -> m result
removeProperty self propertyName
= liftDOM
((self ^. jsf "removeProperty" [toJSVal propertyName]) >>=
fromJSValUnchecked)
removeProperty_ ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> propertyName -> m ()
removeProperty_ self propertyName
= liftDOM
(void (self ^. jsf "removeProperty" [toJSVal propertyName]))
getPropertyPriority ::
(MonadDOM m, ToJSString propertyName, FromJSString result) =>
CSSStyleDeclaration -> propertyName -> m (Maybe result)
getPropertyPriority self propertyName
= liftDOM
((self ^. jsf "getPropertyPriority" [toJSVal propertyName]) >>=
fromMaybeJSString)
getPropertyPriority_ ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> propertyName -> m ()
getPropertyPriority_ self propertyName
= liftDOM
(void (self ^. jsf "getPropertyPriority" [toJSVal propertyName]))
getPropertyPriorityUnsafe ::
(MonadDOM m, ToJSString propertyName, HasCallStack,
FromJSString result) =>
CSSStyleDeclaration -> propertyName -> m result
getPropertyPriorityUnsafe self propertyName
= liftDOM
(((self ^. jsf "getPropertyPriority" [toJSVal propertyName]) >>=
fromMaybeJSString)
>>= maybe (Prelude.error "Nothing to return") return)
getPropertyPriorityUnchecked ::
(MonadDOM m, ToJSString propertyName, FromJSString result) =>
CSSStyleDeclaration -> propertyName -> m result
getPropertyPriorityUnchecked self propertyName
= liftDOM
((self ^. jsf "getPropertyPriority" [toJSVal propertyName]) >>=
fromJSValUnchecked)
setProperty ::
(MonadDOM m, ToJSString propertyName, ToJSString value,
ToJSString priority) =>
CSSStyleDeclaration ->
propertyName -> value -> Maybe priority -> m ()
setProperty self propertyName value priority
= liftDOM
(void
(self ^. jsf "setProperty"
[toJSVal propertyName, toJSVal value, toJSVal priority]))
item ::
(MonadDOM m, FromJSString result) =>
CSSStyleDeclaration -> Word -> m result
item self index
= liftDOM
((self ^. jsf "item" [toJSVal index]) >>= fromJSValUnchecked)
item_ :: (MonadDOM m) => CSSStyleDeclaration -> Word -> m ()
item_ self index
= liftDOM (void (self ^. jsf "item" [toJSVal index]))
getPropertyShorthand ::
(MonadDOM m, ToJSString propertyName, FromJSString result) =>
CSSStyleDeclaration -> Maybe propertyName -> m (Maybe result)
getPropertyShorthand self propertyName
= liftDOM
((self ^. jsf "getPropertyShorthand" [toJSVal propertyName]) >>=
fromMaybeJSString)
getPropertyShorthand_ ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> Maybe propertyName -> m ()
getPropertyShorthand_ self propertyName
= liftDOM
(void (self ^. jsf "getPropertyShorthand" [toJSVal propertyName]))
getPropertyShorthandUnsafe ::
(MonadDOM m, ToJSString propertyName, HasCallStack,
FromJSString result) =>
CSSStyleDeclaration -> Maybe propertyName -> m result
getPropertyShorthandUnsafe self propertyName
= liftDOM
(((self ^. jsf "getPropertyShorthand" [toJSVal propertyName]) >>=
fromMaybeJSString)
>>= maybe (Prelude.error "Nothing to return") return)
getPropertyShorthandUnchecked ::
(MonadDOM m, ToJSString propertyName, FromJSString result) =>
CSSStyleDeclaration -> Maybe propertyName -> m result
getPropertyShorthandUnchecked self propertyName
= liftDOM
((self ^. jsf "getPropertyShorthand" [toJSVal propertyName]) >>=
fromJSValUnchecked)
isPropertyImplicit ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> Maybe propertyName -> m Bool
isPropertyImplicit self propertyName
= liftDOM
((self ^. jsf "isPropertyImplicit" [toJSVal propertyName]) >>=
valToBool)
isPropertyImplicit_ ::
(MonadDOM m, ToJSString propertyName) =>
CSSStyleDeclaration -> Maybe propertyName -> m ()
isPropertyImplicit_ self propertyName
= liftDOM
(void (self ^. jsf "isPropertyImplicit" [toJSVal propertyName]))
setCssText ::
(MonadDOM m, ToJSString val) => CSSStyleDeclaration -> val -> m ()
setCssText self val = liftDOM (self ^. jss "cssText" (toJSVal val))
getCssText ::
(MonadDOM m, FromJSString result) =>
CSSStyleDeclaration -> m result
getCssText self
= liftDOM ((self ^. js "cssText") >>= fromJSValUnchecked)
getLength :: (MonadDOM m) => CSSStyleDeclaration -> m Word
getLength self
= liftDOM (round <$> ((self ^. js "length") >>= valToNumber))
getParentRule ::
(MonadDOM m) => CSSStyleDeclaration -> m (Maybe CSSRule)
getParentRule self
= liftDOM ((self ^. js "parentRule") >>= fromJSVal)
getParentRuleUnsafe ::
(MonadDOM m, HasCallStack) => CSSStyleDeclaration -> m CSSRule
getParentRuleUnsafe self
= liftDOM
(((self ^. js "parentRule") >>= fromJSVal) >>=
maybe (Prelude.error "Nothing to return") return)
getParentRuleUnchecked ::
(MonadDOM m) => CSSStyleDeclaration -> m CSSRule
getParentRuleUnchecked self
= liftDOM ((self ^. js "parentRule") >>= fromJSValUnchecked)