{-# 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.DOMClientRect
    ( 

-- * Exported types
    DOMClientRect(..)                       ,
    IsDOMClientRect                         ,
    toDOMClientRect                         ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDOMClientRectMethod              ,
#endif


-- ** getBottom #method:getBottom#

#if defined(ENABLE_OVERLOADING)
    DOMClientRectGetBottomMethodInfo        ,
#endif
    dOMClientRectGetBottom                  ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    DOMClientRectGetHeightMethodInfo        ,
#endif
    dOMClientRectGetHeight                  ,


-- ** getLeft #method:getLeft#

#if defined(ENABLE_OVERLOADING)
    DOMClientRectGetLeftMethodInfo          ,
#endif
    dOMClientRectGetLeft                    ,


-- ** getRight #method:getRight#

#if defined(ENABLE_OVERLOADING)
    DOMClientRectGetRightMethodInfo         ,
#endif
    dOMClientRectGetRight                   ,


-- ** getTop #method:getTop#

#if defined(ENABLE_OVERLOADING)
    DOMClientRectGetTopMethodInfo           ,
#endif
    dOMClientRectGetTop                     ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    DOMClientRectGetWidthMethodInfo         ,
#endif
    dOMClientRectGetWidth                   ,




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

#if defined(ENABLE_OVERLOADING)
    DOMClientRectBottomPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMClientRectBottom                     ,
#endif
    getDOMClientRectBottom                  ,


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

#if defined(ENABLE_OVERLOADING)
    DOMClientRectHeightPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMClientRectHeight                     ,
#endif
    getDOMClientRectHeight                  ,


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

#if defined(ENABLE_OVERLOADING)
    DOMClientRectLeftPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMClientRectLeft                       ,
#endif
    getDOMClientRectLeft                    ,


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

#if defined(ENABLE_OVERLOADING)
    DOMClientRectRightPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMClientRectRight                      ,
#endif
    getDOMClientRectRight                   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMClientRectTopPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMClientRectTop                        ,
#endif
    getDOMClientRectTop                     ,


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

#if defined(ENABLE_OVERLOADING)
    DOMClientRectWidthPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMClientRectWidth                      ,
#endif
    getDOMClientRectWidth                   ,




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

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

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

foreign import ccall "webkit_dom_client_rect_get_type"
    c_webkit_dom_client_rect_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMClientRect where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_client_rect_get_type

instance B.Types.GObject DOMClientRect

-- | Convert 'DOMClientRect' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DOMClientRect where
    toGValue :: DOMClientRect -> IO GValue
toGValue DOMClientRect
o = do
        GType
gtype <- IO GType
c_webkit_dom_client_rect_get_type
        DOMClientRect -> (Ptr DOMClientRect -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DOMClientRect
o (GType
-> (GValue -> Ptr DOMClientRect -> IO ())
-> Ptr DOMClientRect
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DOMClientRect -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DOMClientRect
fromGValue GValue
gv = do
        Ptr DOMClientRect
ptr <- GValue -> IO (Ptr DOMClientRect)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DOMClientRect)
        (ManagedPtr DOMClientRect -> DOMClientRect)
-> Ptr DOMClientRect -> IO DOMClientRect
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DOMClientRect -> DOMClientRect
DOMClientRect Ptr DOMClientRect
ptr
        
    

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMClientRectMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMClientRectMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMClientRectMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMClientRectMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMClientRectMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMClientRectMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMClientRectMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMClientRectMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMClientRectMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMClientRectMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMClientRectMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMClientRectMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMClientRectMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMClientRectMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMClientRectMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMClientRectMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMClientRectMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMClientRectMethod "getBottom" o = DOMClientRectGetBottomMethodInfo
    ResolveDOMClientRectMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMClientRectMethod "getHeight" o = DOMClientRectGetHeightMethodInfo
    ResolveDOMClientRectMethod "getLeft" o = DOMClientRectGetLeftMethodInfo
    ResolveDOMClientRectMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMClientRectMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMClientRectMethod "getRight" o = DOMClientRectGetRightMethodInfo
    ResolveDOMClientRectMethod "getTop" o = DOMClientRectGetTopMethodInfo
    ResolveDOMClientRectMethod "getWidth" o = DOMClientRectGetWidthMethodInfo
    ResolveDOMClientRectMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMClientRectMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMClientRectMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMClientRectMethod l o = O.MethodResolutionFailed l o

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

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMClientRectBottomPropertyInfo
instance AttrInfo DOMClientRectBottomPropertyInfo where
    type AttrAllowedOps DOMClientRectBottomPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMClientRectBottomPropertyInfo = IsDOMClientRect
    type AttrSetTypeConstraint DOMClientRectBottomPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMClientRectBottomPropertyInfo = (~) ()
    type AttrTransferType DOMClientRectBottomPropertyInfo = ()
    type AttrGetType DOMClientRectBottomPropertyInfo = Float
    type AttrLabel DOMClientRectBottomPropertyInfo = "bottom"
    type AttrOrigin DOMClientRectBottomPropertyInfo = DOMClientRect
    attrGet = getDOMClientRectBottom
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMClientRectHeightPropertyInfo
instance AttrInfo DOMClientRectHeightPropertyInfo where
    type AttrAllowedOps DOMClientRectHeightPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMClientRectHeightPropertyInfo = IsDOMClientRect
    type AttrSetTypeConstraint DOMClientRectHeightPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMClientRectHeightPropertyInfo = (~) ()
    type AttrTransferType DOMClientRectHeightPropertyInfo = ()
    type AttrGetType DOMClientRectHeightPropertyInfo = Float
    type AttrLabel DOMClientRectHeightPropertyInfo = "height"
    type AttrOrigin DOMClientRectHeightPropertyInfo = DOMClientRect
    attrGet = getDOMClientRectHeight
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMClientRectLeftPropertyInfo
instance AttrInfo DOMClientRectLeftPropertyInfo where
    type AttrAllowedOps DOMClientRectLeftPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMClientRectLeftPropertyInfo = IsDOMClientRect
    type AttrSetTypeConstraint DOMClientRectLeftPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMClientRectLeftPropertyInfo = (~) ()
    type AttrTransferType DOMClientRectLeftPropertyInfo = ()
    type AttrGetType DOMClientRectLeftPropertyInfo = Float
    type AttrLabel DOMClientRectLeftPropertyInfo = "left"
    type AttrOrigin DOMClientRectLeftPropertyInfo = DOMClientRect
    attrGet = getDOMClientRectLeft
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMClientRectRightPropertyInfo
instance AttrInfo DOMClientRectRightPropertyInfo where
    type AttrAllowedOps DOMClientRectRightPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMClientRectRightPropertyInfo = IsDOMClientRect
    type AttrSetTypeConstraint DOMClientRectRightPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMClientRectRightPropertyInfo = (~) ()
    type AttrTransferType DOMClientRectRightPropertyInfo = ()
    type AttrGetType DOMClientRectRightPropertyInfo = Float
    type AttrLabel DOMClientRectRightPropertyInfo = "right"
    type AttrOrigin DOMClientRectRightPropertyInfo = DOMClientRect
    attrGet = getDOMClientRectRight
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMClientRectTopPropertyInfo
instance AttrInfo DOMClientRectTopPropertyInfo where
    type AttrAllowedOps DOMClientRectTopPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMClientRectTopPropertyInfo = IsDOMClientRect
    type AttrSetTypeConstraint DOMClientRectTopPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMClientRectTopPropertyInfo = (~) ()
    type AttrTransferType DOMClientRectTopPropertyInfo = ()
    type AttrGetType DOMClientRectTopPropertyInfo = Float
    type AttrLabel DOMClientRectTopPropertyInfo = "top"
    type AttrOrigin DOMClientRectTopPropertyInfo = DOMClientRect
    attrGet = getDOMClientRectTop
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data DOMClientRectWidthPropertyInfo
instance AttrInfo DOMClientRectWidthPropertyInfo where
    type AttrAllowedOps DOMClientRectWidthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMClientRectWidthPropertyInfo = IsDOMClientRect
    type AttrSetTypeConstraint DOMClientRectWidthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMClientRectWidthPropertyInfo = (~) ()
    type AttrTransferType DOMClientRectWidthPropertyInfo = ()
    type AttrGetType DOMClientRectWidthPropertyInfo = Float
    type AttrLabel DOMClientRectWidthPropertyInfo = "width"
    type AttrOrigin DOMClientRectWidthPropertyInfo = DOMClientRect
    attrGet = getDOMClientRectWidth
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMClientRect
type instance O.AttributeList DOMClientRect = DOMClientRectAttributeList
type DOMClientRectAttributeList = ('[ '("bottom", DOMClientRectBottomPropertyInfo), '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("height", DOMClientRectHeightPropertyInfo), '("left", DOMClientRectLeftPropertyInfo), '("right", DOMClientRectRightPropertyInfo), '("top", DOMClientRectTopPropertyInfo), '("width", DOMClientRectWidthPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMClientRectBottom :: AttrLabelProxy "bottom"
dOMClientRectBottom = AttrLabelProxy

dOMClientRectHeight :: AttrLabelProxy "height"
dOMClientRectHeight = AttrLabelProxy

dOMClientRectLeft :: AttrLabelProxy "left"
dOMClientRectLeft = AttrLabelProxy

dOMClientRectRight :: AttrLabelProxy "right"
dOMClientRectRight = AttrLabelProxy

dOMClientRectTop :: AttrLabelProxy "top"
dOMClientRectTop = AttrLabelProxy

dOMClientRectWidth :: AttrLabelProxy "width"
dOMClientRectWidth = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "webkit_dom_client_rect_get_bottom" webkit_dom_client_rect_get_bottom :: 
    Ptr DOMClientRect ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMClientRect"})
    IO CFloat

{-# DEPRECATED dOMClientRectGetBottom ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | Returns the bottom coordinate of /@self@/, relative to the viewport.
-- 
-- /Since: 2.18/
dOMClientRectGetBottom ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMClientRect a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMClientRect.DOMClientRect'
    -> m Float
    -- ^ __Returns:__ A @/gfloat/@
dOMClientRectGetBottom :: a -> m Float
dOMClientRectGetBottom a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMClientRect
self' <- a -> IO (Ptr DOMClientRect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr DOMClientRect -> IO CFloat
webkit_dom_client_rect_get_bottom Ptr DOMClientRect
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data DOMClientRectGetBottomMethodInfo
instance (signature ~ (m Float), MonadIO m, IsDOMClientRect a) => O.MethodInfo DOMClientRectGetBottomMethodInfo a signature where
    overloadedMethod = dOMClientRectGetBottom

#endif

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

foreign import ccall "webkit_dom_client_rect_get_height" webkit_dom_client_rect_get_height :: 
    Ptr DOMClientRect ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMClientRect"})
    IO CFloat

{-# DEPRECATED dOMClientRectGetHeight ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | Returns the height of /@self@/.
-- 
-- /Since: 2.18/
dOMClientRectGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMClientRect a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMClientRect.DOMClientRect'
    -> m Float
    -- ^ __Returns:__ A @/gfloat/@
dOMClientRectGetHeight :: a -> m Float
dOMClientRectGetHeight a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMClientRect
self' <- a -> IO (Ptr DOMClientRect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr DOMClientRect -> IO CFloat
webkit_dom_client_rect_get_height Ptr DOMClientRect
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data DOMClientRectGetHeightMethodInfo
instance (signature ~ (m Float), MonadIO m, IsDOMClientRect a) => O.MethodInfo DOMClientRectGetHeightMethodInfo a signature where
    overloadedMethod = dOMClientRectGetHeight

#endif

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

foreign import ccall "webkit_dom_client_rect_get_left" webkit_dom_client_rect_get_left :: 
    Ptr DOMClientRect ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMClientRect"})
    IO CFloat

{-# DEPRECATED dOMClientRectGetLeft ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | Returns the left coordinate of /@self@/, relative to the viewport.
-- 
-- /Since: 2.18/
dOMClientRectGetLeft ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMClientRect a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMClientRect.DOMClientRect'
    -> m Float
    -- ^ __Returns:__ A @/gfloat/@
dOMClientRectGetLeft :: a -> m Float
dOMClientRectGetLeft a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMClientRect
self' <- a -> IO (Ptr DOMClientRect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr DOMClientRect -> IO CFloat
webkit_dom_client_rect_get_left Ptr DOMClientRect
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data DOMClientRectGetLeftMethodInfo
instance (signature ~ (m Float), MonadIO m, IsDOMClientRect a) => O.MethodInfo DOMClientRectGetLeftMethodInfo a signature where
    overloadedMethod = dOMClientRectGetLeft

#endif

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

foreign import ccall "webkit_dom_client_rect_get_right" webkit_dom_client_rect_get_right :: 
    Ptr DOMClientRect ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMClientRect"})
    IO CFloat

{-# DEPRECATED dOMClientRectGetRight ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | Returns the right coordinate of /@self@/, relative to the viewport.
-- 
-- /Since: 2.18/
dOMClientRectGetRight ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMClientRect a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMClientRect.DOMClientRect'
    -> m Float
    -- ^ __Returns:__ A @/gfloat/@
dOMClientRectGetRight :: a -> m Float
dOMClientRectGetRight a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMClientRect
self' <- a -> IO (Ptr DOMClientRect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr DOMClientRect -> IO CFloat
webkit_dom_client_rect_get_right Ptr DOMClientRect
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data DOMClientRectGetRightMethodInfo
instance (signature ~ (m Float), MonadIO m, IsDOMClientRect a) => O.MethodInfo DOMClientRectGetRightMethodInfo a signature where
    overloadedMethod = dOMClientRectGetRight

#endif

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

foreign import ccall "webkit_dom_client_rect_get_top" webkit_dom_client_rect_get_top :: 
    Ptr DOMClientRect ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMClientRect"})
    IO CFloat

{-# DEPRECATED dOMClientRectGetTop ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | Returns the top coordinate of /@self@/, relative to the viewport.
-- 
-- /Since: 2.18/
dOMClientRectGetTop ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMClientRect a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMClientRect.DOMClientRect'
    -> m Float
    -- ^ __Returns:__ A @/gfloat/@
dOMClientRectGetTop :: a -> m Float
dOMClientRectGetTop a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMClientRect
self' <- a -> IO (Ptr DOMClientRect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr DOMClientRect -> IO CFloat
webkit_dom_client_rect_get_top Ptr DOMClientRect
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data DOMClientRectGetTopMethodInfo
instance (signature ~ (m Float), MonadIO m, IsDOMClientRect a) => O.MethodInfo DOMClientRectGetTopMethodInfo a signature where
    overloadedMethod = dOMClientRectGetTop

#endif

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

foreign import ccall "webkit_dom_client_rect_get_width" webkit_dom_client_rect_get_width :: 
    Ptr DOMClientRect ->                    -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMClientRect"})
    IO CFloat

{-# DEPRECATED dOMClientRectGetWidth ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | Returns the width of /@self@/.
-- 
-- /Since: 2.18/
dOMClientRectGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMClientRect a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMClientRect.DOMClientRect'
    -> m Float
    -- ^ __Returns:__ A @/gfloat/@
dOMClientRectGetWidth :: a -> m Float
dOMClientRectGetWidth a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMClientRect
self' <- a -> IO (Ptr DOMClientRect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr DOMClientRect -> IO CFloat
webkit_dom_client_rect_get_width Ptr DOMClientRect
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data DOMClientRectGetWidthMethodInfo
instance (signature ~ (m Float), MonadIO m, IsDOMClientRect a) => O.MethodInfo DOMClientRectGetWidthMethodInfo a signature where
    overloadedMethod = dOMClientRectGetWidth

#endif