{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.WebKit2WebExtension.Objects.DOMMouseEvent
    ( 

-- * Exported types
    DOMMouseEvent(..)                       ,
    IsDOMMouseEvent                         ,
    toDOMMouseEvent                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [initEvent]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:initEvent"), [initMouseEvent]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:initMouseEvent"), [initUiEvent]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:initUiEvent"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [preventDefault]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:preventDefault"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [stopPropagation]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:stopPropagation"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAltKey]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getAltKey"), [getBubbles]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getBubbles"), [getButton]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getButton"), [getCancelBubble]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getCancelBubble"), [getCancelable]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getCancelable"), [getCharCode]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getCharCode"), [getClientX]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getClientX"), [getClientY]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getClientY"), [getCtrlKey]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getCtrlKey"), [getCurrentTarget]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getCurrentTarget"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDetail]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getDetail"), [getEventPhase]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getEventPhase"), [getEventType]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getEventType"), [getFromElement]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getFromElement"), [getKeyCode]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getKeyCode"), [getLayerX]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getLayerX"), [getLayerY]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getLayerY"), [getMetaKey]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getMetaKey"), [getOffsetX]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getOffsetX"), [getOffsetY]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getOffsetY"), [getPageX]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getPageX"), [getPageY]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getPageY"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRelatedTarget]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getRelatedTarget"), [getReturnValue]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getReturnValue"), [getScreenX]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getScreenX"), [getScreenY]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getScreenY"), [getShiftKey]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getShiftKey"), [getSrcElement]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getSrcElement"), [getTarget]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getTarget"), [getTimeStamp]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getTimeStamp"), [getToElement]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getToElement"), [getView]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getView"), [getX]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getX"), [getY]("GI.WebKit2WebExtension.Objects.DOMMouseEvent#g:method:getY").
-- 
-- ==== Setters
-- [setCancelBubble]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:setCancelBubble"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReturnValue]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:setReturnValue").

#if defined(ENABLE_OVERLOADING)
    ResolveDOMMouseEventMethod              ,
#endif

-- ** getAltKey #method:getAltKey#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetAltKeyMethodInfo        ,
#endif
    dOMMouseEventGetAltKey                  ,


-- ** getButton #method:getButton#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetButtonMethodInfo        ,
#endif
    dOMMouseEventGetButton                  ,


-- ** getClientX #method:getClientX#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetClientXMethodInfo       ,
#endif
    dOMMouseEventGetClientX                 ,


-- ** getClientY #method:getClientY#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetClientYMethodInfo       ,
#endif
    dOMMouseEventGetClientY                 ,


-- ** getCtrlKey #method:getCtrlKey#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetCtrlKeyMethodInfo       ,
#endif
    dOMMouseEventGetCtrlKey                 ,


-- ** getFromElement #method:getFromElement#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetFromElementMethodInfo   ,
#endif
    dOMMouseEventGetFromElement             ,


-- ** getMetaKey #method:getMetaKey#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetMetaKeyMethodInfo       ,
#endif
    dOMMouseEventGetMetaKey                 ,


-- ** getOffsetX #method:getOffsetX#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetOffsetXMethodInfo       ,
#endif
    dOMMouseEventGetOffsetX                 ,


-- ** getOffsetY #method:getOffsetY#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetOffsetYMethodInfo       ,
#endif
    dOMMouseEventGetOffsetY                 ,


-- ** getRelatedTarget #method:getRelatedTarget#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetRelatedTargetMethodInfo ,
#endif
    dOMMouseEventGetRelatedTarget           ,


-- ** getScreenX #method:getScreenX#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetScreenXMethodInfo       ,
#endif
    dOMMouseEventGetScreenX                 ,


-- ** getScreenY #method:getScreenY#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetScreenYMethodInfo       ,
#endif
    dOMMouseEventGetScreenY                 ,


-- ** getShiftKey #method:getShiftKey#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetShiftKeyMethodInfo      ,
#endif
    dOMMouseEventGetShiftKey                ,


-- ** getToElement #method:getToElement#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetToElementMethodInfo     ,
#endif
    dOMMouseEventGetToElement               ,


-- ** getX #method:getX#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetXMethodInfo             ,
#endif
    dOMMouseEventGetX                       ,


-- ** getY #method:getY#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventGetYMethodInfo             ,
#endif
    dOMMouseEventGetY                       ,


-- ** initMouseEvent #method:initMouseEvent#

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventInitMouseEventMethodInfo   ,
#endif
    dOMMouseEventInitMouseEvent             ,




 -- * Properties


-- ** altKey #attr:altKey#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventAltKeyPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventAltKey                     ,
#endif
    getDOMMouseEventAltKey                  ,


-- ** button #attr:button#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventButtonPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventButton                     ,
#endif
    getDOMMouseEventButton                  ,


-- ** clientX #attr:clientX#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventClientXPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventClientX                    ,
#endif
    getDOMMouseEventClientX                 ,


-- ** clientY #attr:clientY#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventClientYPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventClientY                    ,
#endif
    getDOMMouseEventClientY                 ,


-- ** ctrlKey #attr:ctrlKey#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventCtrlKeyPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventCtrlKey                    ,
#endif
    getDOMMouseEventCtrlKey                 ,


-- ** fromElement #attr:fromElement#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventFromElementPropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventFromElement                ,
#endif
    getDOMMouseEventFromElement             ,


-- ** metaKey #attr:metaKey#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventMetaKeyPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventMetaKey                    ,
#endif
    getDOMMouseEventMetaKey                 ,


-- ** offsetX #attr:offsetX#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventOffsetXPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventOffsetX                    ,
#endif
    getDOMMouseEventOffsetX                 ,


-- ** offsetY #attr:offsetY#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventOffsetYPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventOffsetY                    ,
#endif
    getDOMMouseEventOffsetY                 ,


-- ** relatedTarget #attr:relatedTarget#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventRelatedTargetPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventRelatedTarget              ,
#endif
    getDOMMouseEventRelatedTarget           ,


-- ** screenX #attr:screenX#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventScreenXPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventScreenX                    ,
#endif
    getDOMMouseEventScreenX                 ,


-- ** screenY #attr:screenY#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventScreenYPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventScreenY                    ,
#endif
    getDOMMouseEventScreenY                 ,


-- ** shiftKey #attr:shiftKey#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventShiftKeyPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventShiftKey                   ,
#endif
    getDOMMouseEventShiftKey                ,


-- ** toElement #attr:toElement#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventToElementPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventToElement                  ,
#endif
    getDOMMouseEventToElement               ,


-- ** x #attr:x#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventXPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventX                          ,
#endif
    getDOMMouseEventX                       ,


-- ** y #attr:y#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DOMMouseEventYPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMouseEventY                          ,
#endif
    getDOMMouseEventY                       ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Interfaces.DOMEventTarget as WebKit2WebExtension.DOMEventTarget
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMDOMWindow as WebKit2WebExtension.DOMDOMWindow
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMEvent as WebKit2WebExtension.DOMEvent
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMNode as WebKit2WebExtension.DOMNode
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMUIEvent as WebKit2WebExtension.DOMUIEvent

