{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkOverlay is a container which contains a single main child, on top
-- of which it can place “overlay” widgets. The position of each overlay
-- widget is determined by its t'GI.Gtk.Objects.Widget.Widget':@/halign/@ and t'GI.Gtk.Objects.Widget.Widget':@/valign/@
-- properties. E.g. a widget with both alignments set to 'GI.Gtk.Enums.AlignStart'
-- will be placed at the top left corner of the GtkOverlay container,
-- whereas an overlay with halign set to 'GI.Gtk.Enums.AlignCenter' and valign set
-- to 'GI.Gtk.Enums.AlignEnd' will be placed a the bottom edge of the GtkOverlay,
-- horizontally centered. The position can be adjusted by setting the margin
-- properties of the child to non-zero values.
-- 
-- More complicated placement of overlays is possible by connecting
-- to the [getChildPosition]("GI.Gtk.Objects.Overlay#g:signal:getChildPosition") signal.
-- 
-- An overlay’s minimum and natural sizes are those of its main child. The sizes
-- of overlay children are not considered when measuring these preferred sizes.
-- 
-- = GtkOverlay as GtkBuildable
-- 
-- The GtkOverlay implementation of the GtkBuildable interface
-- supports placing a child as an overlay by specifying “overlay” as
-- the “type” attribute of a @\<child>@ element.
-- 
-- = CSS nodes
-- 
-- GtkOverlay has a single CSS node with the name “overlay”. Overlay children
-- whose alignments cause them to be positioned at an edge get the style classes
-- “.left”, “.right”, “.top”, and\/or “.bottom” according to their position.

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

module GI.Gtk.Objects.Overlay
    ( 

-- * Exported types
    Overlay(..)                             ,
    IsOverlay                               ,
    toOverlay                               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addOverlay]("GI.Gtk.Objects.Overlay#g:method:addOverlay"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeOverlay]("GI.Gtk.Objects.Overlay#g:method:removeOverlay"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChild]("GI.Gtk.Objects.Overlay#g:method:getChild"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipOverlay]("GI.Gtk.Objects.Overlay#g:method:getClipOverlay"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getMeasureOverlay]("GI.Gtk.Objects.Overlay#g:method:getMeasureOverlay"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChild]("GI.Gtk.Objects.Overlay#g:method:setChild"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setClipOverlay]("GI.Gtk.Objects.Overlay#g:method:setClipOverlay"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setMeasureOverlay]("GI.Gtk.Objects.Overlay#g:method:setMeasureOverlay"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveOverlayMethod                    ,
#endif

-- ** addOverlay #method:addOverlay#

#if defined(ENABLE_OVERLOADING)
    OverlayAddOverlayMethodInfo             ,
#endif
    overlayAddOverlay                       ,


-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    OverlayGetChildMethodInfo               ,
#endif
    overlayGetChild                         ,


-- ** getClipOverlay #method:getClipOverlay#

#if defined(ENABLE_OVERLOADING)
    OverlayGetClipOverlayMethodInfo         ,
#endif
    overlayGetClipOverlay                   ,


-- ** getMeasureOverlay #method:getMeasureOverlay#

#if defined(ENABLE_OVERLOADING)
    OverlayGetMeasureOverlayMethodInfo      ,
#endif
    overlayGetMeasureOverlay                ,


-- ** new #method:new#

    overlayNew                              ,


-- ** removeOverlay #method:removeOverlay#

#if defined(ENABLE_OVERLOADING)
    OverlayRemoveOverlayMethodInfo          ,
#endif
    overlayRemoveOverlay                    ,


-- ** setChild #method:setChild#

#if defined(ENABLE_OVERLOADING)
    OverlaySetChildMethodInfo               ,
#endif
    overlaySetChild                         ,


-- ** setClipOverlay #method:setClipOverlay#

#if defined(ENABLE_OVERLOADING)
    OverlaySetClipOverlayMethodInfo         ,
#endif
    overlaySetClipOverlay                   ,


-- ** setMeasureOverlay #method:setMeasureOverlay#

#if defined(ENABLE_OVERLOADING)
    OverlaySetMeasureOverlayMethodInfo      ,
#endif
    overlaySetMeasureOverlay                ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    OverlayChildPropertyInfo                ,
#endif
    clearOverlayChild                       ,
    constructOverlayChild                   ,
    getOverlayChild                         ,
#if defined(ENABLE_OVERLOADING)
    overlayChild                            ,
#endif
    setOverlayChild                         ,




 -- * Signals


-- ** getChildPosition #signal:getChildPosition#

#if defined(ENABLE_OVERLOADING)
    OverlayGetChildPositionSignalInfo       ,
#endif




    ) 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.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_overlay_get_type"
    c_gtk_overlay_get_type :: IO B.Types.GType

instance B.Types.TypedObject Overlay where
    glibType :: IO GType
glibType = IO GType
c_gtk_overlay_get_type

instance B.Types.GObject Overlay

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

instance O.HasParentTypes Overlay
type instance O.ParentTypes Overlay = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveOverlayMethod (t :: Symbol) (o :: *) :: * where
    ResolveOverlayMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveOverlayMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveOverlayMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveOverlayMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveOverlayMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveOverlayMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveOverlayMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveOverlayMethod "addOverlay" o = OverlayAddOverlayMethodInfo
    ResolveOverlayMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveOverlayMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveOverlayMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveOverlayMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveOverlayMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveOverlayMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveOverlayMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveOverlayMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveOverlayMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveOverlayMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveOverlayMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveOverlayMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveOverlayMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveOverlayMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveOverlayMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveOverlayMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveOverlayMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveOverlayMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveOverlayMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveOverlayMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveOverlayMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveOverlayMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveOverlayMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveOverlayMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveOverlayMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveOverlayMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveOverlayMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveOverlayMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveOverlayMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveOverlayMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveOverlayMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveOverlayMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveOverlayMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveOverlayMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveOverlayMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveOverlayMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveOverlayMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveOverlayMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveOverlayMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveOverlayMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveOverlayMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveOverlayMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveOverlayMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveOverlayMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveOverlayMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveOverlayMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveOverlayMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveOverlayMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveOverlayMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveOverlayMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveOverlayMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveOverlayMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveOverlayMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveOverlayMethod "removeOverlay" o = OverlayRemoveOverlayMethodInfo
    ResolveOverlayMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveOverlayMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveOverlayMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveOverlayMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveOverlayMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveOverlayMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveOverlayMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveOverlayMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveOverlayMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveOverlayMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveOverlayMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveOverlayMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveOverlayMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveOverlayMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveOverlayMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveOverlayMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveOverlayMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveOverlayMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveOverlayMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveOverlayMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveOverlayMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveOverlayMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveOverlayMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveOverlayMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveOverlayMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveOverlayMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveOverlayMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveOverlayMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveOverlayMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveOverlayMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveOverlayMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveOverlayMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveOverlayMethod "getChild" o = OverlayGetChildMethodInfo
    ResolveOverlayMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveOverlayMethod "getClipOverlay" o = OverlayGetClipOverlayMethodInfo
    ResolveOverlayMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveOverlayMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveOverlayMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveOverlayMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveOverlayMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveOverlayMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveOverlayMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveOverlayMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveOverlayMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveOverlayMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveOverlayMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveOverlayMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveOverlayMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveOverlayMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveOverlayMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveOverlayMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveOverlayMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveOverlayMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveOverlayMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveOverlayMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveOverlayMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveOverlayMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveOverlayMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveOverlayMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveOverlayMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveOverlayMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveOverlayMethod "getMeasureOverlay" o = OverlayGetMeasureOverlayMethodInfo
    ResolveOverlayMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveOverlayMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveOverlayMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveOverlayMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveOverlayMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveOverlayMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveOverlayMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveOverlayMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveOverlayMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveOverlayMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveOverlayMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveOverlayMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveOverlayMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveOverlayMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveOverlayMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveOverlayMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveOverlayMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveOverlayMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveOverlayMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveOverlayMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveOverlayMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveOverlayMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveOverlayMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveOverlayMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveOverlayMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveOverlayMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveOverlayMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveOverlayMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveOverlayMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveOverlayMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveOverlayMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveOverlayMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveOverlayMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveOverlayMethod "setChild" o = OverlaySetChildMethodInfo
    ResolveOverlayMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveOverlayMethod "setClipOverlay" o = OverlaySetClipOverlayMethodInfo
    ResolveOverlayMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveOverlayMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveOverlayMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveOverlayMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveOverlayMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveOverlayMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveOverlayMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveOverlayMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveOverlayMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveOverlayMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveOverlayMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveOverlayMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveOverlayMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveOverlayMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveOverlayMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveOverlayMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveOverlayMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveOverlayMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveOverlayMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveOverlayMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveOverlayMethod "setMeasureOverlay" o = OverlaySetMeasureOverlayMethodInfo
    ResolveOverlayMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveOverlayMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveOverlayMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveOverlayMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveOverlayMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveOverlayMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveOverlayMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveOverlayMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveOverlayMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveOverlayMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveOverlayMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveOverlayMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveOverlayMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveOverlayMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveOverlayMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveOverlayMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- XXX Could not generate signal Overlay::get-child-position
-- Error was : 
-- Not implemented: Unexpected transfer type for "allocation"
#if defined(ENABLE_OVERLOADING)
data OverlayGetChildPositionSignalInfo
instance SignalInfo OverlayGetChildPositionSignalInfo where
    type HaskellCallbackType OverlayGetChildPositionSignalInfo = B.Signals.SignalCodeGenError "Overlay::get-child-position"
    connectSignal = undefined

#endif

-- VVV Prop "child"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Widget"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

-- | Set the value of the “@child@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' overlay [ #child 'Data.GI.Base.Attributes.:=' value ]
-- @
setOverlayChild :: (MonadIO m, IsOverlay o, Gtk.Widget.IsWidget a) => o -> a -> m ()
setOverlayChild :: forall (m :: * -> *) o a.
(MonadIO m, IsOverlay o, IsWidget a) =>
o -> a -> m ()
setOverlayChild o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"child" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@child@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructOverlayChild :: (IsOverlay o, MIO.MonadIO m, Gtk.Widget.IsWidget a) => a -> m (GValueConstruct o)
constructOverlayChild :: forall o (m :: * -> *) a.
(IsOverlay o, MonadIO m, IsWidget a) =>
a -> m (GValueConstruct o)
constructOverlayChild a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"child" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@child@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #child
-- @
clearOverlayChild :: (MonadIO m, IsOverlay o) => o -> m ()
clearOverlayChild :: forall (m :: * -> *) o. (MonadIO m, IsOverlay o) => o -> m ()
clearOverlayChild o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Widget -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"child" (Maybe Widget
forall a. Maybe a
Nothing :: Maybe Gtk.Widget.Widget)

#if defined(ENABLE_OVERLOADING)
data OverlayChildPropertyInfo
instance AttrInfo OverlayChildPropertyInfo where
    type AttrAllowedOps OverlayChildPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint OverlayChildPropertyInfo = IsOverlay
    type AttrSetTypeConstraint OverlayChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint OverlayChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType OverlayChildPropertyInfo = Gtk.Widget.Widget
    type AttrGetType OverlayChildPropertyInfo = (Maybe Gtk.Widget.Widget)
    type AttrLabel OverlayChildPropertyInfo = "child"
    type AttrOrigin OverlayChildPropertyInfo = Overlay
    attrGet = getOverlayChild
    attrSet = setOverlayChild
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructOverlayChild
    attrClear = clearOverlayChild
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Overlay
type instance O.AttributeList Overlay = OverlayAttributeList
type OverlayAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("child", OverlayChildPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
overlayChild :: AttrLabelProxy "child"
overlayChild = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Overlay = OverlaySignalList
type OverlaySignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("getChildPosition", OverlayGetChildPositionSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

-- method Overlay::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Overlay" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_new" gtk_overlay_new :: 
    IO (Ptr Overlay)

-- | Creates a new t'GI.Gtk.Objects.Overlay.Overlay'.
overlayNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Overlay
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Overlay.Overlay' object.
overlayNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Overlay
overlayNew  = IO Overlay -> m Overlay
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Overlay -> m Overlay) -> IO Overlay -> m Overlay
forall a b. (a -> b) -> a -> b
$ do
    Ptr Overlay
result <- IO (Ptr Overlay)
gtk_overlay_new
    Text -> Ptr Overlay -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"overlayNew" Ptr Overlay
result
    Overlay
result' <- ((ManagedPtr Overlay -> Overlay) -> Ptr Overlay -> IO Overlay
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Overlay -> Overlay
Overlay) Ptr Overlay
result
    Overlay -> IO Overlay
forall (m :: * -> *) a. Monad m => a -> m a
return Overlay
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Overlay::add_overlay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidget to be added to the container"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_add_overlay" gtk_overlay_add_overlay :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Adds /@widget@/ to /@overlay@/.
-- 
-- The widget will be stacked on top of the main widget
-- added with 'GI.Gtk.Objects.Overlay.overlaySetChild'.
-- 
-- The position at which /@widget@/ is placed is determined
-- from its t'GI.Gtk.Objects.Widget.Widget':@/halign/@ and t'GI.Gtk.Objects.Widget.Widget':@/valign/@ properties.
overlayAddOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> b
    -- ^ /@widget@/: a t'GI.Gtk.Objects.Widget.Widget' to be added to the container
    -> m ()
overlayAddOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsOverlay a, IsWidget b) =>
a -> b -> m ()
overlayAddOverlay a
overlay b
widget = 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 Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr Overlay -> Ptr Widget -> IO ()
gtk_overlay_add_overlay Ptr Overlay
overlay' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data OverlayAddOverlayMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) => O.OverloadedMethod OverlayAddOverlayMethodInfo a signature where
    overloadedMethod = overlayAddOverlay

