module Data.DOM.DocumentType
       (get'name, getm'name, get'entities, getm'entities, get'notations,
        getm'notations, get'publicId, getm'publicId, get'systemId,
        getm'systemId, get'internalSubset, getm'internalSubset)
       where
import Data.DOM.Dom
import Control.Monad
import WebBits.JavaScript
import Data.DOM.WBTypes
import Data.DOM.Document (createElement)
 
get'name ::
         (Monad mn, CDocumentType this) =>
           Expression this -> mn (Expression String)
get'name thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "name")
       return r
 
getm'name ::
          (Monad mn, CDocumentType this) =>
            Expression this -> mn (Expression String)
getm'name = get'name
 
get'entities ::
             (Monad mn, CDocumentType this, CNamedNodeMap zz) =>
               Expression this -> mn (Expression zz)
get'entities thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "entities")
       return r
 
getm'entities ::
              (Monad mn, CDocumentType this) =>
                Expression this -> mn (Expression TNamedNodeMap)
getm'entities = get'entities
 
get'notations ::
              (Monad mn, CDocumentType this, CNamedNodeMap zz) =>
                Expression this -> mn (Expression zz)
get'notations thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "notations")
       return r
 
getm'notations ::
               (Monad mn, CDocumentType this) =>
                 Expression this -> mn (Expression TNamedNodeMap)
getm'notations = get'notations
 
get'publicId ::
             (Monad mn, CDocumentType this) =>
               Expression this -> mn (Expression String)
get'publicId thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "publicId")
       return r
 
getm'publicId ::
              (Monad mn, CDocumentType this) =>
                Expression this -> mn (Expression String)
getm'publicId = get'publicId
 
get'systemId ::
             (Monad mn, CDocumentType this) =>
               Expression this -> mn (Expression String)
get'systemId thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "systemId")
       return r
 
getm'systemId ::
              (Monad mn, CDocumentType this) =>
                Expression this -> mn (Expression String)
getm'systemId = get'systemId
 
get'internalSubset ::
                   (Monad mn, CDocumentType this) =>
                     Expression this -> mn (Expression String)
get'internalSubset thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "internalSubset")
       return r
 
getm'internalSubset ::
                    (Monad mn, CDocumentType this) =>
                      Expression this -> mn (Expression String)
getm'internalSubset = get'internalSubset