-- | Memory-managed wrapper type.
newtype DOMMouseEvent = DOMMouseEvent (SP.ManagedPtr DOMMouseEvent)
    deriving (DOMMouseEvent -> DOMMouseEvent -> Bool
(DOMMouseEvent -> DOMMouseEvent -> Bool)
-> (DOMMouseEvent -> DOMMouseEvent -> Bool) -> Eq DOMMouseEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DOMMouseEvent -> DOMMouseEvent -> Bool
$c/= :: DOMMouseEvent -> DOMMouseEvent -> Bool
== :: DOMMouseEvent -> DOMMouseEvent -> Bool
$c== :: DOMMouseEvent -> DOMMouseEvent -> Bool
Eq)

instance SP.ManagedPtrNewtype DOMMouseEvent where
    toManagedPtr :: DOMMouseEvent -> ManagedPtr DOMMouseEvent
toManagedPtr (DOMMouseEvent ManagedPtr DOMMouseEvent
p) = ManagedPtr DOMMouseEvent
p

foreign import ccall "webkit_dom_mouse_event_get_type"
    c_webkit_dom_mouse_event_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMMouseEvent where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_mouse_event_get_type

instance B.Types.GObject DOMMouseEvent

-- | Type class for types which can be safely cast to `DOMMouseEvent`, for instance with `toDOMMouseEvent`.
class (SP.GObject o, O.IsDescendantOf DOMMouseEvent o) => IsDOMMouseEvent o
instance (SP.GObject o, O.IsDescendantOf DOMMouseEvent o) => IsDOMMouseEvent o

instance O.HasParentTypes DOMMouseEvent
type instance O.ParentTypes DOMMouseEvent = '[WebKit2WebExtension.DOMUIEvent.DOMUIEvent, WebKit2WebExtension.DOMEvent.DOMEvent, WebKit2WebExtension.DOMObject.DOMObject, GObject.Object.Object]

-- | Cast to `DOMMouseEvent`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDOMMouseEvent :: (MIO.MonadIO m, IsDOMMouseEvent o) => o -> m DOMMouseEvent
toDOMMouseEvent :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m DOMMouseEvent
toDOMMouseEvent = IO DOMMouseEvent -> m DOMMouseEvent
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DOMMouseEvent -> m DOMMouseEvent)
-> (o -> IO DOMMouseEvent) -> o -> m DOMMouseEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DOMMouseEvent -> DOMMouseEvent)
-> o -> IO DOMMouseEvent
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DOMMouseEvent -> DOMMouseEvent
DOMMouseEvent

-- | Convert 'DOMMouseEvent' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe DOMMouseEvent) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_dom_mouse_event_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DOMMouseEvent -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DOMMouseEvent
P.Nothing = Ptr GValue -> Ptr DOMMouseEvent -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DOMMouseEvent
forall a. Ptr a
FP.nullPtr :: FP.Ptr DOMMouseEvent)
    gvalueSet_ Ptr GValue
gv (P.Just DOMMouseEvent
obj) = DOMMouseEvent -> (Ptr DOMMouseEvent -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMMouseEvent
obj (Ptr GValue -> Ptr DOMMouseEvent -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DOMMouseEvent)
gvalueGet_ Ptr GValue
gv = do
        Ptr DOMMouseEvent
ptr <- Ptr GValue -> IO (Ptr DOMMouseEvent)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DOMMouseEvent)
        if Ptr DOMMouseEvent
ptr Ptr DOMMouseEvent -> Ptr DOMMouseEvent -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DOMMouseEvent
forall a. Ptr a
FP.nullPtr
        then DOMMouseEvent -> Maybe DOMMouseEvent
