{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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.DOMUIEvent
    ( 

-- * Exported types
    DOMUIEvent(..)                          ,
    IsDOMUIEvent                            ,
    toDOMUIEvent                            ,


 -- * 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"), [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
-- [getBubbles]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getBubbles"), [getCancelBubble]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getCancelBubble"), [getCancelable]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getCancelable"), [getCharCode]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getCharCode"), [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"), [getKeyCode]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getKeyCode"), [getLayerX]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getLayerX"), [getLayerY]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getLayerY"), [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"), [getReturnValue]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getReturnValue"), [getSrcElement]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getSrcElement"), [getTarget]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getTarget"), [getTimeStamp]("GI.WebKit2WebExtension.Objects.DOMEvent#g:method:getTimeStamp"), [getView]("GI.WebKit2WebExtension.Objects.DOMUIEvent#g:method:getView").
-- 
-- ==== 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)
    ResolveDOMUIEventMethod                 ,
#endif

-- ** getCharCode #method:getCharCode#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetCharCodeMethodInfo         ,
#endif
    dOMUIEventGetCharCode                   ,


-- ** getDetail #method:getDetail#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetDetailMethodInfo           ,
#endif
    dOMUIEventGetDetail                     ,


-- ** getKeyCode #method:getKeyCode#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetKeyCodeMethodInfo          ,
#endif
    dOMUIEventGetKeyCode                    ,


-- ** getLayerX #method:getLayerX#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetLayerXMethodInfo           ,
#endif
    dOMUIEventGetLayerX                     ,


-- ** getLayerY #method:getLayerY#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetLayerYMethodInfo           ,
#endif
    dOMUIEventGetLayerY                     ,


-- ** getPageX #method:getPageX#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetPageXMethodInfo            ,
#endif
    dOMUIEventGetPageX                      ,


-- ** getPageY #method:getPageY#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetPageYMethodInfo            ,
#endif
    dOMUIEventGetPageY                      ,


-- ** getView #method:getView#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventGetViewMethodInfo             ,
#endif
    dOMUIEventGetView                       ,


-- ** initUiEvent #method:initUiEvent#

#if defined(ENABLE_OVERLOADING)
    DOMUIEventInitUiEventMethodInfo         ,
#endif
    dOMUIEventInitUiEvent                   ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventCharCodePropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventCharCode                      ,
#endif
    getDOMUIEventCharCode                   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventDetailPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventDetail                        ,
#endif
    getDOMUIEventDetail                     ,


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventKeyCodePropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventKeyCode                       ,
#endif
    getDOMUIEventKeyCode                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventLayerXPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventLayerX                        ,
#endif
    getDOMUIEventLayerX                     ,


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventLayerYPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventLayerY                        ,
#endif
    getDOMUIEventLayerY                     ,


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventPageXPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventPageX                         ,
#endif
    getDOMUIEventPageX                      ,


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventPageYPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventPageY                         ,
#endif
    getDOMUIEventPageY                      ,


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

#if defined(ENABLE_OVERLOADING)
    DOMUIEventViewPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMUIEventView                          ,
#endif
    getDOMUIEventView                       ,




    ) 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.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.Objects.DOMDOMWindow as WebKit2WebExtension.DOMDOMWindow
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMEvent as WebKit2WebExtension.DOMEvent
import {-# SOURCE #-} qualified GI.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject

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

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

foreign import ccall "webkit_dom_ui_event_get_type"
    c_webkit_dom_ui_event_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMUIEvent where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_ui_event_get_type

instance B.Types.GObject DOMUIEvent

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

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

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

-- | Convert 'DOMUIEvent' 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 DOMUIEvent) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_webkit_dom_ui_event_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DOMUIEvent -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DOMUIEvent
P.Nothing = Ptr GValue -> Ptr DOMUIEvent -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DOMUIEvent
forall a. Ptr a
FP.nullPtr :: FP.Ptr DOMUIEvent)
    gvalueSet_ Ptr GValue
gv (P.Just DOMUIEvent
obj) = DOMUIEvent -> (Ptr DOMUIEvent -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMUIEvent
obj (Ptr GValue -> Ptr DOMUIEvent -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DOMUIEvent)
gvalueGet_ Ptr GValue
gv = do
        Ptr DOMUIEvent
ptr <- Ptr GValue -> IO (Ptr DOMUIEvent)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DOMUIEvent)
        if Ptr DOMUIEvent
