module Data.DOM.Event
       (stopPropagation, preventDefault, initEvent, cCAPTURING_PHASE,
        cAT_TARGET, cBUBBLING_PHASE, get'type, getm'type, get'target,
        getm'target, get'currentTarget, getm'currentTarget, get'eventPhase,
        getm'eventPhase, get'bubbles, getm'bubbles, get'cancelable,
        getm'cancelable, get'timeStamp, getm'timeStamp)
       where
import Data.DOM.Events
import Control.Monad
import BrownPLT.JavaScript
import Data.DOM.WBTypes
import Data.DOM.Views
import Data.DOM.Dom
import Data.DOM.Document (createElement)
 
stopPropagation ::
                (Monad mn, CEvent this) => Expression this -> mn (Expression ())
stopPropagation thisp
  = do let et = undefined :: ()
       let r = DotRef et (thisp /\ et) (Id et "stopPropagation")
       return (CallExpr et r [])
 
preventDefault ::
               (Monad mn, CEvent this) => Expression this -> mn (Expression ())
preventDefault thisp
  = do let et = undefined :: ()
       let r = DotRef et (thisp /\ et) (Id et "preventDefault")
       return (CallExpr et r [])
 
initEvent ::
          (Monad mn, CEvent this) =>
            Expression String ->
              Expression Bool ->
                Expression Bool -> Expression this -> mn (Expression ())
initEvent a b c thisp
  = do let et = undefined :: ()
       let r = DotRef et (thisp /\ et) (Id et "initEvent")
       return (CallExpr et r [a /\ et, b /\ et, c /\ et])
cCAPTURING_PHASE = 1
cAT_TARGET = 2
cBUBBLING_PHASE = 3
 
get'type ::
         (Monad mn, CEvent this) =>
           Expression this -> mn (Expression String)
get'type thisp
  = do let et = undefined :: String
       let r = DotRef et (thisp /\ et) (Id et "type")
       return r
 
getm'type ::
          (Monad mn, CEvent this) =>
            Expression this -> mn (Expression String)
getm'type = get'type
 
get'target ::
           (Monad mn, CEvent this, CEventTarget zz) =>
             Expression this -> mn (Expression zz)
get'target thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "target")
       return r
 
getm'target ::
            (Monad mn, CEvent this) =>
              Expression this -> mn (Expression TEventTarget)
getm'target = get'target
 
get'currentTarget ::
                  (Monad mn, CEvent this, CEventTarget zz) =>
                    Expression this -> mn (Expression zz)
get'currentTarget thisp
  = do let et = undefined :: zz
       let r = DotRef et (thisp /\ et) (Id et "currentTarget")
       return r
 
getm'currentTarget ::
                   (Monad mn, CEvent this) =>
                     Expression this -> mn (Expression TEventTarget)
getm'currentTarget = get'currentTarget
 
get'eventPhase ::
               (Monad mn, CEvent this) =>
                 Expression this -> mn (Expression Double)
get'eventPhase thisp
  = do let et = undefined :: Double
       let r = DotRef et (thisp /\ et) (Id et "eventPhase")
       return r
 
getm'eventPhase ::
                (Monad mn, CEvent this) =>
                  Expression this -> mn (Expression Double)
getm'eventPhase = get'eventPhase
 
get'bubbles ::
            (Monad mn, CEvent this) => Expression this -> mn (Expression Bool)
get'bubbles thisp
  = do let et = undefined :: Bool
       let r = DotRef et (thisp /\ et) (Id et "bubbles")
       return r
 
getm'bubbles ::
             (Monad mn, CEvent this) => Expression this -> mn (Expression Bool)
getm'bubbles = get'bubbles
 
get'cancelable ::
               (Monad mn, CEvent this) => Expression this -> mn (Expression Bool)
get'cancelable thisp
  = do let et = undefined :: Bool
       let r = DotRef et (thisp /\ et) (Id et "cancelable")
       return r
 
getm'cancelable ::
                (Monad mn, CEvent this) => Expression this -> mn (Expression Bool)
getm'cancelable = get'cancelable
 
get'timeStamp ::
              (Monad mn, CEvent this) =>
                Expression this -> mn (Expression Double)
get'timeStamp thisp
  = do let et = undefined :: Double
       let r = DotRef et (thisp /\ et) (Id et "timeStamp")
       return r
 
getm'timeStamp ::
               (Monad mn, CEvent this) =>
                 Expression this -> mn (Expression Double)
getm'timeStamp = get'timeStamp