forall a. a -> Maybe a
P.Just (DOMMouseEvent -> Maybe DOMMouseEvent)
-> IO DOMMouseEvent -> IO (Maybe DOMMouseEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DOMMouseEvent -> DOMMouseEvent)
-> Ptr DOMMouseEvent -> IO DOMMouseEvent
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMMouseEvent -> DOMMouseEvent
DOMMouseEvent Ptr DOMMouseEvent
ptr
        else Maybe DOMMouseEvent -> IO (Maybe DOMMouseEvent)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DOMMouseEvent
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMMouseEventMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMMouseEventMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMMouseEventMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMMouseEventMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMMouseEventMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMMouseEventMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMMouseEventMethod "initEvent" o = WebKit2WebExtension.DOMEvent.DOMEventInitEventMethodInfo
    ResolveDOMMouseEventMethod "initMouseEvent" o = DOMMouseEventInitMouseEventMethodInfo
    ResolveDOMMouseEventMethod "initUiEvent" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventInitUiEventMethodInfo
    ResolveDOMMouseEventMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMMouseEventMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMMouseEventMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMMouseEventMethod "preventDefault" o = WebKit2WebExtension.DOMEvent.DOMEventPreventDefaultMethodInfo
    ResolveDOMMouseEventMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMMouseEventMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMMouseEventMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMMouseEventMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMMouseEventMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMMouseEventMethod "stopPropagation" o = WebKit2WebExtension.DOMEvent.DOMEventStopPropagationMethodInfo
    ResolveDOMMouseEventMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMMouseEventMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMMouseEventMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMMouseEventMethod "getAltKey" o = DOMMouseEventGetAltKeyMethodInfo
    ResolveDOMMouseEventMethod "getBubbles" o = WebKit2WebExtension.DOMEvent.DOMEventGetBubblesMethodInfo
    ResolveDOMMouseEventMethod "getButton" o = DOMMouseEventGetButtonMethodInfo
    ResolveDOMMouseEventMethod "getCancelBubble" o = WebKit2WebExtension.DOMEvent.DOMEventGetCancelBubbleMethodInfo
    ResolveDOMMouseEventMethod "getCancelable" o = WebKit2WebExtension.DOMEvent.DOMEventGetCancelableMethodInfo
    ResolveDOMMouseEventMethod "getCharCode" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetCharCodeMethodInfo
    ResolveDOMMouseEventMethod "getClientX" o = DOMMouseEventGetClientXMethodInfo
    ResolveDOMMouseEventMethod "getClientY" o = DOMMouseEventGetClientYMethodInfo
    ResolveDOMMouseEventMethod "getCtrlKey" o = DOMMouseEventGetCtrlKeyMethodInfo
    ResolveDOMMouseEventMethod "getCurrentTarget" o = WebKit2WebExtension.DOMEvent.DOMEventGetCurrentTargetMethodInfo
    ResolveDOMMouseEventMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMMouseEventMethod "getDetail" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetDetailMethodInfo
    ResolveDOMMouseEventMethod "getEventPhase" o = WebKit2WebExtension.DOMEvent.DOMEventGetEventPhaseMethodInfo
    ResolveDOMMouseEventMethod "getEventType" o = WebKit2WebExtension.DOMEvent.DOMEventGetEventTypeMethodInfo
    ResolveDOMMouseEventMethod "getFromElement" o = DOMMouseEventGetFromElementMethodInfo
    ResolveDOMMouseEventMethod "getKeyCode" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetKeyCodeMethodInfo
    ResolveDOMMouseEventMethod "getLayerX" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetLayerXMethodInfo
    ResolveDOMMouseEventMethod "getLayerY" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetLayerYMethodInfo
    ResolveDOMMouseEventMethod "getMetaKey" o = DOMMouseEventGetMetaKeyMethodInfo
    ResolveDOMMouseEventMethod "getOffsetX" o = DOMMouseEventGetOffsetXMethodInfo
    ResolveDOMMouseEventMethod "getOffsetY" o = DOMMouseEventGetOffsetYMethodInfo
    ResolveDOMMouseEventMethod "getPageX" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetPageXMethodInfo
    ResolveDOMMouseEventMethod "getPageY" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetPageYMethodInfo
    ResolveDOMMouseEventMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMMouseEventMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMMouseEventMethod "getRelatedTarget" o = DOMMouseEventGetRelatedTargetMethodInfo
    ResolveDOMMouseEventMethod "getReturnValue" o = WebKit2WebExtension.DOMEvent.DOMEventGetReturnValueMethodInfo
    ResolveDOMMouseEventMethod "getScreenX" o = DOMMouseEventGetScreenXMethodInfo
    ResolveDOMMouseEventMethod "getScreenY" o = DOMMouseEventGetScreenYMethodInfo
    ResolveDOMMouseEventMethod "getShiftKey" o = DOMMouseEventGetShiftKeyMethodInfo
    ResolveDOMMouseEventMethod "getSrcElement" o = WebKit2WebExtension.DOMEvent.DOMEventGetSrcElementMethodInfo
    ResolveDOMMouseEventMethod "getTarget" o = WebKit2WebExtension.DOMEvent.DOMEventGetTargetMethodInfo
    ResolveDOMMouseEventMethod "getTimeStamp" o = WebKit2WebExtension.DOMEvent.DOMEventGetTimeStampMethodInfo
    ResolveDOMMouseEventMethod "getToElement" o = DOMMouseEventGetToElementMethodInfo
    ResolveDOMMouseEventMethod "getView" o = WebKit2WebExtension.DOMUIEvent.DOMUIEventGetViewMethodInfo
    ResolveDOMMouseEventMethod "getX" o = DOMMouseEventGetXMethodInfo
    ResolveDOMMouseEventMethod "getY" o = DOMMouseEventGetYMethodInfo
    ResolveDOMMouseEventMethod "setCancelBubble" o = WebKit2WebExtension.DOMEvent.DOMEventSetCancelBubbleMethodInfo
    ResolveDOMMouseEventMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMMouseEventMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMMouseEventMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMMouseEventMethod "setReturnValue" o = WebKit2WebExtension.DOMEvent.DOMEventSetReturnValueMethodInfo
    ResolveDOMMouseEventMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDOMMouseEventMethod t DOMMouseEvent, O.OverloadedMethod info DOMMouseEvent p) => OL.IsLabel t (DOMMouseEvent -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDOMMouseEventMethod t DOMMouseEvent, O.OverloadedMethod info DOMMouseEvent p, R.HasField t DOMMouseEvent p) => R.HasField t DOMMouseEvent p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveDOMMouseEventMethod t DOMMouseEvent, O.OverloadedMethodInfo info DOMMouseEvent) => OL.IsLabel t (O.MethodProxy info DOMMouseEvent) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "alt-key"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@alt-key@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #altKey
-- @
getDOMMouseEventAltKey :: (MonadIO m, IsDOMMouseEvent o) => o -> m Bool
getDOMMouseEventAltKey :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m Bool
getDOMMouseEventAltKey o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"alt-key"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventAltKeyPropertyInfo
instance AttrInfo DOMMouseEventAltKeyPropertyInfo where
    type AttrAllowedOps DOMMouseEventAltKeyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventAltKeyPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventAltKeyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventAltKeyPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventAltKeyPropertyInfo = ()
    type AttrGetType DOMMouseEventAltKeyPropertyInfo = Bool
    type AttrLabel DOMMouseEventAltKeyPropertyInfo = "alt-key"
    type AttrOrigin DOMMouseEventAltKeyPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventAltKey
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.altKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:altKey"
        })
#endif

-- VVV Prop "button"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@button@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #button
-- @
getDOMMouseEventButton :: (MonadIO m, IsDOMMouseEvent o) => o -> m Word32
getDOMMouseEventButton :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m Word32
getDOMMouseEventButton o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"button"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventButtonPropertyInfo
instance AttrInfo DOMMouseEventButtonPropertyInfo where
    type AttrAllowedOps DOMMouseEventButtonPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventButtonPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventButtonPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventButtonPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventButtonPropertyInfo = ()
    type AttrGetType DOMMouseEventButtonPropertyInfo = Word32
    type AttrLabel DOMMouseEventButtonPropertyInfo = "button"
    type AttrOrigin DOMMouseEventButtonPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventButton
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.button"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:button"
        })
#endif

-- VVV Prop "client-x"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@client-x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #clientX
-- @
getDOMMouseEventClientX :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventClientX :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventClientX o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"client-x"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventClientXPropertyInfo
instance AttrInfo DOMMouseEventClientXPropertyInfo where
    type AttrAllowedOps DOMMouseEventClientXPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventClientXPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventClientXPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventClientXPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventClientXPropertyInfo = ()
    type AttrGetType DOMMouseEventClientXPropertyInfo = CLong
    type AttrLabel DOMMouseEventClientXPropertyInfo = "client-x"
    type AttrOrigin DOMMouseEventClientXPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventClientX
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.clientX"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:clientX"
        })
#endif

-- VVV Prop "client-y"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@client-y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #clientY
-- @
getDOMMouseEventClientY :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventClientY :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventClientY o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"client-y"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventClientYPropertyInfo
instance AttrInfo DOMMouseEventClientYPropertyInfo where
    type AttrAllowedOps DOMMouseEventClientYPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventClientYPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventClientYPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventClientYPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventClientYPropertyInfo = ()
    type AttrGetType DOMMouseEventClientYPropertyInfo = CLong
    type AttrLabel DOMMouseEventClientYPropertyInfo = "client-y"
    type AttrOrigin DOMMouseEventClientYPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventClientY
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.clientY"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:clientY"
        })
#endif