instance O.OverloadedMethodInfo OverlayAddOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlayAddOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlayAddOverlay"
        }


#endif

-- method Overlay::get_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_get_child" gtk_overlay_get_child :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the child widget of /@overlay@/.
overlayGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the child widget of /@overlay@/
overlayGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOverlay a) =>
a -> m (Maybe Widget)
overlayGetChild a
overlay = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
result <- Ptr Overlay -> IO (Ptr Widget)
gtk_overlay_get_child Ptr Overlay
overlay'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult

#if defined(ENABLE_OVERLOADING)
data OverlayGetChildMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsOverlay a) => O.OverloadedMethod OverlayGetChildMethodInfo a signature where
    overloadedMethod = overlayGetChild

instance O.OverloadedMethodInfo OverlayGetChildMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlayGetChild",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlayGetChild"
        }


#endif

-- method Overlay::get_clip_overlay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an overlay child of #GtkOverlay"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_get_clip_overlay" gtk_overlay_get_clip_overlay :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO CInt

-- | Gets whether /@widget@/ should be clipped within the parent.
overlayGetClipOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> b
    -- ^ /@widget@/: an overlay child of t'GI.Gtk.Objects.Overlay.Overlay'
    -> m Bool
    -- ^ __Returns:__ whether the widget is clipped within the parent.
overlayGetClipOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsOverlay a, IsWidget b) =>
a -> b -> m Bool
overlayGetClipOverlay a
overlay b
widget = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    CInt
result <- Ptr Overlay -> Ptr Widget -> IO CInt
gtk_overlay_get_clip_overlay Ptr Overlay
overlay' Ptr Widget
widget'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data OverlayGetClipOverlayMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) => O.OverloadedMethod OverlayGetClipOverlayMethodInfo a signature where
    overloadedMethod = overlayGetClipOverlay

instance O.OverloadedMethodInfo OverlayGetClipOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlayGetClipOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlayGetClipOverlay"
        }


#endif

-- method Overlay::get_measure_overlay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an overlay child of #GtkOverlay"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_get_measure_overlay" gtk_overlay_get_measure_overlay :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO CInt

-- | Gets whether /@widget@/\'s size is included in the measurement of
-- /@overlay@/.
overlayGetMeasureOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> b
    -- ^ /@widget@/: an overlay child of t'GI.Gtk.Objects.Overlay.Overlay'
    -> m Bool
    -- ^ __Returns:__ whether the widget is measured
overlayGetMeasureOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsOverlay a, IsWidget b) =>
a -> b -> m Bool
overlayGetMeasureOverlay a
overlay b
widget = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    CInt
result <- Ptr Overlay -> Ptr Widget -> IO CInt
gtk_overlay_get_measure_overlay Ptr Overlay
overlay' Ptr Widget
widget'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data OverlayGetMeasureOverlayMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) => O.OverloadedMethod OverlayGetMeasureOverlayMethodInfo a signature where
    overloadedMethod = overlayGetMeasureOverlay

