{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkPopoverMenuBar@ presents a horizontal bar of items that pop
-- up popover menus when clicked.
-- 
-- <<https://docs.gtk.org/gtk4/menubar.png An example GtkPopoverMenuBar>>
-- 
-- The only way to create instances of @GtkPopoverMenuBar@ is
-- from a @GMenuModel@.
-- 
-- = CSS nodes
-- 
-- >menubar
-- >├── item[.active]
-- >┊   ╰── popover
-- >╰── item
-- >    ╰── popover
-- 
-- 
-- @GtkPopoverMenuBar@ has a single CSS node with name menubar, below which
-- each item has its CSS node, and below that the corresponding popover.
-- 
-- The item whose popover is currently open gets the .active
-- style class.
-- 
-- = Accessibility
-- 
-- @GtkPopoverMenuBar@ uses the 'GI.Gtk.Enums.AccessibleRoleMenuBar' role,
-- the menu items use the 'GI.Gtk.Enums.AccessibleRoleMenuItem' role and
-- the menus use the 'GI.Gtk.Enums.AccessibleRoleMenu' role.

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

module GI.Gtk.Objects.PopoverMenuBar
    ( 

-- * Exported types
    PopoverMenuBar(..)                      ,
    IsPopoverMenuBar                        ,
    toPopoverMenuBar                        ,


 -- * 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"), [addChild]("GI.Gtk.Objects.PopoverMenuBar#g:method:addChild"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [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"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [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"), [removeChild]("GI.Gtk.Objects.PopoverMenuBar#g:method:removeChild"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [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"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [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"), [getMenuModel]("GI.Gtk.Objects.PopoverMenuBar#g:method:getMenuModel"), [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"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [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"), [setMenuModel]("GI.Gtk.Objects.PopoverMenuBar#g:method:setMenuModel"), [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)
    ResolvePopoverMenuBarMethod             ,
#endif

-- ** addChild #method:addChild#

#if defined(ENABLE_OVERLOADING)
    PopoverMenuBarAddChildMethodInfo        ,
#endif
    popoverMenuBarAddChild                  ,


-- ** getMenuModel #method:getMenuModel#

#if defined(ENABLE_OVERLOADING)
    PopoverMenuBarGetMenuModelMethodInfo    ,
#endif
    popoverMenuBarGetMenuModel              ,


-- ** newFromModel #method:newFromModel#

    popoverMenuBarNewFromModel              ,


-- ** removeChild #method:removeChild#

#if defined(ENABLE_OVERLOADING)
    PopoverMenuBarRemoveChildMethodInfo     ,
#endif
    popoverMenuBarRemoveChild               ,


-- ** setMenuModel #method:setMenuModel#

#if defined(ENABLE_OVERLOADING)
    PopoverMenuBarSetMenuModelMethodInfo    ,
#endif
    popoverMenuBarSetMenuModel              ,




 -- * Properties


-- ** menuModel #attr:menuModel#
-- | The @GMenuModel@ from which the menu bar is created.
-- 
-- The model should only contain submenus as toplevel elements.

#if defined(ENABLE_OVERLOADING)
    PopoverMenuBarMenuModelPropertyInfo     ,
#endif
    clearPopoverMenuBarMenuModel            ,
    constructPopoverMenuBarMenuModel        ,
    getPopoverMenuBarMenuModel              ,
#if defined(ENABLE_OVERLOADING)
    popoverMenuBarMenuModel                 ,
#endif
    setPopoverMenuBarMenuModel              ,




    ) 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.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
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 PopoverMenuBar = PopoverMenuBar (SP.ManagedPtr PopoverMenuBar)
    deriving (PopoverMenuBar -> PopoverMenuBar -> Bool
(PopoverMenuBar -> PopoverMenuBar -> Bool)
-> (PopoverMenuBar -> PopoverMenuBar -> Bool) -> Eq PopoverMenuBar
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PopoverMenuBar -> PopoverMenuBar -> Bool
== :: PopoverMenuBar -> PopoverMenuBar -> Bool
$c/= :: PopoverMenuBar -> PopoverMenuBar -> Bool
/= :: PopoverMenuBar -> PopoverMenuBar -> Bool
Eq)

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

foreign import ccall "gtk_popover_menu_bar_get_type"
    c_gtk_popover_menu_bar_get_type :: IO B.Types.GType

instance B.Types.TypedObject PopoverMenuBar where
    glibType :: IO GType
glibType = IO GType
c_gtk_popover_menu_bar_get_type

instance B.Types.GObject PopoverMenuBar

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

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

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

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

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

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

#endif

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

#endif

-- VVV Prop "menu-model"
   -- Type: TInterface (Name {namespace = "Gio", name = "MenuModel"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

-- | Set the value of the “@menu-model@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' popoverMenuBar [ #menuModel 'Data.GI.Base.Attributes.:=' value ]
-- @
setPopoverMenuBarMenuModel :: (MonadIO m, IsPopoverMenuBar o, Gio.MenuModel.IsMenuModel a) => o -> a -> m ()
setPopoverMenuBarMenuModel :: forall (m :: * -> *) o a.
(MonadIO m, IsPopoverMenuBar o, IsMenuModel a) =>
o -> a -> m ()
setPopoverMenuBarMenuModel o
obj a
val = IO () -> m ()
forall a. IO a -> m a
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
"menu-model" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@menu-model@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPopoverMenuBarMenuModel :: (IsPopoverMenuBar o, MIO.MonadIO m, Gio.MenuModel.IsMenuModel a) => a -> m (GValueConstruct o)
constructPopoverMenuBarMenuModel :: forall o (m :: * -> *) a.
(IsPopoverMenuBar o, MonadIO m, IsMenuModel a) =>
a -> m (GValueConstruct o)
constructPopoverMenuBarMenuModel a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"menu-model" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@menu-model@” 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' #menuModel
-- @
clearPopoverMenuBarMenuModel :: (MonadIO m, IsPopoverMenuBar o) => o -> m ()
clearPopoverMenuBarMenuModel :: forall (m :: * -> *) o.
(MonadIO m, IsPopoverMenuBar o) =>
o -> m ()
clearPopoverMenuBarMenuModel o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe MenuModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"menu-model" (Maybe MenuModel
forall a. Maybe a
Nothing :: Maybe Gio.MenuModel.MenuModel)

#if defined(ENABLE_OVERLOADING)
data PopoverMenuBarMenuModelPropertyInfo
instance AttrInfo PopoverMenuBarMenuModelPropertyInfo where
    type AttrAllowedOps PopoverMenuBarMenuModelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PopoverMenuBarMenuModelPropertyInfo = IsPopoverMenuBar
    type AttrSetTypeConstraint PopoverMenuBarMenuModelPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferTypeConstraint PopoverMenuBarMenuModelPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferType PopoverMenuBarMenuModelPropertyInfo = Gio.MenuModel.MenuModel
    type AttrGetType PopoverMenuBarMenuModelPropertyInfo = (Maybe Gio.MenuModel.MenuModel)
    type AttrLabel PopoverMenuBarMenuModelPropertyInfo = "menu-model"
    type AttrOrigin PopoverMenuBarMenuModelPropertyInfo = PopoverMenuBar
    attrGet = getPopoverMenuBarMenuModel
    attrSet = setPopoverMenuBarMenuModel
    attrTransfer _ v = do
        unsafeCastTo Gio.MenuModel.MenuModel v
    attrConstruct = constructPopoverMenuBarMenuModel
    attrClear = clearPopoverMenuBarMenuModel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PopoverMenuBar.menuModel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-PopoverMenuBar.html#g:attr:menuModel"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PopoverMenuBar
type instance O.AttributeList PopoverMenuBar = PopoverMenuBarAttributeList
type PopoverMenuBarAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("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), '("menuModel", PopoverMenuBarMenuModelPropertyInfo), '("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)
popoverMenuBarMenuModel :: AttrLabelProxy "menuModel"
popoverMenuBarMenuModel = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PopoverMenuBar = PopoverMenuBarSignalList
type PopoverMenuBarSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("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 PopoverMenuBar::new_from_model
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GMenuModel`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "PopoverMenuBar" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_popover_menu_bar_new_from_model" gtk_popover_menu_bar_new_from_model :: 
    Ptr Gio.MenuModel.MenuModel ->          -- model : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO (Ptr PopoverMenuBar)

-- | Creates a @GtkPopoverMenuBar@ from a @GMenuModel@.
popoverMenuBarNewFromModel ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.MenuModel.IsMenuModel a) =>
    Maybe (a)
    -- ^ /@model@/: a @GMenuModel@
    -> m PopoverMenuBar
    -- ^ __Returns:__ a new @GtkPopoverMenuBar@
popoverMenuBarNewFromModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuModel a) =>
Maybe a -> m PopoverMenuBar
popoverMenuBarNewFromModel Maybe a
model = IO PopoverMenuBar -> m PopoverMenuBar
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PopoverMenuBar -> m PopoverMenuBar)
-> IO PopoverMenuBar -> m PopoverMenuBar
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuModel
maybeModel <- case Maybe a
model of
        Maybe a
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just a
jModel -> do
            Ptr MenuModel
jModel' <- a -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jModel
            Ptr MenuModel -> IO (Ptr MenuModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jModel'
    Ptr PopoverMenuBar
result <- Ptr MenuModel -> IO (Ptr PopoverMenuBar)
gtk_popover_menu_bar_new_from_model Ptr MenuModel
maybeModel
    Text -> Ptr PopoverMenuBar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"popoverMenuBarNewFromModel" Ptr PopoverMenuBar
result
    PopoverMenuBar
result' <- ((ManagedPtr PopoverMenuBar -> PopoverMenuBar)
-> Ptr PopoverMenuBar -> IO PopoverMenuBar
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PopoverMenuBar -> PopoverMenuBar
PopoverMenuBar) Ptr PopoverMenuBar
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
model a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    PopoverMenuBar -> IO PopoverMenuBar
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PopoverMenuBar
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PopoverMenuBar::add_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PopoverMenuBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPopoverMenuBar`"
--                 , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkWidget` to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the ID to insert @child at"
--                 , 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_popover_menu_bar_add_child" gtk_popover_menu_bar_add_child :: 
    Ptr PopoverMenuBar ->                   -- bar : TInterface (Name {namespace = "Gtk", name = "PopoverMenuBar"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    CString ->                              -- id : TBasicType TUTF8
    IO CInt

-- | Adds a custom widget to a generated menubar.
-- 
-- For this to work, the menu model of /@bar@/ must have an
-- item with a @custom@ attribute that matches /@id@/.
popoverMenuBarAddChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopoverMenuBar a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@bar@/: a @GtkPopoverMenuBar@
    -> b
    -- ^ /@child@/: the @GtkWidget@ to add
    -> T.Text
    -- ^ /@id@/: the ID to insert /@child@/ at
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@id@/ was found and the widget added
popoverMenuBarAddChild :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPopoverMenuBar a, IsWidget b) =>
a -> b -> Text -> m Bool
popoverMenuBarAddChild a
bar b
child Text
id = IO Bool -> m Bool
forall a. IO a -> m a
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 PopoverMenuBar
bar' <- a -> IO (Ptr PopoverMenuBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CString
id' <- Text -> IO CString
textToCString Text
id
    CInt
result <- Ptr PopoverMenuBar -> Ptr Widget -> CString -> IO CInt
gtk_popover_menu_bar_add_child Ptr PopoverMenuBar
bar' Ptr Widget
child' CString
id'
    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
bar
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
id'
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PopoverMenuBarAddChildMethodInfo
instance (signature ~ (b -> T.Text -> m Bool), MonadIO m, IsPopoverMenuBar a, Gtk.Widget.IsWidget b) => O.OverloadedMethod PopoverMenuBarAddChildMethodInfo a signature where
    overloadedMethod = popoverMenuBarAddChild

instance O.OverloadedMethodInfo PopoverMenuBarAddChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PopoverMenuBar.popoverMenuBarAddChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-PopoverMenuBar.html#v:popoverMenuBarAddChild"
        })


#endif

-- method PopoverMenuBar::get_menu_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PopoverMenuBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPopoverMenuBar`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "MenuModel" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_popover_menu_bar_get_menu_model" gtk_popover_menu_bar_get_menu_model :: 
    Ptr PopoverMenuBar ->                   -- bar : TInterface (Name {namespace = "Gtk", name = "PopoverMenuBar"})
    IO (Ptr Gio.MenuModel.MenuModel)

-- | Returns the model from which the contents of /@bar@/ are taken.
popoverMenuBarGetMenuModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopoverMenuBar a) =>
    a
    -- ^ /@bar@/: a @GtkPopoverMenuBar@
    -> m (Maybe Gio.MenuModel.MenuModel)
    -- ^ __Returns:__ a @GMenuModel@
popoverMenuBarGetMenuModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopoverMenuBar a) =>
a -> m (Maybe MenuModel)
popoverMenuBarGetMenuModel a
bar = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PopoverMenuBar
bar' <- a -> IO (Ptr PopoverMenuBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    Ptr MenuModel
result <- Ptr PopoverMenuBar -> IO (Ptr MenuModel)
gtk_popover_menu_bar_get_menu_model Ptr PopoverMenuBar
bar'
    Maybe MenuModel
maybeResult <- Ptr MenuModel
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MenuModel
result ((Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel))
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ \Ptr MenuModel
result' -> do
        MenuModel
result'' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result'
        MenuModel -> IO MenuModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MenuModel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    Maybe MenuModel -> IO (Maybe MenuModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MenuModel
maybeResult

#if defined(ENABLE_OVERLOADING)
data PopoverMenuBarGetMenuModelMethodInfo
instance (signature ~ (m (Maybe Gio.MenuModel.MenuModel)), MonadIO m, IsPopoverMenuBar a) => O.OverloadedMethod PopoverMenuBarGetMenuModelMethodInfo a signature where
    overloadedMethod = popoverMenuBarGetMenuModel

instance O.OverloadedMethodInfo PopoverMenuBarGetMenuModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PopoverMenuBar.popoverMenuBarGetMenuModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-PopoverMenuBar.html#v:popoverMenuBarGetMenuModel"
        })


#endif

-- method PopoverMenuBar::remove_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PopoverMenuBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPopoverMenuBar`"
--                 , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkWidget` to remove"
--                 , 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_popover_menu_bar_remove_child" gtk_popover_menu_bar_remove_child :: 
    Ptr PopoverMenuBar ->                   -- bar : TInterface (Name {namespace = "Gtk", name = "PopoverMenuBar"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO CInt

-- | Removes a widget that has previously been added with
-- 'GI.Gtk.Objects.PopoverMenuBar.popoverMenuBarAddChild'.
popoverMenuBarRemoveChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopoverMenuBar a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@bar@/: a @GtkPopoverMenuBar@
    -> b
    -- ^ /@child@/: the @GtkWidget@ to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the widget was removed
popoverMenuBarRemoveChild :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPopoverMenuBar a, IsWidget b) =>
a -> b -> m Bool
popoverMenuBarRemoveChild a
bar b
child = IO Bool -> m Bool
forall a. IO a -> m a
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 PopoverMenuBar
bar' <- a -> IO (Ptr PopoverMenuBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CInt
result <- Ptr PopoverMenuBar -> Ptr Widget -> IO CInt
gtk_popover_menu_bar_remove_child Ptr PopoverMenuBar
bar' Ptr Widget
child'
    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
bar
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

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

instance O.OverloadedMethodInfo PopoverMenuBarRemoveChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PopoverMenuBar.popoverMenuBarRemoveChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-PopoverMenuBar.html#v:popoverMenuBarRemoveChild"
        })