-- VVV Prop "ctrl-key"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@ctrl-key@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #ctrlKey
-- @
getDOMMouseEventCtrlKey :: (MonadIO m, IsDOMMouseEvent o) => o -> m Bool
getDOMMouseEventCtrlKey :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m Bool
getDOMMouseEventCtrlKey o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"ctrl-key"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventCtrlKeyPropertyInfo
instance AttrInfo DOMMouseEventCtrlKeyPropertyInfo where
    type AttrAllowedOps DOMMouseEventCtrlKeyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventCtrlKeyPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventCtrlKeyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventCtrlKeyPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventCtrlKeyPropertyInfo = ()
    type AttrGetType DOMMouseEventCtrlKeyPropertyInfo = Bool
    type AttrLabel DOMMouseEventCtrlKeyPropertyInfo = "ctrl-key"
    type AttrOrigin DOMMouseEventCtrlKeyPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventCtrlKey
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.ctrlKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:ctrlKey"
        })
#endif

-- VVV Prop "from-element"
   -- Type: TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@from-element@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #fromElement
-- @
getDOMMouseEventFromElement :: (MonadIO m, IsDOMMouseEvent o) => o -> m WebKit2WebExtension.DOMNode.DOMNode
getDOMMouseEventFromElement :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m DOMNode
getDOMMouseEventFromElement o
obj = IO DOMNode -> m DOMNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DOMNode -> m DOMNode) -> IO DOMNode -> m DOMNode
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe DOMNode) -> IO DOMNode
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDOMMouseEventFromElement" (IO (Maybe DOMNode) -> IO DOMNode)
-> IO (Maybe DOMNode) -> IO DOMNode
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr DOMNode -> DOMNode) -> IO (Maybe DOMNode)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"from-element" ManagedPtr DOMNode -> DOMNode
WebKit2WebExtension.DOMNode.DOMNode

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventFromElementPropertyInfo
instance AttrInfo DOMMouseEventFromElementPropertyInfo where
    type AttrAllowedOps DOMMouseEventFromElementPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMMouseEventFromElementPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventFromElementPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventFromElementPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventFromElementPropertyInfo = ()
    type AttrGetType DOMMouseEventFromElementPropertyInfo = WebKit2WebExtension.DOMNode.DOMNode
    type AttrLabel DOMMouseEventFromElementPropertyInfo = "from-element"
    type AttrOrigin DOMMouseEventFromElementPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventFromElement
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.fromElement"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:fromElement"
        })
#endif

-- VVV Prop "meta-key"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@meta-key@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #metaKey
-- @
getDOMMouseEventMetaKey :: (MonadIO m, IsDOMMouseEvent o) => o -> m Bool
getDOMMouseEventMetaKey :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m Bool
getDOMMouseEventMetaKey o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"meta-key"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventMetaKeyPropertyInfo
instance AttrInfo DOMMouseEventMetaKeyPropertyInfo where
    type AttrAllowedOps DOMMouseEventMetaKeyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventMetaKeyPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventMetaKeyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventMetaKeyPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventMetaKeyPropertyInfo = ()
    type AttrGetType DOMMouseEventMetaKeyPropertyInfo = Bool
    type AttrLabel DOMMouseEventMetaKeyPropertyInfo = "meta-key"
    type AttrOrigin DOMMouseEventMetaKeyPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventMetaKey
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.metaKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:metaKey"
        })
#endif

-- VVV Prop "offset-x"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@offset-x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #offsetX
-- @
getDOMMouseEventOffsetX :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventOffsetX :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventOffsetX o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"offset-x"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventOffsetXPropertyInfo
instance AttrInfo DOMMouseEventOffsetXPropertyInfo where
    type AttrAllowedOps DOMMouseEventOffsetXPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventOffsetXPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventOffsetXPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventOffsetXPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventOffsetXPropertyInfo = ()
    type AttrGetType DOMMouseEventOffsetXPropertyInfo = CLong
    type AttrLabel DOMMouseEventOffsetXPropertyInfo = "offset-x"
    type AttrOrigin DOMMouseEventOffsetXPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventOffsetX
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.offsetX"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:offsetX"
        })
#endif

-- VVV Prop "offset-y"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@offset-y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #offsetY
-- @
getDOMMouseEventOffsetY :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventOffsetY :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventOffsetY o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"offset-y"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventOffsetYPropertyInfo
instance AttrInfo DOMMouseEventOffsetYPropertyInfo where
    type AttrAllowedOps DOMMouseEventOffsetYPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventOffsetYPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventOffsetYPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventOffsetYPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventOffsetYPropertyInfo = ()
    type AttrGetType DOMMouseEventOffsetYPropertyInfo = CLong
    type AttrLabel DOMMouseEventOffsetYPropertyInfo = "offset-y"
    type AttrOrigin DOMMouseEventOffsetYPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventOffsetY
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.offsetY"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:offsetY"
        })
#endif

-- VVV Prop "related-target"
   -- Type: TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMEventTarget"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@related-target@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #relatedTarget
-- @
getDOMMouseEventRelatedTarget :: (MonadIO m, IsDOMMouseEvent o) => o -> m (Maybe WebKit2WebExtension.DOMEventTarget.DOMEventTarget)
getDOMMouseEventRelatedTarget :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m (Maybe DOMEventTarget)
getDOMMouseEventRelatedTarget o
obj = IO (Maybe DOMEventTarget) -> m (Maybe DOMEventTarget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe DOMEventTarget) -> m (Maybe DOMEventTarget))
-> IO (Maybe DOMEventTarget) -> m (Maybe DOMEventTarget)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DOMEventTarget -> DOMEventTarget)
-> IO (Maybe DOMEventTarget)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"related-target" ManagedPtr DOMEventTarget -> DOMEventTarget
WebKit2WebExtension.DOMEventTarget.DOMEventTarget

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventRelatedTargetPropertyInfo
instance AttrInfo DOMMouseEventRelatedTargetPropertyInfo where
    type AttrAllowedOps DOMMouseEventRelatedTargetPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMMouseEventRelatedTargetPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventRelatedTargetPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventRelatedTargetPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventRelatedTargetPropertyInfo = ()
    type AttrGetType DOMMouseEventRelatedTargetPropertyInfo = (Maybe WebKit2WebExtension.DOMEventTarget.DOMEventTarget)
    type AttrLabel DOMMouseEventRelatedTargetPropertyInfo = "related-target"
    type AttrOrigin DOMMouseEventRelatedTargetPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventRelatedTarget
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.relatedTarget"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:relatedTarget"
        })
#endif

-- VVV Prop "screen-x"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@screen-x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #screenX
-- @
getDOMMouseEventScreenX :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventScreenX :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventScreenX o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"screen-x"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventScreenXPropertyInfo
instance AttrInfo DOMMouseEventScreenXPropertyInfo where
    type AttrAllowedOps DOMMouseEventScreenXPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventScreenXPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventScreenXPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventScreenXPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventScreenXPropertyInfo = ()
    type AttrGetType DOMMouseEventScreenXPropertyInfo = CLong
    type AttrLabel DOMMouseEventScreenXPropertyInfo = "screen-x"
    type AttrOrigin DOMMouseEventScreenXPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventScreenX
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.screenX"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:screenX"
        })