ptr Ptr DOMUIEvent -> Ptr DOMUIEvent -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DOMUIEvent
forall a. Ptr a
FP.nullPtr
        then DOMUIEvent -> Maybe DOMUIEvent
forall a. a -> Maybe a
P.Just (DOMUIEvent -> Maybe DOMUIEvent)
-> IO DOMUIEvent -> IO (Maybe DOMUIEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DOMUIEvent -> DOMUIEvent)
-> Ptr DOMUIEvent -> IO DOMUIEvent
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMUIEvent -> DOMUIEvent
DOMUIEvent Ptr DOMUIEvent
ptr
        else Maybe DOMUIEvent -> IO (Maybe DOMUIEvent)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DOMUIEvent
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMUIEventMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMUIEventMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMUIEventMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMUIEventMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMUIEventMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMUIEventMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMUIEventMethod "initEvent" o = WebKit2WebExtension.DOMEvent.DOMEventInitEventMethodInfo
    ResolveDOMUIEventMethod "initUiEvent" o = DOMUIEventInitUiEventMethodInfo
    ResolveDOMUIEventMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMUIEventMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMUIEventMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMUIEventMethod "preventDefault" o = WebKit2WebExtension.DOMEvent.DOMEventPreventDefaultMethodInfo
    ResolveDOMUIEventMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMUIEventMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMUIEventMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMUIEventMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMUIEventMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMUIEventMethod "stopPropagation" o = WebKit2WebExtension.DOMEvent.DOMEventStopPropagationMethodInfo
    ResolveDOMUIEventMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMUIEventMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMUIEventMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMUIEventMethod "getBubbles" o = WebKit2WebExtension.DOMEvent.DOMEventGetBubblesMethodInfo
    ResolveDOMUIEventMethod "getCancelBubble" o = WebKit2WebExtension.DOMEvent.DOMEventGetCancelBubbleMethodInfo
    ResolveDOMUIEventMethod "getCancelable" o = WebKit2WebExtension.DOMEvent.DOMEventGetCancelableMethodInfo
    ResolveDOMUIEventMethod "getCharCode" o = DOMUIEventGetCharCodeMethodInfo
    ResolveDOMUIEventMethod "getCurrentTarget" o = WebKit2WebExtension.DOMEvent.DOMEventGetCurrentTargetMethodInfo
    ResolveDOMUIEventMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMUIEventMethod "getDetail" o = DOMUIEventGetDetailMethodInfo
    ResolveDOMUIEventMethod "getEventPhase" o = WebKit2WebExtension.DOMEvent.DOMEventGetEventPhaseMethodInfo
    ResolveDOMUIEventMethod "getEventType" o = WebKit2WebExtension.DOMEvent.DOMEventGetEventTypeMethodInfo
    ResolveDOMUIEventMethod "getKeyCode" o = DOMUIEventGetKeyCodeMethodInfo
    ResolveDOMUIEventMethod "getLayerX" o = DOMUIEventGetLayerXMethodInfo
    ResolveDOMUIEventMethod "getLayerY" o = DOMUIEventGetLayerYMethodInfo
    ResolveDOMUIEventMethod "getPageX" o = DOMUIEventGetPageXMethodInfo
    ResolveDOMUIEventMethod "getPageY" o = DOMUIEventGetPageYMethodInfo
    ResolveDOMUIEventMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMUIEventMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMUIEventMethod "getReturnValue" o = WebKit2WebExtension.DOMEvent.DOMEventGetReturnValueMethodInfo
    ResolveDOMUIEventMethod "getSrcElement" o = WebKit2WebExtension.DOMEvent.DOMEventGetSrcElementMethodInfo
    ResolveDOMUIEventMethod "getTarget" o = WebKit2WebExtension.DOMEvent.DOMEventGetTargetMethodInfo
    ResolveDOMUIEventMethod "getTimeStamp" o = WebKit2WebExtension.DOMEvent.DOMEventGetTimeStampMethodInfo
    ResolveDOMUIEventMethod "getView" o = DOMUIEventGetViewMethodInfo
    ResolveDOMUIEventMethod "setCancelBubble" o = WebKit2WebExtension.DOMEvent.DOMEventSetCancelBubbleMethodInfo
    ResolveDOMUIEventMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMUIEventMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMUIEventMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMUIEventMethod "setReturnValue" o = WebKit2WebExtension.DOMEvent.DOMEventSetReturnValueMethodInfo
    ResolveDOMUIEventMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDOMUIEventMethod t DOMUIEvent, O.OverloadedMethod info DOMUIEvent p) => OL.IsLabel t (DOMUIEvent -> 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 ~ ResolveDOMUIEventMethod t DOMUIEvent, O.OverloadedMethod info DOMUIEvent p, R.HasField t DOMUIEvent p) => R.HasField t DOMUIEvent p where
    getField = O.overloadedMethod @info

