module Data.DOM.CSSImportRule
       (get'href, getm'href, get'media, getm'media, get'styleSheet,
        getm'styleSheet)
       where
import Data.DOM.Css
import Control.Monad
import BrownPLT.JavaScript
import Data.DOM.WBTypes
import Data.DOM.Views
import Data.DOM.Stylesheets
import Data.DOM.Dom
import Data.DOM.Document (createElement)
 
get'href ::
         (Monad mn, CCSSImportRule this) =>
           Expression this -> mn (Expression String)
get'href thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "href")
       return r
 
getm'href ::
          (Monad mn, CCSSImportRule this) =>
            Expression this -> mn (Expression String)
getm'href = get'href
 
get'media ::
          (Monad mn, CCSSImportRule this, CMediaList zz) =>
            Expression this -> mn (Expression zz)
get'media thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "media")
       return r
 
getm'media ::
           (Monad mn, CCSSImportRule this) =>
             Expression this -> mn (Expression TMediaList)
getm'media = get'media
 
get'styleSheet ::
               (Monad mn, CCSSImportRule this, CCSSStyleSheet zz) =>
                 Expression this -> mn (Expression zz)
get'styleSheet thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "styleSheet")
       return r
 
getm'styleSheet ::
                (Monad mn, CCSSImportRule this) =>
                  Expression this -> mn (Expression TCSSStyleSheet)
getm'styleSheet = get'styleSheet