#endif

-- VVV Prop "screen-y"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@screen-y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #screenY
-- @
getDOMMouseEventScreenY :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventScreenY :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventScreenY o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"screen-y"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventScreenYPropertyInfo
instance AttrInfo DOMMouseEventScreenYPropertyInfo where
    type AttrAllowedOps DOMMouseEventScreenYPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventScreenYPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventScreenYPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventScreenYPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventScreenYPropertyInfo = ()
    type AttrGetType DOMMouseEventScreenYPropertyInfo = CLong
    type AttrLabel DOMMouseEventScreenYPropertyInfo = "screen-y"
    type AttrOrigin DOMMouseEventScreenYPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventScreenY
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.screenY"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:screenY"
        })
#endif

-- VVV Prop "shift-key"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@shift-key@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #shiftKey
-- @
getDOMMouseEventShiftKey :: (MonadIO m, IsDOMMouseEvent o) => o -> m Bool
getDOMMouseEventShiftKey :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m Bool
getDOMMouseEventShiftKey o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"shift-key"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventShiftKeyPropertyInfo
instance AttrInfo DOMMouseEventShiftKeyPropertyInfo where
    type AttrAllowedOps DOMMouseEventShiftKeyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventShiftKeyPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventShiftKeyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventShiftKeyPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventShiftKeyPropertyInfo = ()
    type AttrGetType DOMMouseEventShiftKeyPropertyInfo = Bool
    type AttrLabel DOMMouseEventShiftKeyPropertyInfo = "shift-key"
    type AttrOrigin DOMMouseEventShiftKeyPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventShiftKey
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.shiftKey"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:shiftKey"
        })
#endif

-- VVV Prop "to-element"
   -- Type: TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMNode"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@to-element@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #toElement
-- @
getDOMMouseEventToElement :: (MonadIO m, IsDOMMouseEvent o) => o -> m WebKit2WebExtension.DOMNode.DOMNode
getDOMMouseEventToElement :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m DOMNode
getDOMMouseEventToElement o
obj = IO DOMNode -> m DOMNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DOMNode -> m DOMNode) -> IO DOMNode -> m DOMNode
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe DOMNode) -> IO DOMNode
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDOMMouseEventToElement" (IO (Maybe DOMNode) -> IO DOMNode)
-> IO (Maybe DOMNode) -> IO DOMNode
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr DOMNode -> DOMNode) -> IO (Maybe DOMNode)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"to-element" ManagedPtr DOMNode -> DOMNode
WebKit2WebExtension.DOMNode.DOMNode

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventToElementPropertyInfo
instance AttrInfo DOMMouseEventToElementPropertyInfo where
    type AttrAllowedOps DOMMouseEventToElementPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMMouseEventToElementPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventToElementPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventToElementPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventToElementPropertyInfo = ()
    type AttrGetType DOMMouseEventToElementPropertyInfo = WebKit2WebExtension.DOMNode.DOMNode
    type AttrLabel DOMMouseEventToElementPropertyInfo = "to-element"
    type AttrOrigin DOMMouseEventToElementPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventToElement
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.toElement"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:toElement"
        })
#endif

-- VVV Prop "x"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #x
-- @
getDOMMouseEventX :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventX :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventX o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"x"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventXPropertyInfo
instance AttrInfo DOMMouseEventXPropertyInfo where
    type AttrAllowedOps DOMMouseEventXPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventXPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventXPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventXPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventXPropertyInfo = ()
    type AttrGetType DOMMouseEventXPropertyInfo = CLong
    type AttrLabel DOMMouseEventXPropertyInfo = "x"
    type AttrOrigin DOMMouseEventXPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventX
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.x"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:x"
        })
#endif

-- VVV Prop "y"
   -- Type: TBasicType TLong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMouseEvent #y
