module Data.DOM.CSSPrimitiveValue
       (setFloatValue, getFloatValue, setStringValue, getStringValue,
        getCounterValue, getRectValue, getRGBColorValue, cCSS_UNKNOWN,
        cCSS_NUMBER, cCSS_PERCENTAGE, cCSS_EMS, cCSS_EXS, cCSS_PX, cCSS_CM,
        cCSS_MM, cCSS_IN, cCSS_PT, cCSS_PC, cCSS_DEG, cCSS_RAD, cCSS_GRAD,
        cCSS_MS, cCSS_S, cCSS_HZ, cCSS_KHZ, cCSS_DIMENSION, cCSS_STRING,
        cCSS_URI, cCSS_IDENT, cCSS_ATTR, cCSS_COUNTER, cCSS_RECT,
        cCSS_RGBCOLOR, get'primitiveType, getm'primitiveType)
       where
import Data.DOM.Css
import Control.Monad
import WebBits.JavaScript
import Data.DOM.WBTypes
import Data.DOM.Views
import Data.DOM.Stylesheets
import Data.DOM.Dom
import Data.DOM.Document (createElement)
 
setFloatValue ::
              (Monad mn, CCSSPrimitiveValue this) =>
                Expression Double ->
                  Expression Double -> Expression this -> mn (Expression ())
setFloatValue a b thisp
  = do let et = undefined :: ()
       let r = DotRef et (thisp /\ et) (Id et "setFloatValue")
       return (CallExpr et r [a /\ et, b /\ et])
 
getFloatValue ::
              (Monad mn, CCSSPrimitiveValue this) =>
                Expression Double -> Expression this -> mn (Expression Double)
getFloatValue a thisp
  = do let et = undefined :: Double
       let r = DotRef et (thisp /\ et) (Id et "getFloatValue")
       return (CallExpr et r [a /\ et])
 
setStringValue ::
               (Monad mn, CCSSPrimitiveValue this) =>
                 Expression Double ->
                   Expression String -> Expression this -> mn (Expression ())
setStringValue a b thisp
  = do let et = undefined :: ()
       let r = DotRef et (thisp /\ et) (Id et "setStringValue")
       return (CallExpr et r [a /\ et, b /\ et])
 
getStringValue ::
               (Monad mn, CCSSPrimitiveValue this) =>
                 Expression this -> mn (Expression String)
getStringValue thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "getStringValue")
       return (CallExpr et r [])
 
getCounterValue ::
                (Monad mn, CCSSPrimitiveValue this, CCounter zz) =>
                  Expression this -> mn (Expression zz)
getCounterValue thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "getCounterValue")
       return (CallExpr et r [])
 
getRectValue ::
             (Monad mn, CCSSPrimitiveValue this, CRect zz) =>
               Expression this -> mn (Expression zz)
getRectValue thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "getRectValue")
       return (CallExpr et r [])
 
getRGBColorValue ::
                 (Monad mn, CCSSPrimitiveValue this, CRGBColor zz) =>
                   Expression this -> mn (Expression zz)
getRGBColorValue thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "getRGBColorValue")
       return (CallExpr et r [])
cCSS_UNKNOWN = 0
cCSS_NUMBER = 1
cCSS_PERCENTAGE = 2
cCSS_EMS = 3
cCSS_EXS = 4
cCSS_PX = 5
cCSS_CM = 6
cCSS_MM = 7
cCSS_IN = 8
cCSS_PT = 9
cCSS_PC = 10
cCSS_DEG = 11
cCSS_RAD = 12
cCSS_GRAD = 13
cCSS_MS = 14
cCSS_S = 15
cCSS_HZ = 16
cCSS_KHZ = 17
cCSS_DIMENSION = 18
cCSS_STRING = 19
cCSS_URI = 20
cCSS_IDENT = 21
cCSS_ATTR = 22
cCSS_COUNTER = 23
cCSS_RECT = 24
cCSS_RGBCOLOR = 25
 
get'primitiveType ::
                  (Monad mn, CCSSPrimitiveValue this) =>
                    Expression this -> mn (Expression Double)
get'primitiveType thisp
  = do let et = undefined :: Double
       let r = DotRef et (thisp /\ et) (Id et "primitiveType")
       return r
 
getm'primitiveType ::
                   (Monad mn, CCSSPrimitiveValue this) =>
                     Expression this -> mn (Expression Double)
getm'primitiveType = get'primitiveType