instance O.OverloadedMethodInfo OverlayGetMeasureOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlayGetMeasureOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlayGetMeasureOverlay"
        }


#endif

-- method Overlay::remove_overlay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidget to be removed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_remove_overlay" gtk_overlay_remove_overlay :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Removes an overlay that was added with 'GI.Gtk.Objects.Overlay.overlayAddOverlay'.
overlayRemoveOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> b
    -- ^ /@widget@/: a t'GI.Gtk.Objects.Widget.Widget' to be removed
    -> m ()
overlayRemoveOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsOverlay a, IsWidget b) =>
a -> b -> m ()
overlayRemoveOverlay a
overlay b
widget = 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 Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr Overlay -> Ptr Widget -> IO ()
gtk_overlay_remove_overlay Ptr Overlay
overlay' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data OverlayRemoveOverlayMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) => O.OverloadedMethod OverlayRemoveOverlayMethodInfo a signature where
    overloadedMethod = overlayRemoveOverlay

instance O.OverloadedMethodInfo OverlayRemoveOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlayRemoveOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlayRemoveOverlay"
        }


#endif

-- method Overlay::set_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child widget" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_set_child" gtk_overlay_set_child :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the child widget of /@overlay@/.
overlaySetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> Maybe (b)
    -- ^ /@child@/: the child widget
    -> m ()