-- @
getDOMMouseEventY :: (MonadIO m, IsDOMMouseEvent o) => o -> m CLong
getDOMMouseEventY :: forall (m :: * -> *) o.
(MonadIO m, IsDOMMouseEvent o) =>
o -> m CLong
getDOMMouseEventY o
obj = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CLong
forall a. GObject a => a -> String -> IO CLong
B.Properties.getObjectPropertyLong o
obj String
"y"

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventYPropertyInfo
instance AttrInfo DOMMouseEventYPropertyInfo where
    type AttrAllowedOps DOMMouseEventYPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMouseEventYPropertyInfo = IsDOMMouseEvent
    type AttrSetTypeConstraint DOMMouseEventYPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMouseEventYPropertyInfo = (~) ()
    type AttrTransferType DOMMouseEventYPropertyInfo = ()
    type AttrGetType DOMMouseEventYPropertyInfo = CLong
    type AttrLabel DOMMouseEventYPropertyInfo = "y"
    type AttrOrigin DOMMouseEventYPropertyInfo = DOMMouseEvent
    attrGet = getDOMMouseEventY
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.y"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#g:attr:y"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMMouseEvent
type instance O.AttributeList DOMMouseEvent = DOMMouseEventAttributeList
type DOMMouseEventAttributeList = ('[ '("altKey", DOMMouseEventAltKeyPropertyInfo), '("bubbles", WebKit2WebExtension.DOMEvent.DOMEventBubblesPropertyInfo), '("button", DOMMouseEventButtonPropertyInfo), '("cancelBubble", WebKit2WebExtension.DOMEvent.DOMEventCancelBubblePropertyInfo), '("cancelable", WebKit2WebExtension.DOMEvent.DOMEventCancelablePropertyInfo), '("charCode", WebKit2WebExtension.DOMUIEvent.DOMUIEventCharCodePropertyInfo), '("clientX", DOMMouseEventClientXPropertyInfo), '("clientY", DOMMouseEventClientYPropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("ctrlKey", DOMMouseEventCtrlKeyPropertyInfo), '("currentTarget", WebKit2WebExtension.DOMEvent.DOMEventCurrentTargetPropertyInfo), '("detail", WebKit2WebExtension.DOMUIEvent.DOMUIEventDetailPropertyInfo), '("eventPhase", WebKit2WebExtension.DOMEvent.DOMEventEventPhasePropertyInfo), '("fromElement", DOMMouseEventFromElementPropertyInfo), '("keyCode", WebKit2WebExtension.DOMUIEvent.DOMUIEventKeyCodePropertyInfo), '("layerX", WebKit2WebExtension.DOMUIEvent.DOMUIEventLayerXPropertyInfo), '("layerY", WebKit2WebExtension.DOMUIEvent.DOMUIEventLayerYPropertyInfo), '("metaKey", DOMMouseEventMetaKeyPropertyInfo), '("offsetX", DOMMouseEventOffsetXPropertyInfo), '("offsetY", DOMMouseEventOffsetYPropertyInfo), '("pageX", WebKit2WebExtension.DOMUIEvent.DOMUIEventPageXPropertyInfo), '("pageY", WebKit2WebExtension.DOMUIEvent.DOMUIEventPageYPropertyInfo), '("relatedTarget", DOMMouseEventRelatedTargetPropertyInfo), '("returnValue", WebKit2WebExtension.DOMEvent.DOMEventReturnValuePropertyInfo), '("screenX", DOMMouseEventScreenXPropertyInfo), '("screenY", DOMMouseEventScreenYPropertyInfo), '("shiftKey", DOMMouseEventShiftKeyPropertyInfo), '("srcElement", WebKit2WebExtension.DOMEvent.DOMEventSrcElementPropertyInfo), '("target", WebKit2WebExtension.DOMEvent.DOMEventTargetPropertyInfo), '("timeStamp", WebKit2WebExtension.DOMEvent.DOMEventTimeStampPropertyInfo), '("toElement", DOMMouseEventToElementPropertyInfo), '("type", WebKit2WebExtension.DOMEvent.DOMEventTypePropertyInfo), '("view", WebKit2WebExtension.DOMUIEvent.DOMUIEventViewPropertyInfo), '("x", DOMMouseEventXPropertyInfo), '("y", DOMMouseEventYPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMMouseEventAltKey :: AttrLabelProxy "altKey"
dOMMouseEventAltKey = AttrLabelProxy

dOMMouseEventButton :: AttrLabelProxy "button"
dOMMouseEventButton = AttrLabelProxy

dOMMouseEventClientX :: AttrLabelProxy "clientX"
dOMMouseEventClientX = AttrLabelProxy

dOMMouseEventClientY :: AttrLabelProxy "clientY"
dOMMouseEventClientY = AttrLabelProxy

dOMMouseEventCtrlKey :: AttrLabelProxy "ctrlKey"
dOMMouseEventCtrlKey = AttrLabelProxy

dOMMouseEventFromElement :: AttrLabelProxy "fromElement"
dOMMouseEventFromElement = AttrLabelProxy

dOMMouseEventMetaKey :: AttrLabelProxy "metaKey"
dOMMouseEventMetaKey = AttrLabelProxy

dOMMouseEventOffsetX :: AttrLabelProxy "offsetX"
dOMMouseEventOffsetX = AttrLabelProxy

dOMMouseEventOffsetY :: AttrLabelProxy "offsetY"
dOMMouseEventOffsetY = AttrLabelProxy

dOMMouseEventRelatedTarget :: AttrLabelProxy "relatedTarget"
dOMMouseEventRelatedTarget = AttrLabelProxy

dOMMouseEventScreenX :: AttrLabelProxy "screenX"
dOMMouseEventScreenX = AttrLabelProxy

dOMMouseEventScreenY :: AttrLabelProxy "screenY"
dOMMouseEventScreenY = AttrLabelProxy

dOMMouseEventShiftKey :: AttrLabelProxy "shiftKey"
dOMMouseEventShiftKey = AttrLabelProxy

dOMMouseEventToElement :: AttrLabelProxy "toElement"
dOMMouseEventToElement = AttrLabelProxy

dOMMouseEventX :: AttrLabelProxy "x"
dOMMouseEventX = AttrLabelProxy

dOMMouseEventY :: AttrLabelProxy "y"
dOMMouseEventY = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DOMMouseEvent = DOMMouseEventSignalList
type DOMMouseEventSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DOMMouseEvent::get_alt_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_alt_key" webkit_dom_mouse_event_get_alt_key :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CInt

{-# DEPRECATED dOMMouseEventGetAltKey ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetAltKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMMouseEventGetAltKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m Bool
dOMMouseEventGetAltKey a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DOMMouseEvent -> IO CInt
webkit_dom_mouse_event_get_alt_key Ptr DOMMouseEvent
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetAltKeyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetAltKeyMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetAltKey

instance O.OverloadedMethodInfo DOMMouseEventGetAltKeyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetAltKey",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetAltKey"
        })


#endif

-- method DOMMouseEvent::get_button
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt16)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_button" webkit_dom_mouse_event_get_button :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO Word16

{-# DEPRECATED dOMMouseEventGetButton ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m Word16
    -- ^ __Returns:__ A @/gushort/@
dOMMouseEventGetButton :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m Word16
dOMMouseEventGetButton a
self = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word16
result <- Ptr DOMMouseEvent -> IO Word16
webkit_dom_mouse_event_get_button Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetButtonMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetButtonMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetButton

instance O.OverloadedMethodInfo DOMMouseEventGetButtonMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetButton",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetButton"
        })


#endif

-- method DOMMouseEvent::get_client_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_client_x" webkit_dom_mouse_event_get_client_x :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetClientX ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetClientX ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetClientX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetClientX a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_client_x Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetClientXMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetClientXMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetClientX

instance O.OverloadedMethodInfo DOMMouseEventGetClientXMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetClientX",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetClientX"
        })


#endif

-- method DOMMouseEvent::get_client_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_client_y" webkit_dom_mouse_event_get_client_y :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetClientY ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetClientY ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetClientY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetClientY a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_client_y Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetClientYMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetClientYMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetClientY

instance O.OverloadedMethodInfo DOMMouseEventGetClientYMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetClientY",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetClientY"
        })


#endif

-- method DOMMouseEvent::get_ctrl_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_ctrl_key" webkit_dom_mouse_event_get_ctrl_key :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CInt

{-# DEPRECATED dOMMouseEventGetCtrlKey ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetCtrlKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMMouseEventGetCtrlKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m Bool
dOMMouseEventGetCtrlKey a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DOMMouseEvent -> IO CInt
webkit_dom_mouse_event_get_ctrl_key Ptr DOMMouseEvent
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetCtrlKeyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetCtrlKeyMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetCtrlKey

instance O.OverloadedMethodInfo DOMMouseEventGetCtrlKeyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetCtrlKey",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetCtrlKey"
        })


#endif

-- method DOMMouseEvent::get_from_element
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMNode" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_from_element" webkit_dom_mouse_event_get_from_element :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

{-# DEPRECATED dOMMouseEventGetFromElement ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetFromElement ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m WebKit2WebExtension.DOMNode.DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
dOMMouseEventGetFromElement :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m DOMNode
dOMMouseEventGetFromElement a
self = IO DOMNode -> m DOMNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMNode -> m DOMNode) -> IO DOMNode -> m DOMNode
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
result <- Ptr DOMMouseEvent -> IO (Ptr DOMNode)
webkit_dom_mouse_event_get_from_element Ptr DOMMouseEvent
self'
    Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMMouseEventGetFromElement" Ptr DOMNode
result
    DOMNode
result' <- ((ManagedPtr DOMNode -> DOMNode) -> Ptr DOMNode -> IO DOMNode
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DOMNode -> DOMNode
WebKit2WebExtension.DOMNode.DOMNode) Ptr DOMNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMNode -> IO DOMNode
forall (m :: * -> *) a. Monad m => a -> m a
return DOMNode
result'

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetFromElementMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetFromElementMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetFromElement

instance O.OverloadedMethodInfo DOMMouseEventGetFromElementMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetFromElement",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetFromElement"
        })


#endif

-- method DOMMouseEvent::get_meta_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_meta_key" webkit_dom_mouse_event_get_meta_key :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CInt

{-# DEPRECATED dOMMouseEventGetMetaKey ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetMetaKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMMouseEventGetMetaKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m Bool
dOMMouseEventGetMetaKey a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DOMMouseEvent -> IO CInt
webkit_dom_mouse_event_get_meta_key Ptr DOMMouseEvent
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetMetaKeyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetMetaKeyMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetMetaKey

instance O.OverloadedMethodInfo DOMMouseEventGetMetaKeyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetMetaKey",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetMetaKey"
        })


#endif

-- method DOMMouseEvent::get_offset_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_offset_x" webkit_dom_mouse_event_get_offset_x :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetOffsetX ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetOffsetX ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetOffsetX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetOffsetX a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_offset_x Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetOffsetXMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetOffsetXMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetOffsetX

instance O.OverloadedMethodInfo DOMMouseEventGetOffsetXMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetOffsetX",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetOffsetX"
        })


#endif

-- method DOMMouseEvent::get_offset_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_offset_y" webkit_dom_mouse_event_get_offset_y :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetOffsetY ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetOffsetY ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetOffsetY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetOffsetY a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_offset_y Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetOffsetYMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetOffsetYMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetOffsetY

instance O.OverloadedMethodInfo DOMMouseEventGetOffsetYMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetOffsetY",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetOffsetY"
        })


#endif

-- method DOMMouseEvent::get_related_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name
--                    { namespace = "WebKit2WebExtension" , name = "DOMEventTarget" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_related_target" webkit_dom_mouse_event_get_related_target :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO (Ptr WebKit2WebExtension.DOMEventTarget.DOMEventTarget)

{-# DEPRECATED dOMMouseEventGetRelatedTarget ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetRelatedTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m WebKit2WebExtension.DOMEventTarget.DOMEventTarget
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Interfaces.DOMEventTarget.DOMEventTarget'
dOMMouseEventGetRelatedTarget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m DOMEventTarget
dOMMouseEventGetRelatedTarget a
self = IO DOMEventTarget -> m DOMEventTarget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMEventTarget -> m DOMEventTarget)
-> IO DOMEventTarget -> m DOMEventTarget
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMEventTarget
result <- Ptr DOMMouseEvent -> IO (Ptr DOMEventTarget)
webkit_dom_mouse_event_get_related_target Ptr DOMMouseEvent
self'
    Text -> Ptr DOMEventTarget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMMouseEventGetRelatedTarget" Ptr DOMEventTarget
result
    DOMEventTarget
result' <- ((ManagedPtr DOMEventTarget -> DOMEventTarget)
-> Ptr DOMEventTarget -> IO DOMEventTarget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DOMEventTarget -> DOMEventTarget
WebKit2WebExtension.DOMEventTarget.DOMEventTarget) Ptr DOMEventTarget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMEventTarget -> IO DOMEventTarget
forall (m :: * -> *) a. Monad m => a -> m a
return DOMEventTarget
result'

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetRelatedTargetMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMEventTarget.DOMEventTarget), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetRelatedTargetMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetRelatedTarget

instance O.OverloadedMethodInfo DOMMouseEventGetRelatedTargetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetRelatedTarget",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetRelatedTarget"
        })


#endif

-- method DOMMouseEvent::get_screen_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_screen_x" webkit_dom_mouse_event_get_screen_x :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetScreenX ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetScreenX ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetScreenX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetScreenX a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_screen_x Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetScreenXMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetScreenXMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetScreenX

instance O.OverloadedMethodInfo DOMMouseEventGetScreenXMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetScreenX",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetScreenX"
        })


#endif

-- method DOMMouseEvent::get_screen_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_screen_y" webkit_dom_mouse_event_get_screen_y :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetScreenY ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetScreenY ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetScreenY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetScreenY a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_screen_y Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetScreenYMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetScreenYMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetScreenY

instance O.OverloadedMethodInfo DOMMouseEventGetScreenYMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetScreenY",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetScreenY"
        })


#endif

-- method DOMMouseEvent::get_shift_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_shift_key" webkit_dom_mouse_event_get_shift_key :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CInt

{-# DEPRECATED dOMMouseEventGetShiftKey ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetShiftKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m Bool
    -- ^ __Returns:__ A t'P.Bool'
dOMMouseEventGetShiftKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m Bool
dOMMouseEventGetShiftKey a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DOMMouseEvent -> IO CInt
webkit_dom_mouse_event_get_shift_key Ptr DOMMouseEvent
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetShiftKeyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetShiftKeyMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetShiftKey

instance O.OverloadedMethodInfo DOMMouseEventGetShiftKeyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetShiftKey",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetShiftKey"
        })


#endif

-- method DOMMouseEvent::get_to_element
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "WebKit2WebExtension" , name = "DOMNode" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_to_element" webkit_dom_mouse_event_get_to_element :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO (Ptr WebKit2WebExtension.DOMNode.DOMNode)

{-# DEPRECATED dOMMouseEventGetToElement ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetToElement ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m WebKit2WebExtension.DOMNode.DOMNode
    -- ^ __Returns:__ A t'GI.WebKit2WebExtension.Objects.DOMNode.DOMNode'
dOMMouseEventGetToElement :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m DOMNode
dOMMouseEventGetToElement a
self = IO DOMNode -> m DOMNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DOMNode -> m DOMNode) -> IO DOMNode -> m DOMNode
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DOMNode
result <- Ptr DOMMouseEvent -> IO (Ptr DOMNode)
webkit_dom_mouse_event_get_to_element Ptr DOMMouseEvent
self'
    Text -> Ptr DOMNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMMouseEventGetToElement" Ptr DOMNode
result
    DOMNode
result' <- ((ManagedPtr DOMNode -> DOMNode) -> Ptr DOMNode -> IO DOMNode
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DOMNode -> DOMNode
WebKit2WebExtension.DOMNode.DOMNode) Ptr DOMNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    DOMNode -> IO DOMNode
forall (m :: * -> *) a. Monad m => a -> m a
return DOMNode
result'

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetToElementMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMNode.DOMNode), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetToElementMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetToElement

instance O.OverloadedMethodInfo DOMMouseEventGetToElementMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetToElement",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetToElement"
        })


#endif

-- method DOMMouseEvent::get_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_x" webkit_dom_mouse_event_get_x :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetX ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetX ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetX a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_x Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetXMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetXMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetX

instance O.OverloadedMethodInfo DOMMouseEventGetXMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetX",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetX"
        })


#endif

-- method DOMMouseEvent::get_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_get_y" webkit_dom_mouse_event_get_y :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    IO CLong