#endif

-- method PopoverMenuBar::set_menu_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PopoverMenuBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPopoverMenuBar`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GMenuModel`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_popover_menu_bar_set_menu_model" gtk_popover_menu_bar_set_menu_model :: 
    Ptr PopoverMenuBar ->                   -- bar : TInterface (Name {namespace = "Gtk", name = "PopoverMenuBar"})
    Ptr Gio.MenuModel.MenuModel ->          -- model : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO ()

-- | Sets a menu model from which /@bar@/ should take
-- its contents.
popoverMenuBarSetMenuModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopoverMenuBar a, Gio.MenuModel.IsMenuModel b) =>
    a
    -- ^ /@bar@/: a @GtkPopoverMenuBar@
    -> Maybe (b)
    -- ^ /@model@/: a @GMenuModel@
    -> m ()
popoverMenuBarSetMenuModel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPopoverMenuBar a, IsMenuModel b) =>
a -> Maybe b -> m ()
popoverMenuBarSetMenuModel a
bar Maybe b
model = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PopoverMenuBar
bar' <- a -> IO (Ptr PopoverMenuBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    Ptr MenuModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr MenuModel
jModel' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr MenuModel -> IO (Ptr MenuModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jModel'
    Ptr PopoverMenuBar -> Ptr MenuModel -> IO ()
gtk_popover_menu_bar_set_menu_model Ptr PopoverMenuBar
bar' Ptr MenuModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PopoverMenuBarSetMenuModelMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsPopoverMenuBar a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod PopoverMenuBarSetMenuModelMethodInfo a signature where
    overloadedMethod = popoverMenuBarSetMenuModel

instance O.OverloadedMethodInfo PopoverMenuBarSetMenuModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PopoverMenuBar.popoverMenuBarSetMenuModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-PopoverMenuBar.html#v:popoverMenuBarSetMenuModel"
        })


#endif