overlaySetChild :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsOverlay a, IsWidget b) =>
a -> Maybe b -> m ()
overlaySetChild a
overlay Maybe b
child = 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 Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
maybeChild <- case Maybe b
child of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jChild -> do
            Ptr Widget
jChild' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jChild
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jChild'
    Ptr Overlay -> Ptr Widget -> IO ()
gtk_overlay_set_child Ptr Overlay
overlay' Ptr Widget
maybeChild
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
child b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data OverlaySetChildMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) => O.OverloadedMethod OverlaySetChildMethodInfo a signature where
    overloadedMethod = overlaySetChild

instance O.OverloadedMethodInfo OverlaySetChildMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlaySetChild",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlaySetChild"
        }


#endif

-- method Overlay::set_clip_overlay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an overlay child of #GtkOverlay"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "clip_overlay"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the child should be clipped"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_set_clip_overlay" gtk_overlay_set_clip_overlay :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    CInt ->                                 -- clip_overlay : TBasicType TBoolean
    IO ()

-- | Sets whether /@widget@/ should be clipped within the parent.
overlaySetClipOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> b
    -- ^ /@widget@/: an overlay child of t'GI.Gtk.Objects.Overlay.Overlay'
    -> Bool
    -- ^ /@clipOverlay@/: whether the child should be clipped
    -> m ()
overlaySetClipOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsOverlay a, IsWidget b) =>
a -> b -> Bool -> m ()
overlaySetClipOverlay a
overlay b
widget Bool
clipOverlay = 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 Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    let clipOverlay' :: CInt
clipOverlay' = (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
clipOverlay
    Ptr Overlay -> Ptr Widget -> CInt -> IO ()
gtk_overlay_set_clip_overlay Ptr Overlay
overlay' Ptr Widget
widget' CInt
clipOverlay'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data OverlaySetClipOverlayMethodInfo
instance (signature ~ (b -> Bool -> m ()), MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) => O.OverloadedMethod OverlaySetClipOverlayMethodInfo a signature where
    overloadedMethod = overlaySetClipOverlay

instance O.OverloadedMethodInfo OverlaySetClipOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlaySetClipOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlaySetClipOverlay"
        }


#endif

-- method Overlay::set_measure_overlay
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "overlay"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Overlay" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkOverlay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an overlay child of #GtkOverlay"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "measure"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the child should be measured"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_overlay_set_measure_overlay" gtk_overlay_set_measure_overlay :: 
    Ptr Overlay ->                          -- overlay : TInterface (Name {namespace = "Gtk", name = "Overlay"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    CInt ->                                 -- measure : TBasicType TBoolean
    IO ()

-- | Sets whether /@widget@/ is included in the measured size of /@overlay@/.
-- 
-- The overlay will request the size of the largest child that has
-- this property set to 'P.True'. Children who are not included may
-- be drawn outside of /@overlay@/\'s allocation if they are too large.
overlaySetMeasureOverlay ::
    (B.CallStack.HasCallStack, MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@overlay@/: a t'GI.Gtk.Objects.Overlay.Overlay'
    -> b
    -- ^ /@widget@/: an overlay child of t'GI.Gtk.Objects.Overlay.Overlay'
    -> Bool
    -- ^ /@measure@/: whether the child should be measured
    -> m ()
overlaySetMeasureOverlay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsOverlay a, IsWidget b) =>
a -> b -> Bool -> m ()
overlaySetMeasureOverlay a
overlay b
widget Bool
measure = 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 Overlay
overlay' <- a -> IO (Ptr Overlay)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
overlay
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    let measure' :: CInt
measure' = (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
measure
    Ptr Overlay -> Ptr Widget -> CInt -> IO ()
gtk_overlay_set_measure_overlay Ptr Overlay
overlay' Ptr Widget
widget' CInt
measure'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
overlay
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data OverlaySetMeasureOverlayMethodInfo
instance (signature ~ (b -> Bool -> m ()), MonadIO m, IsOverlay a, Gtk.Widget.IsWidget b) => O.OverloadedMethod OverlaySetMeasureOverlayMethodInfo a signature where
    overloadedMethod = overlaySetMeasureOverlay

instance O.OverloadedMethodInfo OverlaySetMeasureOverlayMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Overlay.overlaySetMeasureOverlay",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Overlay.html#v:overlaySetMeasureOverlay"
        }


#endif