{-# DEPRECATED dOMMouseEventGetY ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventGetY ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMMouseEventGetY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMMouseEvent a) =>
a -> m CLong
dOMMouseEventGetY a
self = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMMouseEvent -> IO CLong
webkit_dom_mouse_event_get_y Ptr DOMMouseEvent
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventGetYMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMMouseEvent a) => O.OverloadedMethod DOMMouseEventGetYMethodInfo a signature where
    overloadedMethod = dOMMouseEventGetY

instance O.OverloadedMethodInfo DOMMouseEventGetYMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventGetY",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventGetY"
        })


#endif

-- method DOMMouseEvent::init_mouse_event
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMouseEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMouseEvent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "canBubble"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gboolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancelable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gboolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "view"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMDOMWindow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMDOMWindow"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detail"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screenX"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screenY"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "clientX"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "clientY"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #glong" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ctrlKey"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gboolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "altKey"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gboolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shiftKey"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gboolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "metaKey"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gboolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "button"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gushort" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relatedTarget"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "WebKit2WebExtension" , name = "DOMEventTarget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMEventTarget"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_mouse_event_init_mouse_event" webkit_dom_mouse_event_init_mouse_event :: 
    Ptr DOMMouseEvent ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMouseEvent"})
    CString ->                              -- type : TBasicType TUTF8
    CInt ->                                 -- canBubble : TBasicType TBoolean
    CInt ->                                 -- cancelable : TBasicType TBoolean
    Ptr WebKit2WebExtension.DOMDOMWindow.DOMDOMWindow -> -- view : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMDOMWindow"})
    CLong ->                                -- detail : TBasicType TLong
    CLong ->                                -- screenX : TBasicType TLong
    CLong ->                                -- screenY : TBasicType TLong
    CLong ->                                -- clientX : TBasicType TLong
    CLong ->                                -- clientY : TBasicType TLong
    CInt ->                                 -- ctrlKey : TBasicType TBoolean
    CInt ->                                 -- altKey : TBasicType TBoolean
    CInt ->                                 -- shiftKey : TBasicType TBoolean
    CInt ->                                 -- metaKey : TBasicType TBoolean
    Word16 ->                               -- button : TBasicType TUInt16
    Ptr WebKit2WebExtension.DOMEventTarget.DOMEventTarget -> -- relatedTarget : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMEventTarget"})
    IO ()

{-# DEPRECATED dOMMouseEventInitMouseEvent ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMouseEventInitMouseEvent ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMouseEvent a, WebKit2WebExtension.DOMDOMWindow.IsDOMDOMWindow b, WebKit2WebExtension.DOMEventTarget.IsDOMEventTarget c) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMouseEvent.DOMMouseEvent'
    -> T.Text
    -- ^ /@type@/: A @/gchar/@
    -> Bool
    -- ^ /@canBubble@/: A t'P.Bool'
    -> Bool
    -- ^ /@cancelable@/: A t'P.Bool'
    -> b
    -- ^ /@view@/: A t'GI.WebKit2WebExtension.Objects.DOMDOMWindow.DOMDOMWindow'
    -> CLong
    -- ^ /@detail@/: A @/glong/@
    -> CLong
    -- ^ /@screenX@/: A @/glong/@
    -> CLong
    -- ^ /@screenY@/: A @/glong/@
    -> CLong
    -- ^ /@clientX@/: A @/glong/@
    -> CLong
    -- ^ /@clientY@/: A @/glong/@
    -> Bool
    -- ^ /@ctrlKey@/: A t'P.Bool'
    -> Bool
    -- ^ /@altKey@/: A t'P.Bool'
    -> Bool
    -- ^ /@shiftKey@/: A t'P.Bool'
    -> Bool
    -- ^ /@metaKey@/: A t'P.Bool'
    -> Word16
    -- ^ /@button@/: A @/gushort/@
    -> c
    -- ^ /@relatedTarget@/: A t'GI.WebKit2WebExtension.Interfaces.DOMEventTarget.DOMEventTarget'
    -> m ()
dOMMouseEventInitMouseEvent :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDOMMouseEvent a, IsDOMDOMWindow b,
 IsDOMEventTarget c) =>
a
-> Text
-> Bool
-> Bool
-> b
-> CLong
-> CLong
-> CLong
-> CLong
-> CLong
-> Bool
-> Bool
-> Bool
-> Bool
-> Word16
-> c
-> m ()
dOMMouseEventInitMouseEvent a
self Text
type_ Bool
canBubble Bool
cancelable b
view CLong
detail CLong
screenX CLong
screenY CLong
clientX CLong
clientY Bool
ctrlKey Bool
altKey Bool
shiftKey Bool
metaKey Word16
button c
relatedTarget = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMouseEvent
self' <- a -> IO (Ptr DOMMouseEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
type_' <- Text -> IO CString
textToCString Text
type_
    let canBubble' :: CInt
canBubble' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
canBubble
    let cancelable' :: CInt
cancelable' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
cancelable
    Ptr DOMDOMWindow
view' <- b -> IO (Ptr DOMDOMWindow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
view
    let ctrlKey' :: CInt
ctrlKey' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
ctrlKey
    let altKey' :: CInt
altKey' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
altKey
    let shiftKey' :: CInt
shiftKey' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
shiftKey
    let metaKey' :: CInt
metaKey' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
metaKey
    Ptr DOMEventTarget
relatedTarget' <- c -> IO (Ptr DOMEventTarget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
relatedTarget
    Ptr DOMMouseEvent
-> CString
-> CInt
-> CInt
-> Ptr DOMDOMWindow
-> CLong
-> CLong
-> CLong
-> CLong
-> CLong
-> CInt
-> CInt
-> CInt
-> CInt
-> Word16
-> Ptr DOMEventTarget
-> IO ()
webkit_dom_mouse_event_init_mouse_event Ptr DOMMouseEvent
self' CString
type_' CInt
canBubble' CInt
cancelable' Ptr DOMDOMWindow
view' CLong
detail CLong
screenX CLong
screenY CLong
clientX CLong
clientY CInt
ctrlKey' CInt
altKey' CInt
shiftKey' CInt
metaKey' Word16
button Ptr DOMEventTarget
relatedTarget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
view
    c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
relatedTarget
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DOMMouseEventInitMouseEventMethodInfo
instance (signature ~ (T.Text -> Bool -> Bool -> b -> CLong -> CLong -> CLong -> CLong -> CLong -> Bool -> Bool -> Bool -> Bool -> Word16 -> c -> m ()), MonadIO m, IsDOMMouseEvent a, WebKit2WebExtension.DOMDOMWindow.IsDOMDOMWindow b, WebKit2WebExtension.DOMEventTarget.IsDOMEventTarget c) => O.OverloadedMethod DOMMouseEventInitMouseEventMethodInfo a signature where
    overloadedMethod = dOMMouseEventInitMouseEvent

instance O.OverloadedMethodInfo DOMMouseEventInitMouseEventMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2WebExtension.Objects.DOMMouseEvent.dOMMouseEventInitMouseEvent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.27/docs/GI-WebKit2WebExtension-Objects-DOMMouseEvent.html#v:dOMMouseEventInitMouseEvent"
        })


#endif