module Data.DOM.CSSRule
       (cUNKNOWN_RULE, cSTYLE_RULE, cCHARSET_RULE, cIMPORT_RULE,
        cMEDIA_RULE, cFONT_FACE_RULE, cPAGE_RULE, get'type, getm'type,
        set'cssText, get'cssText, getm'cssText, get'parentStyleSheet,
        getm'parentStyleSheet, get'parentRule, getm'parentRule)
       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)
cUNKNOWN_RULE = 0
cSTYLE_RULE = 1
cCHARSET_RULE = 2
cIMPORT_RULE = 3
cMEDIA_RULE = 4
cFONT_FACE_RULE = 5
cPAGE_RULE = 6
 
get'type ::
         (Monad mn, CCSSRule this) =>
           Expression this -> mn (Expression Double)
get'type thisp
  = do let et = undefined :: Double
       let r = DotRef et (thisp /\ et) (Id et "type")
       return r
 
getm'type ::
          (Monad mn, CCSSRule this) =>
            Expression this -> mn (Expression Double)
getm'type = get'type
 
set'cssText ::
            (Monad mn, CCSSRule zz) =>
              Expression String -> Expression zz -> mn (Expression zz)
set'cssText = setjsProperty "cssText"
 
get'cssText ::
            (Monad mn, CCSSRule this) =>
              Expression this -> mn (Expression String)
get'cssText thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "cssText")
       return r
 
getm'cssText ::
             (Monad mn, CCSSRule this) =>
               Expression this -> mn (Expression String)
getm'cssText = get'cssText
 
get'parentStyleSheet ::
                     (Monad mn, CCSSRule this, CCSSStyleSheet zz) =>
                       Expression this -> mn (Expression zz)
get'parentStyleSheet thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "parentStyleSheet")
       return r
 
getm'parentStyleSheet ::
                      (Monad mn, CCSSRule this) =>
                        Expression this -> mn (Expression TCSSStyleSheet)
getm'parentStyleSheet = get'parentStyleSheet
 
get'parentRule ::
               (Monad mn, CCSSRule this, CCSSRule zz) =>
                 Expression this -> mn (Expression zz)
get'parentRule thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "parentRule")
       return r
 
getm'parentRule ::
                (Monad mn, CCSSRule this) =>
                  Expression this -> mn (Expression TCSSRule)
getm'parentRule = get'parentRule