#endif

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

#endif

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

-- | Get the value of the “@char-code@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMUIEvent #charCode
-- @
getDOMUIEventCharCode :: (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventCharCode :: forall (m :: * -> *) o. (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventCharCode 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
"char-code"

#if defined(ENABLE_OVERLOADING)
data DOMUIEventCharCodePropertyInfo
instance AttrInfo DOMUIEventCharCodePropertyInfo where
    type AttrAllowedOps DOMUIEventCharCodePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMUIEventCharCodePropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventCharCodePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventCharCodePropertyInfo = (~) ()
    type AttrTransferType DOMUIEventCharCodePropertyInfo = ()
    type AttrGetType DOMUIEventCharCodePropertyInfo = CLong
    type AttrLabel DOMUIEventCharCodePropertyInfo = "char-code"
    type AttrOrigin DOMUIEventCharCodePropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventCharCode
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@detail@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMUIEvent #detail
-- @
getDOMUIEventDetail :: (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventDetail :: forall (m :: * -> *) o. (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventDetail 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
"detail"

#if defined(ENABLE_OVERLOADING)
data DOMUIEventDetailPropertyInfo
instance AttrInfo DOMUIEventDetailPropertyInfo where
    type AttrAllowedOps DOMUIEventDetailPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMUIEventDetailPropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventDetailPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventDetailPropertyInfo = (~) ()
    type AttrTransferType DOMUIEventDetailPropertyInfo = ()
    type AttrGetType DOMUIEventDetailPropertyInfo = CLong
    type AttrLabel DOMUIEventDetailPropertyInfo = "detail"
    type AttrOrigin DOMUIEventDetailPropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventDetail
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@key-code@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMUIEvent #keyCode
-- @
getDOMUIEventKeyCode :: (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventKeyCode :: forall (m :: * -> *) o. (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventKeyCode 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
"key-code"

#if defined(ENABLE_OVERLOADING)
data DOMUIEventKeyCodePropertyInfo
instance AttrInfo DOMUIEventKeyCodePropertyInfo where
    type AttrAllowedOps DOMUIEventKeyCodePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMUIEventKeyCodePropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventKeyCodePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventKeyCodePropertyInfo = (~) ()
    type AttrTransferType DOMUIEventKeyCodePropertyInfo = ()
    type AttrGetType DOMUIEventKeyCodePropertyInfo = CLong
    type AttrLabel DOMUIEventKeyCodePropertyInfo = "key-code"
    type AttrOrigin DOMUIEventKeyCodePropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventKeyCode
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@layer-x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMUIEvent #layerX
-- @
getDOMUIEventLayerX :: (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventLayerX :: forall (m :: * -> *) o. (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventLayerX 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
"layer-x"

#if defined(ENABLE_OVERLOADING)
data DOMUIEventLayerXPropertyInfo
instance AttrInfo DOMUIEventLayerXPropertyInfo where
    type AttrAllowedOps DOMUIEventLayerXPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMUIEventLayerXPropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventLayerXPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventLayerXPropertyInfo = (~) ()
    type AttrTransferType DOMUIEventLayerXPropertyInfo = ()
    type AttrGetType DOMUIEventLayerXPropertyInfo = CLong
    type AttrLabel DOMUIEventLayerXPropertyInfo = "layer-x"
    type AttrOrigin DOMUIEventLayerXPropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventLayerX
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@layer-y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMUIEvent #layerY
-- @
getDOMUIEventLayerY :: (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventLayerY :: forall (m :: * -> *) o. (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventLayerY 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
"layer-y"

#if defined(ENABLE_OVERLOADING)
data DOMUIEventLayerYPropertyInfo
instance AttrInfo DOMUIEventLayerYPropertyInfo where
    type AttrAllowedOps DOMUIEventLayerYPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMUIEventLayerYPropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventLayerYPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventLayerYPropertyInfo = (~) ()
    type AttrTransferType DOMUIEventLayerYPropertyInfo = ()
    type AttrGetType DOMUIEventLayerYPropertyInfo = CLong
    type AttrLabel DOMUIEventLayerYPropertyInfo = "layer-y"
    type AttrOrigin DOMUIEventLayerYPropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventLayerY
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@page-x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMUIEvent #pageX
-- @
getDOMUIEventPageX :: (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventPageX :: forall (m :: * -> *) o. (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventPageX 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
"page-x"

#if defined(ENABLE_OVERLOADING)
data DOMUIEventPageXPropertyInfo
instance AttrInfo DOMUIEventPageXPropertyInfo where
    type AttrAllowedOps DOMUIEventPageXPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMUIEventPageXPropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventPageXPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventPageXPropertyInfo = (~) ()
    type AttrTransferType DOMUIEventPageXPropertyInfo = ()
    type AttrGetType DOMUIEventPageXPropertyInfo = CLong
    type AttrLabel DOMUIEventPageXPropertyInfo = "page-x"
    type AttrOrigin DOMUIEventPageXPropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventPageX
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@page-y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMUIEvent #pageY
-- @
getDOMUIEventPageY :: (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventPageY :: forall (m :: * -> *) o. (MonadIO m, IsDOMUIEvent o) => o -> m CLong
getDOMUIEventPageY 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
"page-y"

#if defined(ENABLE_OVERLOADING)
data DOMUIEventPageYPropertyInfo
instance AttrInfo DOMUIEventPageYPropertyInfo where
    type AttrAllowedOps DOMUIEventPageYPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMUIEventPageYPropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventPageYPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventPageYPropertyInfo = (~) ()
    type AttrTransferType DOMUIEventPageYPropertyInfo = ()
    type AttrGetType DOMUIEventPageYPropertyInfo = CLong
    type AttrLabel DOMUIEventPageYPropertyInfo = "page-y"
    type AttrOrigin DOMUIEventPageYPropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventPageY
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMUIEventViewPropertyInfo
instance AttrInfo DOMUIEventViewPropertyInfo where
    type AttrAllowedOps DOMUIEventViewPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMUIEventViewPropertyInfo = IsDOMUIEvent
    type AttrSetTypeConstraint DOMUIEventViewPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMUIEventViewPropertyInfo = (~) ()
    type AttrTransferType DOMUIEventViewPropertyInfo = ()
    type AttrGetType DOMUIEventViewPropertyInfo = (Maybe WebKit2WebExtension.DOMDOMWindow.DOMDOMWindow)
    type AttrLabel DOMUIEventViewPropertyInfo = "view"
    type AttrOrigin DOMUIEventViewPropertyInfo = DOMUIEvent
    attrGet = getDOMUIEventView
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMUIEvent
type instance O.AttributeList DOMUIEvent = DOMUIEventAttributeList
type DOMUIEventAttributeList = ('[ '("bubbles", WebKit2WebExtension.DOMEvent.DOMEventBubblesPropertyInfo), '("cancelBubble", WebKit2WebExtension.DOMEvent.DOMEventCancelBubblePropertyInfo), '("cancelable", WebKit2WebExtension.DOMEvent.DOMEventCancelablePropertyInfo), '("charCode", DOMUIEventCharCodePropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("currentTarget", WebKit2WebExtension.DOMEvent.DOMEventCurrentTargetPropertyInfo), '("detail", DOMUIEventDetailPropertyInfo), '("eventPhase", WebKit2WebExtension.DOMEvent.DOMEventEventPhasePropertyInfo), '("keyCode", DOMUIEventKeyCodePropertyInfo), '("layerX", DOMUIEventLayerXPropertyInfo), '("layerY", DOMUIEventLayerYPropertyInfo), '("pageX", DOMUIEventPageXPropertyInfo), '("pageY", DOMUIEventPageYPropertyInfo), '("returnValue", WebKit2WebExtension.DOMEvent.DOMEventReturnValuePropertyInfo), '("srcElement", WebKit2WebExtension.DOMEvent.DOMEventSrcElementPropertyInfo), '("target", WebKit2WebExtension.DOMEvent.DOMEventTargetPropertyInfo), '("timeStamp", WebKit2WebExtension.DOMEvent.DOMEventTimeStampPropertyInfo), '("type", WebKit2WebExtension.DOMEvent.DOMEventTypePropertyInfo), '("view", DOMUIEventViewPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMUIEventCharCode :: AttrLabelProxy "charCode"
dOMUIEventCharCode = AttrLabelProxy

dOMUIEventDetail :: AttrLabelProxy "detail"
dOMUIEventDetail = AttrLabelProxy

dOMUIEventKeyCode :: AttrLabelProxy "keyCode"
dOMUIEventKeyCode = AttrLabelProxy

dOMUIEventLayerX :: AttrLabelProxy "layerX"
dOMUIEventLayerX = AttrLabelProxy

dOMUIEventLayerY :: AttrLabelProxy "layerY"
dOMUIEventLayerY = AttrLabelProxy

dOMUIEventPageX :: AttrLabelProxy "pageX"
dOMUIEventPageX = AttrLabelProxy

dOMUIEventPageY :: AttrLabelProxy "pageY"
dOMUIEventPageY = AttrLabelProxy

dOMUIEventView :: AttrLabelProxy "view"
dOMUIEventView = AttrLabelProxy

#endif

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

#endif

-- method DOMUIEvent::get_char_code
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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_ui_event_get_char_code" webkit_dom_ui_event_get_char_code :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO CLong

{-# DEPRECATED dOMUIEventGetCharCode ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventGetCharCode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMUIEventGetCharCode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMUIEvent a) =>
a -> m CLong
dOMUIEventGetCharCode 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMUIEvent -> IO CLong
webkit_dom_ui_event_get_char_code Ptr DOMUIEvent
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 DOMUIEventGetCharCodeMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetCharCodeMethodInfo a signature where
    overloadedMethod = dOMUIEventGetCharCode

instance O.OverloadedMethodInfo DOMUIEventGetCharCodeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetCharCode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetCharCode"
        }


#endif

-- method DOMUIEvent::get_detail
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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_ui_event_get_detail" webkit_dom_ui_event_get_detail :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO CLong

{-# DEPRECATED dOMUIEventGetDetail ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventGetDetail ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMUIEventGetDetail :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMUIEvent a) =>
a -> m CLong
dOMUIEventGetDetail 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMUIEvent -> IO CLong
webkit_dom_ui_event_get_detail Ptr DOMUIEvent
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 DOMUIEventGetDetailMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetDetailMethodInfo a signature where
    overloadedMethod = dOMUIEventGetDetail

instance O.OverloadedMethodInfo DOMUIEventGetDetailMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetDetail",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetDetail"
        }


#endif

-- method DOMUIEvent::get_key_code
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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_ui_event_get_key_code" webkit_dom_ui_event_get_key_code :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO CLong

{-# DEPRECATED dOMUIEventGetKeyCode ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventGetKeyCode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMUIEventGetKeyCode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMUIEvent a) =>
a -> m CLong
dOMUIEventGetKeyCode 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMUIEvent -> IO CLong
webkit_dom_ui_event_get_key_code Ptr DOMUIEvent
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 DOMUIEventGetKeyCodeMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetKeyCodeMethodInfo a signature where
    overloadedMethod = dOMUIEventGetKeyCode

instance O.OverloadedMethodInfo DOMUIEventGetKeyCodeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetKeyCode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetKeyCode"
        }


#endif

-- method DOMUIEvent::get_layer_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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_ui_event_get_layer_x" webkit_dom_ui_event_get_layer_x :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO CLong

{-# DEPRECATED dOMUIEventGetLayerX ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventGetLayerX ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMUIEventGetLayerX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMUIEvent a) =>
a -> m CLong
dOMUIEventGetLayerX 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMUIEvent -> IO CLong
webkit_dom_ui_event_get_layer_x Ptr DOMUIEvent
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 DOMUIEventGetLayerXMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetLayerXMethodInfo a signature where
    overloadedMethod = dOMUIEventGetLayerX

instance O.OverloadedMethodInfo DOMUIEventGetLayerXMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetLayerX",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetLayerX"
        }


#endif

-- method DOMUIEvent::get_layer_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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_ui_event_get_layer_y" webkit_dom_ui_event_get_layer_y :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO CLong

{-# DEPRECATED dOMUIEventGetLayerY ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventGetLayerY ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMUIEventGetLayerY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMUIEvent a) =>
a -> m CLong
dOMUIEventGetLayerY 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMUIEvent -> IO CLong
webkit_dom_ui_event_get_layer_y Ptr DOMUIEvent
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 DOMUIEventGetLayerYMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetLayerYMethodInfo a signature where
    overloadedMethod = dOMUIEventGetLayerY

instance O.OverloadedMethodInfo DOMUIEventGetLayerYMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetLayerY",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetLayerY"
        }


#endif

-- method DOMUIEvent::get_page_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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_ui_event_get_page_x" webkit_dom_ui_event_get_page_x :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO CLong

{-# DEPRECATED dOMUIEventGetPageX ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventGetPageX ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMUIEventGetPageX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMUIEvent a) =>
a -> m CLong
dOMUIEventGetPageX 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMUIEvent -> IO CLong
webkit_dom_ui_event_get_page_x Ptr DOMUIEvent
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 DOMUIEventGetPageXMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetPageXMethodInfo a signature where
    overloadedMethod = dOMUIEventGetPageX

instance O.OverloadedMethodInfo DOMUIEventGetPageXMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetPageX",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetPageX"
        }


#endif

-- method DOMUIEvent::get_page_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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_ui_event_get_page_y" webkit_dom_ui_event_get_page_y :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO CLong

{-# DEPRECATED dOMUIEventGetPageY ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventGetPageY ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> m CLong
    -- ^ __Returns:__ A @/glong/@
dOMUIEventGetPageY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDOMUIEvent a) =>
a -> m CLong
dOMUIEventGetPageY 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CLong
result <- Ptr DOMUIEvent -> IO CLong
webkit_dom_ui_event_get_page_y Ptr DOMUIEvent
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 DOMUIEventGetPageYMethodInfo
instance (signature ~ (m CLong), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetPageYMethodInfo a signature where
    overloadedMethod = dOMUIEventGetPageY

instance O.OverloadedMethodInfo DOMUIEventGetPageYMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetPageY",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetPageY"
        }


#endif

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

foreign import ccall "webkit_dom_ui_event_get_view" webkit_dom_ui_event_get_view :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    IO (Ptr WebKit2WebExtension.DOMDOMWindow.DOMDOMWindow)

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

#if defined(ENABLE_OVERLOADING)
data DOMUIEventGetViewMethodInfo
instance (signature ~ (m WebKit2WebExtension.DOMDOMWindow.DOMDOMWindow), MonadIO m, IsDOMUIEvent a) => O.OverloadedMethod DOMUIEventGetViewMethodInfo a signature where
    overloadedMethod = dOMUIEventGetView

instance O.OverloadedMethodInfo DOMUIEventGetViewMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventGetView",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventGetView"
        }


#endif

-- method DOMUIEvent::init_ui_event
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMUIEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMUIEvent"
--                 , 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
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_ui_event_init_ui_event" webkit_dom_ui_event_init_ui_event :: 
    Ptr DOMUIEvent ->                       -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMUIEvent"})
    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
    IO ()

{-# DEPRECATED dOMUIEventInitUiEvent ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMUIEventInitUiEvent ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMUIEvent a, WebKit2WebExtension.DOMDOMWindow.IsDOMDOMWindow b) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMUIEvent.DOMUIEvent'
    -> 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/@
    -> m ()
dOMUIEventInitUiEvent :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDOMUIEvent a, IsDOMDOMWindow b) =>
a -> Text -> Bool -> Bool -> b -> CLong -> m ()
dOMUIEventInitUiEvent a
self Text
type_ Bool
canBubble Bool
cancelable b
view CLong
detail = 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 DOMUIEvent
self' <- a -> IO (Ptr DOMUIEvent)
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
    Ptr DOMUIEvent
-> CString -> CInt -> CInt -> Ptr DOMDOMWindow -> CLong -> IO ()
webkit_dom_ui_event_init_ui_event Ptr DOMUIEvent
self' CString
type_' CInt
canBubble' CInt
cancelable' Ptr DOMDOMWindow
view' CLong
detail
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
view
    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 DOMUIEventInitUiEventMethodInfo
instance (signature ~ (T.Text -> Bool -> Bool -> b -> CLong -> m ()), MonadIO m, IsDOMUIEvent a, WebKit2WebExtension.DOMDOMWindow.IsDOMDOMWindow b) => O.OverloadedMethod DOMUIEventInitUiEventMethodInfo a signature where
    overloadedMethod = dOMUIEventInitUiEvent

instance O.OverloadedMethodInfo DOMUIEventInitUiEventMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.WebKit2WebExtension.Objects.DOMUIEvent.dOMUIEventInitUiEvent",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-webkit2webextension-4.0.26/docs/GI-WebKit2WebExtension-Objects-DOMUIEvent.html#v:dOMUIEventInitUiEvent"
        }


#endif