{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gtk.Objects.UIManager.UIManager' constructs a user interface (menus and toolbars) from
-- one or more UI definitions, which reference actions from one or more
-- action groups.
-- 
-- > GtkUIManager is deprecated since GTK+ 3.10. To construct user interfaces
-- > from XML definitions, you should use t'GI.Gtk.Objects.Builder.Builder', t'GI.Gio.Objects.MenuModel.MenuModel', et al. To
-- > work with actions, use t'GI.Gio.Interfaces.Action.Action', t'GI.Gtk.Interfaces.Actionable.Actionable' et al. These newer classes
-- > support richer functionality and integration with various desktop shells.
-- > It should be possible to migrate most\/all functionality from GtkUIManager.
-- 
-- # UI Definitions # {@/XML/@-UI}
-- 
-- The UI definitions are specified in an XML format which can be
-- roughly described by the following DTD.
-- 
-- > Do not confuse the GtkUIManager UI Definitions described here with
-- > the similarly named [GtkBuilder UI Definitions][BUILDER-UI].
-- 
-- >
-- ><!ELEMENT ui          (menubar|toolbar|popup|accelerator)* >
-- ><!ELEMENT menubar     (menuitem|separator|placeholder|menu)* >
-- ><!ELEMENT menu        (menuitem|separator|placeholder|menu)* >
-- ><!ELEMENT popup       (menuitem|separator|placeholder|menu)* >
-- ><!ELEMENT toolbar     (toolitem|separator|placeholder)* >
-- ><!ELEMENT placeholder (menuitem|toolitem|separator|placeholder|menu)* >
-- ><!ELEMENT menuitem     EMPTY >
-- ><!ELEMENT toolitem     (menu?) >
-- ><!ELEMENT separator    EMPTY >
-- ><!ELEMENT accelerator  EMPTY >
-- ><!ATTLIST menubar      name                      #IMPLIED
-- >                       action                    #IMPLIED >
-- ><!ATTLIST toolbar      name                      #IMPLIED
-- >                       action                    #IMPLIED >
-- ><!ATTLIST popup        name                      #IMPLIED
-- >                       action                    #IMPLIED
-- >                       accelerators (true|false) #IMPLIED >
-- ><!ATTLIST placeholder  name                      #IMPLIED
-- >                       action                    #IMPLIED >
-- ><!ATTLIST separator    name                      #IMPLIED
-- >                       action                    #IMPLIED
-- >                       expand       (true|false) #IMPLIED >
-- ><!ATTLIST menu         name                      #IMPLIED
-- >                       action                    #REQUIRED
-- >                       position     (top|bot)    #IMPLIED >
-- ><!ATTLIST menuitem     name                      #IMPLIED
-- >                       action                    #REQUIRED
-- >                       position     (top|bot)    #IMPLIED
-- >                       always-show-image (true|false) #IMPLIED >
-- ><!ATTLIST toolitem     name                      #IMPLIED
-- >                       action                    #REQUIRED
-- >                       position     (top|bot)    #IMPLIED >
-- ><!ATTLIST accelerator  name                      #IMPLIED
-- >                       action                    #REQUIRED >
-- 
-- 
-- There are some additional restrictions beyond those specified in the
-- DTD, e.g. every toolitem must have a toolbar in its anchestry and
-- every menuitem must have a menubar or popup in its anchestry. Since
-- a t'GI.GLib.Structs.MarkupParser.MarkupParser' is used to parse the UI description, it must not only
-- be valid XML, but valid markup.
-- 
-- If a name is not specified, it defaults to the action. If an action is
-- not specified either, the element name is used. The name and action
-- attributes must not contain “\/” characters after parsing (since that
-- would mess up path lookup) and must be usable as XML attributes when
-- enclosed in doublequotes, thus they must not “\"” characters or references
-- to the &quot; entity.
-- 
-- = A UI definition 
-- 
-- 
-- === /xml code/
-- >
-- ><ui>
-- >  <menubar>
-- >    <menu name="FileMenu" action="FileMenuAction">
-- >      <menuitem name="New" action="New2Action" />
-- >      <placeholder name="FileMenuAdditions" />
-- >    </menu>
-- >    <menu name="JustifyMenu" action="JustifyMenuAction">
-- >      <menuitem name="Left" action="justify-left"/>
-- >      <menuitem name="Centre" action="justify-center"/>
-- >      <menuitem name="Right" action="justify-right"/>
-- >      <menuitem name="Fill" action="justify-fill"/>
-- >    </menu>
-- >  </menubar>
-- >  <toolbar action="toolbar1">
-- >    <placeholder name="JustifyToolItems">
-- >      <separator/>
-- >      <toolitem name="Left" action="justify-left"/>
-- >      <toolitem name="Centre" action="justify-center"/>
-- >      <toolitem name="Right" action="justify-right"/>
-- >      <toolitem name="Fill" action="justify-fill"/>
-- >      <separator/>
-- >    </placeholder>
-- >  </toolbar>
-- ></ui>
-- 
-- 
-- The constructed widget hierarchy is very similar to the element tree
-- of the XML, with the exception that placeholders are merged into their
-- parents. The correspondence of XML elements to widgets should be
-- almost obvious:
-- 
-- * menubar
-- 
-- 
--    a t'GI.Gtk.Objects.MenuBar.MenuBar'
-- 
-- * toolbar
-- 
-- 
--    a t'GI.Gtk.Objects.Toolbar.Toolbar'
-- 
-- * popup
-- 
-- 
--    a toplevel t'GI.Gtk.Objects.Menu.Menu'
-- 
-- * menu
-- 
-- 
--    a t'GI.Gtk.Objects.Menu.Menu' attached to a menuitem
-- 
-- * menuitem
-- 
-- 
--    a t'GI.Gtk.Objects.MenuItem.MenuItem' subclass, the exact type depends on the action
-- 
-- * toolitem
-- 
-- 
--    a t'GI.Gtk.Objects.ToolItem.ToolItem' subclass, the exact type depends on the
--    action. Note that toolitem elements may contain a menu element,
--    but only if their associated action specifies a
--    t'GI.Gtk.Objects.MenuToolButton.MenuToolButton' as proxy.
-- 
-- * separator
-- 
-- 
--    a t'GI.Gtk.Objects.SeparatorMenuItem.SeparatorMenuItem' or t'GI.Gtk.Objects.SeparatorToolItem.SeparatorToolItem'
-- 
-- * accelerator
-- 
-- 
--    a keyboard accelerator
-- 
-- The “position” attribute determines where a constructed widget is positioned
-- wrt. to its siblings in the partially constructed tree. If it is
-- “top”, the widget is prepended, otherwise it is appended.
-- 
-- # UI Merging # {@/UI/@-Merging}
-- 
-- The most remarkable feature of t'GI.Gtk.Objects.UIManager.UIManager' is that it can overlay a set
-- of menuitems and toolitems over another one, and demerge them later.
-- 
-- Merging is done based on the names of the XML elements. Each element is
-- identified by a path which consists of the names of its anchestors, separated
-- by slashes. For example, the menuitem named “Left” in the example above
-- has the path @\/ui\/menubar\/JustifyMenu\/Left@ and the
-- toolitem with the same name has path
-- @\/ui\/toolbar1\/JustifyToolItems\/Left@.
-- 
-- = Accelerators 
-- 
-- Every action has an accelerator path. Accelerators are installed together
-- with menuitem proxies, but they can also be explicitly added with
-- @\<accelerator>@ elements in the UI definition. This makes it possible to
-- have accelerators for actions even if they have no visible proxies.
-- 
-- # Smart Separators # {@/Smart/@-Separators}
-- 
-- The separators created by t'GI.Gtk.Objects.UIManager.UIManager' are “smart”, i.e. they do not show up
-- in the UI unless they end up between two visible menu or tool items. Separators
-- which are located at the very beginning or end of the menu or toolbar
-- containing them, or multiple separators next to each other, are hidden. This
-- is a useful feature, since the merging of UI elements from multiple sources
-- can make it hard or impossible to determine in advance whether a separator
-- will end up in such an unfortunate position.
-- 
-- For separators in toolbars, you can set @expand=\"true\"@ to
-- turn them from a small, visible separator to an expanding, invisible one.
-- Toolitems following an expanding separator are effectively right-aligned.
-- 
-- = Empty Menus
-- 
-- Submenus pose similar problems to separators inconnection with merging. It is
-- impossible to know in advance whether they will end up empty after merging.
-- t'GI.Gtk.Objects.UIManager.UIManager' offers two ways to treat empty submenus:
-- 
-- * make them disappear by hiding the menu item they’re attached to
-- * add an insensitive “Empty” item
-- 
-- 
-- The behaviour is chosen based on the “hide_if_empty” property of the action
-- to which the submenu is associated.
-- 
-- # GtkUIManager as GtkBuildable # {t'GI.Gtk.Objects.UIManager.UIManager'-BUILDER-UI}
-- 
-- The GtkUIManager implementation of the GtkBuildable interface accepts
-- GtkActionGroup objects as @\<child>@ elements in UI definitions.
-- 
-- A GtkUIManager UI definition as described above can be embedded in
-- an GtkUIManager @\<object>@ element in a GtkBuilder UI definition.
-- 
-- The widgets that are constructed by a GtkUIManager can be embedded in
-- other parts of the constructed user interface with the help of the
-- “constructor” attribute. See the example below.
-- 
-- == An embedded GtkUIManager UI definition
-- 
-- 
-- === /xml code/
-- >
-- ><object class="GtkUIManager" id="uiman">
-- >  <child>
-- >    <object class="GtkActionGroup" id="actiongroup">
-- >      <child>
-- >        <object class="GtkAction" id="file">
-- >          <property name="label">_File</property>
-- >        </object>
-- >      </child>
-- >    </object>
-- >  </child>
-- >  <ui>
-- >    <menubar name="menubar1">
-- >      <menu action="file">
-- >      </menu>
-- >    </menubar>
-- >  </ui>
-- ></object>
-- ><object class="GtkWindow" id="main-window">
-- >  <child>
-- >    <object class="GtkMenuBar" id="menubar1" constructor="uiman"/>
-- >  </child>
-- ></object>
-- 

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

module GI.Gtk.Objects.UIManager
    ( 

-- * Exported types
    UIManager(..)                           ,
    IsUIManager                             ,
    toUIManager                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addChild]("GI.Gtk.Interfaces.Buildable#g:method:addChild"), [addUi]("GI.Gtk.Objects.UIManager#g:method:addUi"), [addUiFromFile]("GI.Gtk.Objects.UIManager#g:method:addUiFromFile"), [addUiFromResource]("GI.Gtk.Objects.UIManager#g:method:addUiFromResource"), [addUiFromString]("GI.Gtk.Objects.UIManager#g:method:addUiFromString"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [constructChild]("GI.Gtk.Interfaces.Buildable#g:method:constructChild"), [customFinished]("GI.Gtk.Interfaces.Buildable#g:method:customFinished"), [customTagEnd]("GI.Gtk.Interfaces.Buildable#g:method:customTagEnd"), [customTagStart]("GI.Gtk.Interfaces.Buildable#g:method:customTagStart"), [ensureUpdate]("GI.Gtk.Objects.UIManager#g:method:ensureUpdate"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [insertActionGroup]("GI.Gtk.Objects.UIManager#g:method:insertActionGroup"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [newMergeId]("GI.Gtk.Objects.UIManager#g:method:newMergeId"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [parserFinished]("GI.Gtk.Interfaces.Buildable#g:method:parserFinished"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeActionGroup]("GI.Gtk.Objects.UIManager#g:method:removeActionGroup"), [removeUi]("GI.Gtk.Objects.UIManager#g:method:removeUi"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccelGroup]("GI.Gtk.Objects.UIManager#g:method:getAccelGroup"), [getAction]("GI.Gtk.Objects.UIManager#g:method:getAction"), [getActionGroups]("GI.Gtk.Objects.UIManager#g:method:getActionGroups"), [getAddTearoffs]("GI.Gtk.Objects.UIManager#g:method:getAddTearoffs"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getInternalChild]("GI.Gtk.Interfaces.Buildable#g:method:getInternalChild"), [getName]("GI.Gtk.Interfaces.Buildable#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getToplevels]("GI.Gtk.Objects.UIManager#g:method:getToplevels"), [getUi]("GI.Gtk.Objects.UIManager#g:method:getUi"), [getWidget]("GI.Gtk.Objects.UIManager#g:method:getWidget").
-- 
-- ==== Setters
-- [setAddTearoffs]("GI.Gtk.Objects.UIManager#g:method:setAddTearoffs"), [setBuildableProperty]("GI.Gtk.Interfaces.Buildable#g:method:setBuildableProperty"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setName]("GI.Gtk.Interfaces.Buildable#g:method:setName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveUIManagerMethod                  ,
#endif

-- ** addUi #method:addUi#

#if defined(ENABLE_OVERLOADING)
    UIManagerAddUiMethodInfo                ,
#endif
    uIManagerAddUi                          ,


-- ** addUiFromFile #method:addUiFromFile#

#if defined(ENABLE_OVERLOADING)
    UIManagerAddUiFromFileMethodInfo        ,
#endif
    uIManagerAddUiFromFile                  ,


-- ** addUiFromResource #method:addUiFromResource#

#if defined(ENABLE_OVERLOADING)
    UIManagerAddUiFromResourceMethodInfo    ,
#endif
    uIManagerAddUiFromResource              ,


-- ** addUiFromString #method:addUiFromString#

#if defined(ENABLE_OVERLOADING)
    UIManagerAddUiFromStringMethodInfo      ,
#endif
    uIManagerAddUiFromString                ,


-- ** ensureUpdate #method:ensureUpdate#

#if defined(ENABLE_OVERLOADING)
    UIManagerEnsureUpdateMethodInfo         ,
#endif
    uIManagerEnsureUpdate                   ,


-- ** getAccelGroup #method:getAccelGroup#

#if defined(ENABLE_OVERLOADING)
    UIManagerGetAccelGroupMethodInfo        ,
#endif
    uIManagerGetAccelGroup                  ,


-- ** getAction #method:getAction#

#if defined(ENABLE_OVERLOADING)
    UIManagerGetActionMethodInfo            ,
#endif
    uIManagerGetAction                      ,


-- ** getActionGroups #method:getActionGroups#

#if defined(ENABLE_OVERLOADING)
    UIManagerGetActionGroupsMethodInfo      ,
#endif
    uIManagerGetActionGroups                ,


-- ** getAddTearoffs #method:getAddTearoffs#

#if defined(ENABLE_OVERLOADING)
    UIManagerGetAddTearoffsMethodInfo       ,
#endif
    uIManagerGetAddTearoffs                 ,


-- ** getToplevels #method:getToplevels#

#if defined(ENABLE_OVERLOADING)
    UIManagerGetToplevelsMethodInfo         ,
#endif
    uIManagerGetToplevels                   ,


-- ** getUi #method:getUi#

#if defined(ENABLE_OVERLOADING)
    UIManagerGetUiMethodInfo                ,
#endif
    uIManagerGetUi                          ,


-- ** getWidget #method:getWidget#

#if defined(ENABLE_OVERLOADING)
    UIManagerGetWidgetMethodInfo            ,
#endif
    uIManagerGetWidget                      ,


-- ** insertActionGroup #method:insertActionGroup#

#if defined(ENABLE_OVERLOADING)
    UIManagerInsertActionGroupMethodInfo    ,
#endif
    uIManagerInsertActionGroup              ,


-- ** new #method:new#

    uIManagerNew                            ,


-- ** newMergeId #method:newMergeId#

#if defined(ENABLE_OVERLOADING)
    UIManagerNewMergeIdMethodInfo           ,
#endif
    uIManagerNewMergeId                     ,


-- ** removeActionGroup #method:removeActionGroup#

#if defined(ENABLE_OVERLOADING)
    UIManagerRemoveActionGroupMethodInfo    ,
#endif
    uIManagerRemoveActionGroup              ,


-- ** removeUi #method:removeUi#

#if defined(ENABLE_OVERLOADING)
    UIManagerRemoveUiMethodInfo             ,
#endif
    uIManagerRemoveUi                       ,


-- ** setAddTearoffs #method:setAddTearoffs#

#if defined(ENABLE_OVERLOADING)
    UIManagerSetAddTearoffsMethodInfo       ,
#endif
    uIManagerSetAddTearoffs                 ,




 -- * Properties


-- ** addTearoffs #attr:addTearoffs#
-- | The \"add-tearoffs\" property controls whether generated menus
-- have tearoff menu items.
-- 
-- Note that this only affects regular menus. Generated popup
-- menus never have tearoff menu items.
-- 
-- /Since: 2.4/

#if defined(ENABLE_OVERLOADING)
    UIManagerAddTearoffsPropertyInfo        ,
#endif
    constructUIManagerAddTearoffs           ,
    getUIManagerAddTearoffs                 ,
    setUIManagerAddTearoffs                 ,
#if defined(ENABLE_OVERLOADING)
    uIManagerAddTearoffs                    ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    UIManagerUiPropertyInfo                 ,
#endif
    getUIManagerUi                          ,
#if defined(ENABLE_OVERLOADING)
    uIManagerUi                             ,
#endif




 -- * Signals


-- ** actionsChanged #signal:actionsChanged#

    UIManagerActionsChangedCallback         ,
#if defined(ENABLE_OVERLOADING)
    UIManagerActionsChangedSignalInfo       ,
#endif
    afterUIManagerActionsChanged            ,
    onUIManagerActionsChanged               ,


-- ** addWidget #signal:addWidget#

    UIManagerAddWidgetCallback              ,
#if defined(ENABLE_OVERLOADING)
    UIManagerAddWidgetSignalInfo            ,
#endif
    afterUIManagerAddWidget                 ,
    onUIManagerAddWidget                    ,


-- ** connectProxy #signal:connectProxy#

    UIManagerConnectProxyCallback           ,
#if defined(ENABLE_OVERLOADING)
    UIManagerConnectProxySignalInfo         ,
#endif
    afterUIManagerConnectProxy              ,
    onUIManagerConnectProxy                 ,


-- ** disconnectProxy #signal:disconnectProxy#

    UIManagerDisconnectProxyCallback        ,
#if defined(ENABLE_OVERLOADING)
    UIManagerDisconnectProxySignalInfo      ,
#endif
    afterUIManagerDisconnectProxy           ,
    onUIManagerDisconnectProxy              ,


-- ** postActivate #signal:postActivate#

    UIManagerPostActivateCallback           ,
#if defined(ENABLE_OVERLOADING)
    UIManagerPostActivateSignalInfo         ,
#endif
    afterUIManagerPostActivate              ,
    onUIManagerPostActivate                 ,


-- ** preActivate #signal:preActivate#

    UIManagerPreActivateCallback            ,
#if defined(ENABLE_OVERLOADING)
    UIManagerPreActivateSignalInfo          ,
#endif
    afterUIManagerPreActivate               ,
    onUIManagerPreActivate                  ,




    ) 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.Kind as DK
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.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.AccelGroup as Gtk.AccelGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Action as Gtk.Action
import {-# SOURCE #-} qualified GI.Gtk.Objects.ActionGroup as Gtk.ActionGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_ui_manager_get_type"
    c_gtk_ui_manager_get_type :: IO B.Types.GType

instance B.Types.TypedObject UIManager where
    glibType :: IO GType
glibType = IO GType
c_gtk_ui_manager_get_type

instance B.Types.GObject UIManager

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

instance O.HasParentTypes UIManager
type instance O.ParentTypes UIManager = '[GObject.Object.Object, Gtk.Buildable.Buildable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveUIManagerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveUIManagerMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveUIManagerMethod "addUi" o = UIManagerAddUiMethodInfo
    ResolveUIManagerMethod "addUiFromFile" o = UIManagerAddUiFromFileMethodInfo
    ResolveUIManagerMethod "addUiFromResource" o = UIManagerAddUiFromResourceMethodInfo
    ResolveUIManagerMethod "addUiFromString" o = UIManagerAddUiFromStringMethodInfo
    ResolveUIManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveUIManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveUIManagerMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveUIManagerMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveUIManagerMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveUIManagerMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveUIManagerMethod "ensureUpdate" o = UIManagerEnsureUpdateMethodInfo
    ResolveUIManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveUIManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveUIManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveUIManagerMethod "insertActionGroup" o = UIManagerInsertActionGroupMethodInfo
    ResolveUIManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveUIManagerMethod "newMergeId" o = UIManagerNewMergeIdMethodInfo
    ResolveUIManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveUIManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveUIManagerMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveUIManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveUIManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveUIManagerMethod "removeActionGroup" o = UIManagerRemoveActionGroupMethodInfo
    ResolveUIManagerMethod "removeUi" o = UIManagerRemoveUiMethodInfo
    ResolveUIManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveUIManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveUIManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveUIManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveUIManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveUIManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveUIManagerMethod "getAccelGroup" o = UIManagerGetAccelGroupMethodInfo
    ResolveUIManagerMethod "getAction" o = UIManagerGetActionMethodInfo
    ResolveUIManagerMethod "getActionGroups" o = UIManagerGetActionGroupsMethodInfo
    ResolveUIManagerMethod "getAddTearoffs" o = UIManagerGetAddTearoffsMethodInfo
    ResolveUIManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveUIManagerMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveUIManagerMethod "getName" o = Gtk.Buildable.BuildableGetNameMethodInfo
    ResolveUIManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveUIManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveUIManagerMethod "getToplevels" o = UIManagerGetToplevelsMethodInfo
    ResolveUIManagerMethod "getUi" o = UIManagerGetUiMethodInfo
    ResolveUIManagerMethod "getWidget" o = UIManagerGetWidgetMethodInfo
    ResolveUIManagerMethod "setAddTearoffs" o = UIManagerSetAddTearoffsMethodInfo
    ResolveUIManagerMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveUIManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveUIManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveUIManagerMethod "setName" o = Gtk.Buildable.BuildableSetNameMethodInfo
    ResolveUIManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveUIManagerMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal UIManager::actions-changed
{-# DEPRECATED UIManagerActionsChangedCallback ["(Since version 3.10)"] #-}
-- | The [actionsChanged](#g:signal:actionsChanged) signal is emitted whenever the set of actions
-- changes.
-- 
-- /Since: 2.4/
type UIManagerActionsChangedCallback =
    IO ()

type C_UIManagerActionsChangedCallback =
    Ptr UIManager ->                        -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_UIManagerActionsChangedCallback`.
foreign import ccall "wrapper"
    mk_UIManagerActionsChangedCallback :: C_UIManagerActionsChangedCallback -> IO (FunPtr C_UIManagerActionsChangedCallback)

wrap_UIManagerActionsChangedCallback :: 
    GObject a => (a -> UIManagerActionsChangedCallback) ->
    C_UIManagerActionsChangedCallback
wrap_UIManagerActionsChangedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_UIManagerActionsChangedCallback
wrap_UIManagerActionsChangedCallback a -> IO ()
gi'cb Ptr UIManager
gi'selfPtr Ptr ()
_ = do
    Ptr UIManager -> (UIManager -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr UIManager
gi'selfPtr ((UIManager -> IO ()) -> IO ()) -> (UIManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \UIManager
gi'self -> a -> IO ()
gi'cb (UIManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce UIManager
gi'self) 


-- | Connect a signal handler for the [actionsChanged](#signal:actionsChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' uIManager #actionsChanged callback
-- @
-- 
-- 
onUIManagerActionsChanged :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerActionsChangedCallback) -> m SignalHandlerId
onUIManagerActionsChanged :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onUIManagerActionsChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_UIManagerActionsChangedCallback
wrapped' = (a -> IO ()) -> C_UIManagerActionsChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_UIManagerActionsChangedCallback
wrap_UIManagerActionsChangedCallback a -> IO ()
wrapped
    FunPtr C_UIManagerActionsChangedCallback
wrapped'' <- C_UIManagerActionsChangedCallback
-> IO (FunPtr C_UIManagerActionsChangedCallback)
mk_UIManagerActionsChangedCallback C_UIManagerActionsChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerActionsChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"actions-changed" FunPtr C_UIManagerActionsChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [actionsChanged](#signal:actionsChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' uIManager #actionsChanged callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterUIManagerActionsChanged :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerActionsChangedCallback) -> m SignalHandlerId
afterUIManagerActionsChanged :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterUIManagerActionsChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_UIManagerActionsChangedCallback
wrapped' = (a -> IO ()) -> C_UIManagerActionsChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_UIManagerActionsChangedCallback
wrap_UIManagerActionsChangedCallback a -> IO ()
wrapped
    FunPtr C_UIManagerActionsChangedCallback
wrapped'' <- C_UIManagerActionsChangedCallback
-> IO (FunPtr C_UIManagerActionsChangedCallback)
mk_UIManagerActionsChangedCallback C_UIManagerActionsChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerActionsChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"actions-changed" FunPtr C_UIManagerActionsChangedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data UIManagerActionsChangedSignalInfo
instance SignalInfo UIManagerActionsChangedSignalInfo where
    type HaskellCallbackType UIManagerActionsChangedSignalInfo = UIManagerActionsChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_UIManagerActionsChangedCallback cb
        cb'' <- mk_UIManagerActionsChangedCallback cb'
        connectSignalFunPtr obj "actions-changed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager::actions-changed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:signal:actionsChanged"})

#endif

-- signal UIManager::add-widget
{-# DEPRECATED UIManagerAddWidgetCallback ["(Since version 3.10)"] #-}
-- | The [addWidget](#g:signal:addWidget) signal is emitted for each generated menubar and toolbar.
-- It is not emitted for generated popup menus, which can be obtained by
-- 'GI.Gtk.Objects.UIManager.uIManagerGetWidget'.
-- 
-- /Since: 2.4/
type UIManagerAddWidgetCallback =
    Gtk.Widget.Widget
    -- ^ /@widget@/: the added widget
    -> IO ()

type C_UIManagerAddWidgetCallback =
    Ptr UIManager ->                        -- object
    Ptr Gtk.Widget.Widget ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_UIManagerAddWidgetCallback`.
foreign import ccall "wrapper"
    mk_UIManagerAddWidgetCallback :: C_UIManagerAddWidgetCallback -> IO (FunPtr C_UIManagerAddWidgetCallback)

wrap_UIManagerAddWidgetCallback :: 
    GObject a => (a -> UIManagerAddWidgetCallback) ->
    C_UIManagerAddWidgetCallback
wrap_UIManagerAddWidgetCallback :: forall a.
GObject a =>
(a -> UIManagerAddWidgetCallback) -> C_UIManagerAddWidgetCallback
wrap_UIManagerAddWidgetCallback a -> UIManagerAddWidgetCallback
gi'cb Ptr UIManager
gi'selfPtr Ptr Widget
widget Ptr ()
_ = do
    Widget
widget' <- ((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
widget
    Ptr UIManager -> (UIManager -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr UIManager
gi'selfPtr ((UIManager -> IO ()) -> IO ()) -> (UIManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \UIManager
gi'self -> a -> UIManagerAddWidgetCallback
gi'cb (UIManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce UIManager
gi'self)  Widget
widget'


-- | Connect a signal handler for the [addWidget](#signal:addWidget) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' uIManager #addWidget callback
-- @
-- 
-- 
onUIManagerAddWidget :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerAddWidgetCallback) -> m SignalHandlerId
onUIManagerAddWidget :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerAddWidgetCallback) -> m SignalHandlerId
onUIManagerAddWidget a
obj (?self::a) => UIManagerAddWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerAddWidgetCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerAddWidgetCallback
UIManagerAddWidgetCallback
cb
    let wrapped' :: C_UIManagerAddWidgetCallback
wrapped' = (a -> UIManagerAddWidgetCallback) -> C_UIManagerAddWidgetCallback
forall a.
GObject a =>
(a -> UIManagerAddWidgetCallback) -> C_UIManagerAddWidgetCallback
wrap_UIManagerAddWidgetCallback a -> UIManagerAddWidgetCallback
wrapped
    FunPtr C_UIManagerAddWidgetCallback
wrapped'' <- C_UIManagerAddWidgetCallback
-> IO (FunPtr C_UIManagerAddWidgetCallback)
mk_UIManagerAddWidgetCallback C_UIManagerAddWidgetCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerAddWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"add-widget" FunPtr C_UIManagerAddWidgetCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [addWidget](#signal:addWidget) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' uIManager #addWidget callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterUIManagerAddWidget :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerAddWidgetCallback) -> m SignalHandlerId
afterUIManagerAddWidget :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerAddWidgetCallback) -> m SignalHandlerId
afterUIManagerAddWidget a
obj (?self::a) => UIManagerAddWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerAddWidgetCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerAddWidgetCallback
UIManagerAddWidgetCallback
cb
    let wrapped' :: C_UIManagerAddWidgetCallback
wrapped' = (a -> UIManagerAddWidgetCallback) -> C_UIManagerAddWidgetCallback
forall a.
GObject a =>
(a -> UIManagerAddWidgetCallback) -> C_UIManagerAddWidgetCallback
wrap_UIManagerAddWidgetCallback a -> UIManagerAddWidgetCallback
wrapped
    FunPtr C_UIManagerAddWidgetCallback
wrapped'' <- C_UIManagerAddWidgetCallback
-> IO (FunPtr C_UIManagerAddWidgetCallback)
mk_UIManagerAddWidgetCallback C_UIManagerAddWidgetCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerAddWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"add-widget" FunPtr C_UIManagerAddWidgetCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data UIManagerAddWidgetSignalInfo
instance SignalInfo UIManagerAddWidgetSignalInfo where
    type HaskellCallbackType UIManagerAddWidgetSignalInfo = UIManagerAddWidgetCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_UIManagerAddWidgetCallback cb
        cb'' <- mk_UIManagerAddWidgetCallback cb'
        connectSignalFunPtr obj "add-widget" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager::add-widget"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:signal:addWidget"})

#endif

-- signal UIManager::connect-proxy
{-# DEPRECATED UIManagerConnectProxyCallback ["(Since version 3.10)"] #-}
-- | The [connectProxy](#g:signal:connectProxy) signal is emitted after connecting a proxy to
-- an action in the group.
-- 
-- This is intended for simple customizations for which a custom action
-- class would be too clumsy, e.g. showing tooltips for menuitems in the
-- statusbar.
-- 
-- /Since: 2.4/
type UIManagerConnectProxyCallback =
    Gtk.Action.Action
    -- ^ /@action@/: the action
    -> Gtk.Widget.Widget
    -- ^ /@proxy@/: the proxy
    -> IO ()

type C_UIManagerConnectProxyCallback =
    Ptr UIManager ->                        -- object
    Ptr Gtk.Action.Action ->
    Ptr Gtk.Widget.Widget ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_UIManagerConnectProxyCallback`.
foreign import ccall "wrapper"
    mk_UIManagerConnectProxyCallback :: C_UIManagerConnectProxyCallback -> IO (FunPtr C_UIManagerConnectProxyCallback)

wrap_UIManagerConnectProxyCallback :: 
    GObject a => (a -> UIManagerConnectProxyCallback) ->
    C_UIManagerConnectProxyCallback
wrap_UIManagerConnectProxyCallback :: forall a.
GObject a =>
(a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
wrap_UIManagerConnectProxyCallback a -> UIManagerConnectProxyCallback
gi'cb Ptr UIManager
gi'selfPtr Ptr Action
action Ptr Widget
proxy Ptr ()
_ = do
    Action
action' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Action -> Action
Gtk.Action.Action) Ptr Action
action
    Widget
proxy' <- ((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
proxy
    Ptr UIManager -> (UIManager -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr UIManager
gi'selfPtr ((UIManager -> IO ()) -> IO ()) -> (UIManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \UIManager
gi'self -> a -> UIManagerConnectProxyCallback
gi'cb (UIManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce UIManager
gi'self)  Action
action' Widget
proxy'


-- | Connect a signal handler for the [connectProxy](#signal:connectProxy) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' uIManager #connectProxy callback
-- @
-- 
-- 
onUIManagerConnectProxy :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerConnectProxyCallback) -> m SignalHandlerId
onUIManagerConnectProxy :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerConnectProxyCallback)
-> m SignalHandlerId
onUIManagerConnectProxy a
obj (?self::a) => UIManagerConnectProxyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerConnectProxyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerConnectProxyCallback
UIManagerConnectProxyCallback
cb
    let wrapped' :: C_UIManagerConnectProxyCallback
wrapped' = (a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
forall a.
GObject a =>
(a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
wrap_UIManagerConnectProxyCallback a -> UIManagerConnectProxyCallback
wrapped
    FunPtr C_UIManagerConnectProxyCallback
wrapped'' <- C_UIManagerConnectProxyCallback
-> IO (FunPtr C_UIManagerConnectProxyCallback)
mk_UIManagerConnectProxyCallback C_UIManagerConnectProxyCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerConnectProxyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"connect-proxy" FunPtr C_UIManagerConnectProxyCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [connectProxy](#signal:connectProxy) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' uIManager #connectProxy callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterUIManagerConnectProxy :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerConnectProxyCallback) -> m SignalHandlerId
afterUIManagerConnectProxy :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerConnectProxyCallback)
-> m SignalHandlerId
afterUIManagerConnectProxy a
obj (?self::a) => UIManagerConnectProxyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerConnectProxyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerConnectProxyCallback
UIManagerConnectProxyCallback
cb
    let wrapped' :: C_UIManagerConnectProxyCallback
wrapped' = (a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
forall a.
GObject a =>
(a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
wrap_UIManagerConnectProxyCallback a -> UIManagerConnectProxyCallback
wrapped
    FunPtr C_UIManagerConnectProxyCallback
wrapped'' <- C_UIManagerConnectProxyCallback
-> IO (FunPtr C_UIManagerConnectProxyCallback)
mk_UIManagerConnectProxyCallback C_UIManagerConnectProxyCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerConnectProxyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"connect-proxy" FunPtr C_UIManagerConnectProxyCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data UIManagerConnectProxySignalInfo
instance SignalInfo UIManagerConnectProxySignalInfo where
    type HaskellCallbackType UIManagerConnectProxySignalInfo = UIManagerConnectProxyCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_UIManagerConnectProxyCallback cb
        cb'' <- mk_UIManagerConnectProxyCallback cb'
        connectSignalFunPtr obj "connect-proxy" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager::connect-proxy"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:signal:connectProxy"})

#endif

-- signal UIManager::disconnect-proxy
{-# DEPRECATED UIManagerDisconnectProxyCallback ["(Since version 3.10)"] #-}
-- | The [disconnectProxy](#g:signal:disconnectProxy) signal is emitted after disconnecting a proxy
-- from an action in the group.
-- 
-- /Since: 2.4/
type UIManagerDisconnectProxyCallback =
    Gtk.Action.Action
    -- ^ /@action@/: the action
    -> Gtk.Widget.Widget
    -- ^ /@proxy@/: the proxy
    -> IO ()

type C_UIManagerDisconnectProxyCallback =
    Ptr UIManager ->                        -- object
    Ptr Gtk.Action.Action ->
    Ptr Gtk.Widget.Widget ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_UIManagerDisconnectProxyCallback`.
foreign import ccall "wrapper"
    mk_UIManagerDisconnectProxyCallback :: C_UIManagerDisconnectProxyCallback -> IO (FunPtr C_UIManagerDisconnectProxyCallback)

wrap_UIManagerDisconnectProxyCallback :: 
    GObject a => (a -> UIManagerDisconnectProxyCallback) ->
    C_UIManagerDisconnectProxyCallback
wrap_UIManagerDisconnectProxyCallback :: forall a.
GObject a =>
(a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
wrap_UIManagerDisconnectProxyCallback a -> UIManagerConnectProxyCallback
gi'cb Ptr UIManager
gi'selfPtr Ptr Action
action Ptr Widget
proxy Ptr ()
_ = do
    Action
action' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Action -> Action
Gtk.Action.Action) Ptr Action
action
    Widget
proxy' <- ((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
proxy
    Ptr UIManager -> (UIManager -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr UIManager
gi'selfPtr ((UIManager -> IO ()) -> IO ()) -> (UIManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \UIManager
gi'self -> a -> UIManagerConnectProxyCallback
gi'cb (UIManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce UIManager
gi'self)  Action
action' Widget
proxy'


-- | Connect a signal handler for the [disconnectProxy](#signal:disconnectProxy) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' uIManager #disconnectProxy callback
-- @
-- 
-- 
onUIManagerDisconnectProxy :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerDisconnectProxyCallback) -> m SignalHandlerId
onUIManagerDisconnectProxy :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerConnectProxyCallback)
-> m SignalHandlerId
onUIManagerDisconnectProxy a
obj (?self::a) => UIManagerConnectProxyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerConnectProxyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerConnectProxyCallback
UIManagerConnectProxyCallback
cb
    let wrapped' :: C_UIManagerConnectProxyCallback
wrapped' = (a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
forall a.
GObject a =>
(a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
wrap_UIManagerDisconnectProxyCallback a -> UIManagerConnectProxyCallback
wrapped
    FunPtr C_UIManagerConnectProxyCallback
wrapped'' <- C_UIManagerConnectProxyCallback
-> IO (FunPtr C_UIManagerConnectProxyCallback)
mk_UIManagerDisconnectProxyCallback C_UIManagerConnectProxyCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerConnectProxyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"disconnect-proxy" FunPtr C_UIManagerConnectProxyCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [disconnectProxy](#signal:disconnectProxy) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' uIManager #disconnectProxy callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterUIManagerDisconnectProxy :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerDisconnectProxyCallback) -> m SignalHandlerId
afterUIManagerDisconnectProxy :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerConnectProxyCallback)
-> m SignalHandlerId
afterUIManagerDisconnectProxy a
obj (?self::a) => UIManagerConnectProxyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerConnectProxyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerConnectProxyCallback
UIManagerConnectProxyCallback
cb
    let wrapped' :: C_UIManagerConnectProxyCallback
wrapped' = (a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
forall a.
GObject a =>
(a -> UIManagerConnectProxyCallback)
-> C_UIManagerConnectProxyCallback
wrap_UIManagerDisconnectProxyCallback a -> UIManagerConnectProxyCallback
wrapped
    FunPtr C_UIManagerConnectProxyCallback
wrapped'' <- C_UIManagerConnectProxyCallback
-> IO (FunPtr C_UIManagerConnectProxyCallback)
mk_UIManagerDisconnectProxyCallback C_UIManagerConnectProxyCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerConnectProxyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"disconnect-proxy" FunPtr C_UIManagerConnectProxyCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data UIManagerDisconnectProxySignalInfo
instance SignalInfo UIManagerDisconnectProxySignalInfo where
    type HaskellCallbackType UIManagerDisconnectProxySignalInfo = UIManagerDisconnectProxyCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_UIManagerDisconnectProxyCallback cb
        cb'' <- mk_UIManagerDisconnectProxyCallback cb'
        connectSignalFunPtr obj "disconnect-proxy" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager::disconnect-proxy"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:signal:disconnectProxy"})

#endif

-- signal UIManager::post-activate
{-# DEPRECATED UIManagerPostActivateCallback ["(Since version 3.10)"] #-}
-- | The [postActivate](#g:signal:postActivate) signal is emitted just after the /@action@/
-- is activated.
-- 
-- This is intended for applications to get notification
-- just after any action is activated.
-- 
-- /Since: 2.4/
type UIManagerPostActivateCallback =
    Gtk.Action.Action
    -- ^ /@action@/: the action
    -> IO ()

type C_UIManagerPostActivateCallback =
    Ptr UIManager ->                        -- object
    Ptr Gtk.Action.Action ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_UIManagerPostActivateCallback`.
foreign import ccall "wrapper"
    mk_UIManagerPostActivateCallback :: C_UIManagerPostActivateCallback -> IO (FunPtr C_UIManagerPostActivateCallback)

wrap_UIManagerPostActivateCallback :: 
    GObject a => (a -> UIManagerPostActivateCallback) ->
    C_UIManagerPostActivateCallback
wrap_UIManagerPostActivateCallback :: forall a.
GObject a =>
(a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
wrap_UIManagerPostActivateCallback a -> UIManagerPostActivateCallback
gi'cb Ptr UIManager
gi'selfPtr Ptr Action
action Ptr ()
_ = do
    Action
action' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Action -> Action
Gtk.Action.Action) Ptr Action
action
    Ptr UIManager -> (UIManager -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr UIManager
gi'selfPtr ((UIManager -> IO ()) -> IO ()) -> (UIManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \UIManager
gi'self -> a -> UIManagerPostActivateCallback
gi'cb (UIManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce UIManager
gi'self)  Action
action'


-- | Connect a signal handler for the [postActivate](#signal:postActivate) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' uIManager #postActivate callback
-- @
-- 
-- 
onUIManagerPostActivate :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerPostActivateCallback) -> m SignalHandlerId
onUIManagerPostActivate :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerPostActivateCallback)
-> m SignalHandlerId
onUIManagerPostActivate a
obj (?self::a) => UIManagerPostActivateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerPostActivateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerPostActivateCallback
UIManagerPostActivateCallback
cb
    let wrapped' :: C_UIManagerPostActivateCallback
wrapped' = (a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
forall a.
GObject a =>
(a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
wrap_UIManagerPostActivateCallback a -> UIManagerPostActivateCallback
wrapped
    FunPtr C_UIManagerPostActivateCallback
wrapped'' <- C_UIManagerPostActivateCallback
-> IO (FunPtr C_UIManagerPostActivateCallback)
mk_UIManagerPostActivateCallback C_UIManagerPostActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerPostActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"post-activate" FunPtr C_UIManagerPostActivateCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [postActivate](#signal:postActivate) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' uIManager #postActivate callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterUIManagerPostActivate :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerPostActivateCallback) -> m SignalHandlerId
afterUIManagerPostActivate :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerPostActivateCallback)
-> m SignalHandlerId
afterUIManagerPostActivate a
obj (?self::a) => UIManagerPostActivateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerPostActivateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerPostActivateCallback
UIManagerPostActivateCallback
cb
    let wrapped' :: C_UIManagerPostActivateCallback
wrapped' = (a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
forall a.
GObject a =>
(a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
wrap_UIManagerPostActivateCallback a -> UIManagerPostActivateCallback
wrapped
    FunPtr C_UIManagerPostActivateCallback
wrapped'' <- C_UIManagerPostActivateCallback
-> IO (FunPtr C_UIManagerPostActivateCallback)
mk_UIManagerPostActivateCallback C_UIManagerPostActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerPostActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"post-activate" FunPtr C_UIManagerPostActivateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data UIManagerPostActivateSignalInfo
instance SignalInfo UIManagerPostActivateSignalInfo where
    type HaskellCallbackType UIManagerPostActivateSignalInfo = UIManagerPostActivateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_UIManagerPostActivateCallback cb
        cb'' <- mk_UIManagerPostActivateCallback cb'
        connectSignalFunPtr obj "post-activate" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager::post-activate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:signal:postActivate"})

#endif

-- signal UIManager::pre-activate
{-# DEPRECATED UIManagerPreActivateCallback ["(Since version 3.10)"] #-}
-- | The [preActivate](#g:signal:preActivate) signal is emitted just before the /@action@/
-- is activated.
-- 
-- This is intended for applications to get notification
-- just before any action is activated.
-- 
-- /Since: 2.4/
type UIManagerPreActivateCallback =
    Gtk.Action.Action
    -- ^ /@action@/: the action
    -> IO ()

type C_UIManagerPreActivateCallback =
    Ptr UIManager ->                        -- object
    Ptr Gtk.Action.Action ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_UIManagerPreActivateCallback`.
foreign import ccall "wrapper"
    mk_UIManagerPreActivateCallback :: C_UIManagerPreActivateCallback -> IO (FunPtr C_UIManagerPreActivateCallback)

wrap_UIManagerPreActivateCallback :: 
    GObject a => (a -> UIManagerPreActivateCallback) ->
    C_UIManagerPreActivateCallback
wrap_UIManagerPreActivateCallback :: forall a.
GObject a =>
(a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
wrap_UIManagerPreActivateCallback a -> UIManagerPostActivateCallback
gi'cb Ptr UIManager
gi'selfPtr Ptr Action
action Ptr ()
_ = do
    Action
action' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Action -> Action
Gtk.Action.Action) Ptr Action
action
    Ptr UIManager -> (UIManager -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr UIManager
gi'selfPtr ((UIManager -> IO ()) -> IO ()) -> (UIManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \UIManager
gi'self -> a -> UIManagerPostActivateCallback
gi'cb (UIManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce UIManager
gi'self)  Action
action'


-- | Connect a signal handler for the [preActivate](#signal:preActivate) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' uIManager #preActivate callback
-- @
-- 
-- 
onUIManagerPreActivate :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerPreActivateCallback) -> m SignalHandlerId
onUIManagerPreActivate :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerPostActivateCallback)
-> m SignalHandlerId
onUIManagerPreActivate a
obj (?self::a) => UIManagerPostActivateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerPostActivateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerPostActivateCallback
UIManagerPostActivateCallback
cb
    let wrapped' :: C_UIManagerPostActivateCallback
wrapped' = (a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
forall a.
GObject a =>
(a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
wrap_UIManagerPreActivateCallback a -> UIManagerPostActivateCallback
wrapped
    FunPtr C_UIManagerPostActivateCallback
wrapped'' <- C_UIManagerPostActivateCallback
-> IO (FunPtr C_UIManagerPostActivateCallback)
mk_UIManagerPreActivateCallback C_UIManagerPostActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerPostActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"pre-activate" FunPtr C_UIManagerPostActivateCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [preActivate](#signal:preActivate) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' uIManager #preActivate callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterUIManagerPreActivate :: (IsUIManager a, MonadIO m) => a -> ((?self :: a) => UIManagerPreActivateCallback) -> m SignalHandlerId
afterUIManagerPreActivate :: forall a (m :: * -> *).
(IsUIManager a, MonadIO m) =>
a
-> ((?self::a) => UIManagerPostActivateCallback)
-> m SignalHandlerId
afterUIManagerPreActivate a
obj (?self::a) => UIManagerPostActivateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> UIManagerPostActivateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => UIManagerPostActivateCallback
UIManagerPostActivateCallback
cb
    let wrapped' :: C_UIManagerPostActivateCallback
wrapped' = (a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
forall a.
GObject a =>
(a -> UIManagerPostActivateCallback)
-> C_UIManagerPostActivateCallback
wrap_UIManagerPreActivateCallback a -> UIManagerPostActivateCallback
wrapped
    FunPtr C_UIManagerPostActivateCallback
wrapped'' <- C_UIManagerPostActivateCallback
-> IO (FunPtr C_UIManagerPostActivateCallback)
mk_UIManagerPreActivateCallback C_UIManagerPostActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_UIManagerPostActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"pre-activate" FunPtr C_UIManagerPostActivateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data UIManagerPreActivateSignalInfo
instance SignalInfo UIManagerPreActivateSignalInfo where
    type HaskellCallbackType UIManagerPreActivateSignalInfo = UIManagerPreActivateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_UIManagerPreActivateCallback cb
        cb'' <- mk_UIManagerPreActivateCallback cb'
        connectSignalFunPtr obj "pre-activate" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager::pre-activate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:signal:preActivate"})

#endif

-- VVV Prop "add-tearoffs"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@add-tearoffs@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' uIManager [ #addTearoffs 'Data.GI.Base.Attributes.:=' value ]
-- @
setUIManagerAddTearoffs :: (MonadIO m, IsUIManager o) => o -> Bool -> m ()
setUIManagerAddTearoffs :: forall (m :: * -> *) o.
(MonadIO m, IsUIManager o) =>
o -> Bool -> m ()
setUIManagerAddTearoffs o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"add-tearoffs" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@add-tearoffs@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructUIManagerAddTearoffs :: (IsUIManager o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructUIManagerAddTearoffs :: forall o (m :: * -> *).
(IsUIManager o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructUIManagerAddTearoffs Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"add-tearoffs" Bool
val

#if defined(ENABLE_OVERLOADING)
data UIManagerAddTearoffsPropertyInfo
instance AttrInfo UIManagerAddTearoffsPropertyInfo where
    type AttrAllowedOps UIManagerAddTearoffsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint UIManagerAddTearoffsPropertyInfo = IsUIManager
    type AttrSetTypeConstraint UIManagerAddTearoffsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint UIManagerAddTearoffsPropertyInfo = (~) Bool
    type AttrTransferType UIManagerAddTearoffsPropertyInfo = Bool
    type AttrGetType UIManagerAddTearoffsPropertyInfo = Bool
    type AttrLabel UIManagerAddTearoffsPropertyInfo = "add-tearoffs"
    type AttrOrigin UIManagerAddTearoffsPropertyInfo = UIManager
    attrGet = getUIManagerAddTearoffs
    attrSet = setUIManagerAddTearoffs
    attrTransfer _ v = do
        return v
    attrConstruct = constructUIManagerAddTearoffs
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager.addTearoffs"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:attr:addTearoffs"
        })
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data UIManagerUiPropertyInfo
instance AttrInfo UIManagerUiPropertyInfo where
    type AttrAllowedOps UIManagerUiPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint UIManagerUiPropertyInfo = IsUIManager
    type AttrSetTypeConstraint UIManagerUiPropertyInfo = (~) ()
    type AttrTransferTypeConstraint UIManagerUiPropertyInfo = (~) ()
    type AttrTransferType UIManagerUiPropertyInfo = ()
    type AttrGetType UIManagerUiPropertyInfo = (Maybe T.Text)
    type AttrLabel UIManagerUiPropertyInfo = "ui"
    type AttrOrigin UIManagerUiPropertyInfo = UIManager
    attrGet = getUIManagerUi
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UIManager.ui"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-UIManager.html#g:attr:ui"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList UIManager
type instance O.AttributeList UIManager = UIManagerAttributeList
type UIManagerAttributeList = ('[ '("addTearoffs", UIManagerAddTearoffsPropertyInfo), '("ui", UIManagerUiPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
uIManagerAddTearoffs :: AttrLabelProxy "addTearoffs"
uIManagerAddTearoffs = AttrLabelProxy

uIManagerUi :: AttrLabelProxy "ui"
uIManagerUi = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList UIManager = UIManagerSignalList
type UIManagerSignalList = ('[ '("actionsChanged", UIManagerActionsChangedSignalInfo), '("addWidget", UIManagerAddWidgetSignalInfo), '("connectProxy", UIManagerConnectProxySignalInfo), '("disconnectProxy", UIManagerDisconnectProxySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("postActivate", UIManagerPostActivateSignalInfo), '("preActivate", UIManagerPreActivateSignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

foreign import ccall "gtk_ui_manager_new" gtk_ui_manager_new :: 
    IO (Ptr UIManager)

{-# DEPRECATED uIManagerNew ["(Since version 3.10)"] #-}
-- | Creates a new ui manager object.
-- 
-- /Since: 2.4/
uIManagerNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m UIManager
    -- ^ __Returns:__ a new ui manager object.
uIManagerNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m UIManager
uIManagerNew  = IO UIManager -> m UIManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UIManager -> m UIManager) -> IO UIManager -> m UIManager
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
result <- IO (Ptr UIManager)
gtk_ui_manager_new
    Text -> Ptr UIManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"uIManagerNew" Ptr UIManager
result
    UIManager
result' <- ((ManagedPtr UIManager -> UIManager)
-> Ptr UIManager -> IO UIManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UIManager -> UIManager
UIManager) Ptr UIManager
result
    UIManager -> IO UIManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UIManager
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method UIManager::add_ui
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "merge_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the merge id for the merged UI, see gtk_ui_manager_new_merge_id()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a path" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name for the added UI element"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the action to be proxied, or %NULL to add a separator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManagerItemType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the type of UI element to add."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "top"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "if %TRUE, the UI element is added before its siblings, otherwise it\n  is added after its siblings."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_ui_manager_add_ui" gtk_ui_manager_add_ui :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    Word32 ->                               -- merge_id : TBasicType TUInt
    CString ->                              -- path : TBasicType TUTF8
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- action : TBasicType TUTF8
    CUInt ->                                -- type : TInterface (Name {namespace = "Gtk", name = "UIManagerItemType"})
    CInt ->                                 -- top : TBasicType TBoolean
    IO ()

{-# DEPRECATED uIManagerAddUi ["(Since version 3.10)"] #-}
-- | Adds a UI element to the current contents of /@manager@/.
-- 
-- If /@type@/ is 'GI.Gtk.Flags.UIManagerItemTypeAuto', GTK+ inserts a menuitem, toolitem or
-- separator if such an element can be inserted at the place determined by
-- /@path@/. Otherwise /@type@/ must indicate an element that can be inserted at
-- the place determined by /@path@/.
-- 
-- If /@path@/ points to a menuitem or toolitem, the new element will be inserted
-- before or after this item, depending on /@top@/.
-- 
-- /Since: 2.4/
uIManagerAddUi ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> Word32
    -- ^ /@mergeId@/: the merge id for the merged UI, see 'GI.Gtk.Objects.UIManager.uIManagerNewMergeId'
    -> T.Text
    -- ^ /@path@/: a path
    -> T.Text
    -- ^ /@name@/: the name for the added UI element
    -> Maybe (T.Text)
    -- ^ /@action@/: the name of the action to be proxied, or 'P.Nothing' to add a separator
    -> [Gtk.Flags.UIManagerItemType]
    -- ^ /@type@/: the type of UI element to add.
    -> Bool
    -- ^ /@top@/: if 'P.True', the UI element is added before its siblings, otherwise it
    --   is added after its siblings.
    -> m ()
uIManagerAddUi :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a
-> Word32
-> Text
-> Text
-> Maybe Text
-> [UIManagerItemType]
-> Bool
-> m ()
uIManagerAddUi a
manager Word32
mergeId Text
path Text
name Maybe Text
action [UIManagerItemType]
type_ Bool
top = 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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
path' <- Text -> IO CString
textToCString Text
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
maybeAction <- case Maybe Text
action of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jAction -> do
            CString
jAction' <- Text -> IO CString
textToCString Text
jAction
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jAction'
    let type_' :: CUInt
type_' = [UIManagerItemType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [UIManagerItemType]
type_
    let top' :: CInt
top' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
top
    Ptr UIManager
-> Word32
-> CString
-> CString
-> CString
-> CUInt
-> CInt
-> IO ()
gtk_ui_manager_add_ui Ptr UIManager
manager' Word32
mergeId CString
path' CString
name' CString
maybeAction CUInt
type_' CInt
top'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeAction
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UIManagerAddUiMethodInfo
instance (signature ~ (Word32 -> T.Text -> T.Text -> Maybe (T.Text) -> [Gtk.Flags.UIManagerItemType] -> Bool -> m ()), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerAddUiMethodInfo a signature where
    overloadedMethod = uIManagerAddUi

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


#endif

-- method UIManager::add_ui_from_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the file to parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_ui_manager_add_ui_from_file" gtk_ui_manager_add_ui_from_file :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    CString ->                              -- filename : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO Word32

{-# DEPRECATED uIManagerAddUiFromFile ["(Since version 3.10)"] #-}
-- | Parses a file containing a [UI definition][XML-UI] and
-- merges it with the current contents of /@manager@/.
-- 
-- /Since: 2.4/
uIManagerAddUiFromFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> [Char]
    -- ^ /@filename@/: the name of the file to parse
    -> m Word32
    -- ^ __Returns:__ The merge id for the merged UI. The merge id can be used
    --   to unmerge the UI with 'GI.Gtk.Objects.UIManager.uIManagerRemoveUi'. If an error occurred,
    --   the return value is 0. /(Can throw 'Data.GI.Base.GError.GError')/
uIManagerAddUiFromFile :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> String -> m Word32
uIManagerAddUiFromFile a
manager String
filename = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
filename' <- String -> IO CString
stringToCString String
filename
    IO Word32 -> IO () -> IO Word32
forall a b. IO a -> IO b -> IO a
onException (do
        Word32
result <- (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Word32) -> IO Word32)
-> (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ Ptr UIManager -> CString -> Ptr (Ptr GError) -> IO Word32
gtk_ui_manager_add_ui_from_file Ptr UIManager
manager' CString
filename'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
data UIManagerAddUiFromFileMethodInfo
instance (signature ~ ([Char] -> m Word32), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerAddUiFromFileMethodInfo a signature where
    overloadedMethod = uIManagerAddUiFromFile

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


#endif

-- method UIManager::add_ui_from_resource
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the resource path of the file to parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_ui_manager_add_ui_from_resource" gtk_ui_manager_add_ui_from_resource :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    CString ->                              -- resource_path : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO Word32

{-# DEPRECATED uIManagerAddUiFromResource ["(Since version 3.10)"] #-}
-- | Parses a resource file containing a [UI definition][XML-UI] and
-- merges it with the current contents of /@manager@/.
-- 
-- /Since: 3.4/
uIManagerAddUiFromResource ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> T.Text
    -- ^ /@resourcePath@/: the resource path of the file to parse
    -> m Word32
    -- ^ __Returns:__ The merge id for the merged UI. The merge id can be used
    --   to unmerge the UI with 'GI.Gtk.Objects.UIManager.uIManagerRemoveUi'. If an error occurred,
    --   the return value is 0. /(Can throw 'Data.GI.Base.GError.GError')/
uIManagerAddUiFromResource :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> Text -> m Word32
uIManagerAddUiFromResource a
manager Text
resourcePath = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
resourcePath' <- Text -> IO CString
textToCString Text
resourcePath
    IO Word32 -> IO () -> IO Word32
forall a b. IO a -> IO b -> IO a
onException (do
        Word32
result <- (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Word32) -> IO Word32)
-> (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ Ptr UIManager -> CString -> Ptr (Ptr GError) -> IO Word32
gtk_ui_manager_add_ui_from_resource Ptr UIManager
manager' CString
resourcePath'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
        Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
     )

#if defined(ENABLE_OVERLOADING)
data UIManagerAddUiFromResourceMethodInfo
instance (signature ~ (T.Text -> m Word32), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerAddUiFromResourceMethodInfo a signature where
    overloadedMethod = uIManagerAddUiFromResource

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


#endif

-- method UIManager::add_ui_from_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the length of @buffer (may be -1 if @buffer is nul-terminated)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_ui_manager_add_ui_from_string" gtk_ui_manager_add_ui_from_string :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    CString ->                              -- buffer : TBasicType TUTF8
    Int64 ->                                -- length : TBasicType TInt64
    Ptr (Ptr GError) ->                     -- error
    IO Word32

{-# DEPRECATED uIManagerAddUiFromString ["(Since version 3.10)"] #-}
-- | Parses a string containing a [UI definition][XML-UI] and merges it with
-- the current contents of /@manager@/. An enclosing @\<ui>@ element is added if
-- it is missing.
-- 
-- /Since: 2.4/
uIManagerAddUiFromString ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> T.Text
    -- ^ /@buffer@/: the string to parse
    -> Int64
    -- ^ /@length@/: the length of /@buffer@/ (may be -1 if /@buffer@/ is nul-terminated)
    -> m Word32
    -- ^ __Returns:__ The merge id for the merged UI. The merge id can be used
    --   to unmerge the UI with 'GI.Gtk.Objects.UIManager.uIManagerRemoveUi'. If an error occurred,
    --   the return value is 0. /(Can throw 'Data.GI.Base.GError.GError')/
uIManagerAddUiFromString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> Text -> Int64 -> m Word32
uIManagerAddUiFromString a
manager Text
buffer Int64
length_ = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
buffer' <- Text -> IO CString
textToCString Text
buffer
    IO Word32 -> IO () -> IO Word32
forall a b. IO a -> IO b -> IO a
onException (do
        Word32
result <- (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Word32) -> IO Word32)
-> (Ptr (Ptr GError) -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ Ptr UIManager -> CString -> Int64 -> Ptr (Ptr GError) -> IO Word32
gtk_ui_manager_add_ui_from_string Ptr UIManager
manager' CString
buffer' Int64
length_
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
buffer'
        Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
buffer'
     )

#if defined(ENABLE_OVERLOADING)
data UIManagerAddUiFromStringMethodInfo
instance (signature ~ (T.Text -> Int64 -> m Word32), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerAddUiFromStringMethodInfo a signature where
    overloadedMethod = uIManagerAddUiFromString

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


#endif

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

foreign import ccall "gtk_ui_manager_ensure_update" gtk_ui_manager_ensure_update :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    IO ()

{-# DEPRECATED uIManagerEnsureUpdate ["(Since version 3.10)"] #-}
-- | Makes sure that all pending updates to the UI have been completed.
-- 
-- This may occasionally be necessary, since t'GI.Gtk.Objects.UIManager.UIManager' updates the
-- UI in an idle function. A typical example where this function is
-- useful is to enforce that the menubar and toolbar have been added to
-- the main window before showing it:
-- 
-- === /C code/
-- >
-- >gtk_container_add (GTK_CONTAINER (window), vbox);
-- >g_signal_connect (merge, "add-widget",
-- >                  G_CALLBACK (add_widget), vbox);
-- >gtk_ui_manager_add_ui_from_file (merge, "my-menus");
-- >gtk_ui_manager_add_ui_from_file (merge, "my-toolbars");
-- >gtk_ui_manager_ensure_update (merge);
-- >gtk_widget_show (window);
-- 
-- 
-- /Since: 2.4/
uIManagerEnsureUpdate ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> m ()
uIManagerEnsureUpdate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> m ()
uIManagerEnsureUpdate a
manager = 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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr UIManager -> IO ()
gtk_ui_manager_ensure_update Ptr UIManager
manager'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UIManagerEnsureUpdateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerEnsureUpdateMethodInfo a signature where
    overloadedMethod = uIManagerEnsureUpdate

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


#endif

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

foreign import ccall "gtk_ui_manager_get_accel_group" gtk_ui_manager_get_accel_group :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    IO (Ptr Gtk.AccelGroup.AccelGroup)

{-# DEPRECATED uIManagerGetAccelGroup ["(Since version 3.10)"] #-}
-- | Returns the t'GI.Gtk.Objects.AccelGroup.AccelGroup' associated with /@manager@/.
-- 
-- /Since: 2.4/
uIManagerGetAccelGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> m Gtk.AccelGroup.AccelGroup
    -- ^ __Returns:__ the t'GI.Gtk.Objects.AccelGroup.AccelGroup'.
uIManagerGetAccelGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> m AccelGroup
uIManagerGetAccelGroup a
manager = IO AccelGroup -> m AccelGroup
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AccelGroup -> m AccelGroup) -> IO AccelGroup -> m AccelGroup
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr AccelGroup
result <- Ptr UIManager -> IO (Ptr AccelGroup)
gtk_ui_manager_get_accel_group Ptr UIManager
manager'
    Text -> Ptr AccelGroup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"uIManagerGetAccelGroup" Ptr AccelGroup
result
    AccelGroup
result' <- ((ManagedPtr AccelGroup -> AccelGroup)
-> Ptr AccelGroup -> IO AccelGroup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AccelGroup -> AccelGroup
Gtk.AccelGroup.AccelGroup) Ptr AccelGroup
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    AccelGroup -> IO AccelGroup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AccelGroup
result'

#if defined(ENABLE_OVERLOADING)
data UIManagerGetAccelGroupMethodInfo
instance (signature ~ (m Gtk.AccelGroup.AccelGroup), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerGetAccelGroupMethodInfo a signature where
    overloadedMethod = uIManagerGetAccelGroup

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


#endif

-- method UIManager::get_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a path" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Action" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_ui_manager_get_action" gtk_ui_manager_get_action :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    CString ->                              -- path : TBasicType TUTF8
    IO (Ptr Gtk.Action.Action)

{-# DEPRECATED uIManagerGetAction ["(Since version 3.10)"] #-}
-- | Looks up an action by following a path. See 'GI.Gtk.Objects.UIManager.uIManagerGetWidget'
-- for more information about paths.
-- 
-- /Since: 2.4/
uIManagerGetAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> T.Text
    -- ^ /@path@/: a path
    -> m (Maybe Gtk.Action.Action)
    -- ^ __Returns:__ the action whose proxy widget is found by following the path,
    --     or 'P.Nothing' if no widget was found.
uIManagerGetAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> Text -> m (Maybe Action)
uIManagerGetAction a
manager Text
path = IO (Maybe Action) -> m (Maybe Action)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Action) -> m (Maybe Action))
-> IO (Maybe Action) -> m (Maybe Action)
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr Action
result <- Ptr UIManager -> CString -> IO (Ptr Action)
gtk_ui_manager_get_action Ptr UIManager
manager' CString
path'
    Maybe Action
maybeResult <- Ptr Action -> (Ptr Action -> IO Action) -> IO (Maybe Action)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Action
result ((Ptr Action -> IO Action) -> IO (Maybe Action))
-> (Ptr Action -> IO Action) -> IO (Maybe Action)
forall a b. (a -> b) -> a -> b
$ \Ptr Action
result' -> do
        Action
result'' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Action -> Action
Gtk.Action.Action) Ptr Action
result'
        Action -> IO Action
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Action
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    Maybe Action -> IO (Maybe Action)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Action
maybeResult

#if defined(ENABLE_OVERLOADING)
data UIManagerGetActionMethodInfo
instance (signature ~ (T.Text -> m (Maybe Gtk.Action.Action)), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerGetActionMethodInfo a signature where
    overloadedMethod = uIManagerGetAction

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


#endif

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

foreign import ccall "gtk_ui_manager_get_action_groups" gtk_ui_manager_get_action_groups :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    IO (Ptr (GList (Ptr Gtk.ActionGroup.ActionGroup)))

{-# DEPRECATED uIManagerGetActionGroups ["(Since version 3.10)"] #-}
-- | Returns the list of action groups associated with /@manager@/.
-- 
-- /Since: 2.4/
uIManagerGetActionGroups ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> m [Gtk.ActionGroup.ActionGroup]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of
    --   action groups. The list is owned by GTK+
    --   and should not be modified.
uIManagerGetActionGroups :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> m [ActionGroup]
uIManagerGetActionGroups a
manager = IO [ActionGroup] -> m [ActionGroup]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ActionGroup] -> m [ActionGroup])
-> IO [ActionGroup] -> m [ActionGroup]
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr (GList (Ptr ActionGroup))
result <- Ptr UIManager -> IO (Ptr (GList (Ptr ActionGroup)))
gtk_ui_manager_get_action_groups Ptr UIManager
manager'
    [Ptr ActionGroup]
result' <- Ptr (GList (Ptr ActionGroup)) -> IO [Ptr ActionGroup]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ActionGroup))
result
    [ActionGroup]
result'' <- (Ptr ActionGroup -> IO ActionGroup)
-> [Ptr ActionGroup] -> IO [ActionGroup]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr ActionGroup -> ActionGroup)
-> Ptr ActionGroup -> IO ActionGroup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ActionGroup -> ActionGroup
Gtk.ActionGroup.ActionGroup) [Ptr ActionGroup]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    [ActionGroup] -> IO [ActionGroup]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ActionGroup]
result''

#if defined(ENABLE_OVERLOADING)
data UIManagerGetActionGroupsMethodInfo
instance (signature ~ (m [Gtk.ActionGroup.ActionGroup]), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerGetActionGroupsMethodInfo a signature where
    overloadedMethod = uIManagerGetActionGroups

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


#endif

-- method UIManager::get_add_tearoffs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager" , 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_ui_manager_get_add_tearoffs" gtk_ui_manager_get_add_tearoffs :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    IO CInt

{-# DEPRECATED uIManagerGetAddTearoffs ["(Since version 3.4)","Tearoff menus are deprecated and should not","    be used in newly written code."] #-}
-- | Returns whether menus generated by this t'GI.Gtk.Objects.UIManager.UIManager'
-- will have tearoff menu items.
-- 
-- /Since: 2.4/
uIManagerGetAddTearoffs ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> m Bool
    -- ^ __Returns:__ whether tearoff menu items are added
uIManagerGetAddTearoffs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> m Bool
uIManagerGetAddTearoffs a
manager = 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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CInt
result <- Ptr UIManager -> IO CInt
gtk_ui_manager_get_add_tearoffs Ptr UIManager
manager'
    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
manager
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data UIManagerGetAddTearoffsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerGetAddTearoffsMethodInfo a signature where
    overloadedMethod = uIManagerGetAddTearoffs

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


#endif

-- method UIManager::get_toplevels
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "types"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManagerItemType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies the types of toplevel widgets to include. Allowed\n  types are #GTK_UI_MANAGER_MENUBAR, #GTK_UI_MANAGER_TOOLBAR and\n  #GTK_UI_MANAGER_POPUP."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGSList (TInterface Name { namespace = "Gtk" , name = "Widget" }))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_ui_manager_get_toplevels" gtk_ui_manager_get_toplevels :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    CUInt ->                                -- types : TInterface (Name {namespace = "Gtk", name = "UIManagerItemType"})
    IO (Ptr (GSList (Ptr Gtk.Widget.Widget)))

{-# DEPRECATED uIManagerGetToplevels ["(Since version 3.10)"] #-}
-- | Obtains a list of all toplevel widgets of the requested types.
-- 
-- /Since: 2.4/
uIManagerGetToplevels ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> [Gtk.Flags.UIManagerItemType]
    -- ^ /@types@/: specifies the types of toplevel widgets to include. Allowed
    --   types are @/GTK_UI_MANAGER_MENUBAR/@, @/GTK_UI_MANAGER_TOOLBAR/@ and
    --   @/GTK_UI_MANAGER_POPUP/@.
    -> m [Gtk.Widget.Widget]
    -- ^ __Returns:__ a newly-allocated t'GI.GLib.Structs.SList.SList' of
    -- all toplevel widgets of the requested types.  Free the returned list with @/g_slist_free()/@.
uIManagerGetToplevels :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> [UIManagerItemType] -> m [Widget]
uIManagerGetToplevels a
manager [UIManagerItemType]
types = IO [Widget] -> m [Widget]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Widget] -> m [Widget]) -> IO [Widget] -> m [Widget]
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    let types' :: CUInt
types' = [UIManagerItemType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [UIManagerItemType]
types
    Ptr (GSList (Ptr Widget))
result <- Ptr UIManager -> CUInt -> IO (Ptr (GSList (Ptr Widget)))
gtk_ui_manager_get_toplevels Ptr UIManager
manager' CUInt
types'
    [Ptr Widget]
result' <- Ptr (GSList (Ptr Widget)) -> IO [Ptr Widget]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Widget))
result
    [Widget]
result'' <- (Ptr Widget -> IO Widget) -> [Ptr Widget] -> IO [Widget]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((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'
    Ptr (GSList (Ptr Widget)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr Widget))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    [Widget] -> IO [Widget]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Widget]
result''

#if defined(ENABLE_OVERLOADING)
data UIManagerGetToplevelsMethodInfo
instance (signature ~ ([Gtk.Flags.UIManagerItemType] -> m [Gtk.Widget.Widget]), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerGetToplevelsMethodInfo a signature where
    overloadedMethod = uIManagerGetToplevels

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


#endif

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

foreign import ccall "gtk_ui_manager_get_ui" gtk_ui_manager_get_ui :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    IO CString

{-# DEPRECATED uIManagerGetUi ["(Since version 3.10)"] #-}
-- | Creates a [UI definition][XML-UI] of the merged UI.
-- 
-- /Since: 2.4/
uIManagerGetUi ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> m T.Text
    -- ^ __Returns:__ A newly allocated string containing an XML representation of
    -- the merged UI.
uIManagerGetUi :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> m Text
uIManagerGetUi a
manager = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
result <- Ptr UIManager -> IO CString
gtk_ui_manager_get_ui Ptr UIManager
manager'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"uIManagerGetUi" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data UIManagerGetUiMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerGetUiMethodInfo a signature where
    overloadedMethod = uIManagerGetUi

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


#endif

-- method UIManager::get_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a path" , 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_ui_manager_get_widget" gtk_ui_manager_get_widget :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    CString ->                              -- path : TBasicType TUTF8
    IO (Ptr Gtk.Widget.Widget)

{-# DEPRECATED uIManagerGetWidget ["(Since version 3.10)"] #-}
-- | Looks up a widget by following a path.
-- The path consists of the names specified in the XML description of the UI.
-- separated by “\/”. Elements which don’t have a name or action attribute in
-- the XML (e.g. @\<popup>@) can be addressed by their XML element name
-- (e.g. \"popup\"). The root element (\"\/ui\") can be omitted in the path.
-- 
-- Note that the widget found by following a path that ends in a @\<menu>@;
-- element is the menuitem to which the menu is attached, not the menu it
-- manages.
-- 
-- Also note that the widgets constructed by a ui manager are not tied to
-- the lifecycle of the ui manager. If you add the widgets returned by this
-- function to some container or explicitly ref them, they will survive the
-- destruction of the ui manager.
-- 
-- /Since: 2.4/
uIManagerGetWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> T.Text
    -- ^ /@path@/: a path
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the widget found by following the path,
    --     or 'P.Nothing' if no widget was found
uIManagerGetWidget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> Text -> m (Maybe Widget)
uIManagerGetWidget a
manager Text
path = IO (Maybe Widget) -> m (Maybe Widget)
forall a. IO a -> m a
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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr Widget
result <- Ptr UIManager -> CString -> IO (Ptr Widget)
gtk_ui_manager_get_widget Ptr UIManager
manager' CString
path'
    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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    Maybe Widget -> IO (Maybe Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult

#if defined(ENABLE_OVERLOADING)
data UIManagerGetWidgetMethodInfo
instance (signature ~ (T.Text -> m (Maybe Gtk.Widget.Widget)), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerGetWidgetMethodInfo a signature where
    overloadedMethod = uIManagerGetWidget

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


#endif

-- method UIManager::insert_action_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the action group to be inserted"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the position at which the group will be inserted."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_ui_manager_insert_action_group" gtk_ui_manager_insert_action_group :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    Ptr Gtk.ActionGroup.ActionGroup ->      -- action_group : TInterface (Name {namespace = "Gtk", name = "ActionGroup"})
    Int32 ->                                -- pos : TBasicType TInt
    IO ()

{-# DEPRECATED uIManagerInsertActionGroup ["(Since version 3.10)"] #-}
-- | Inserts an action group into the list of action groups associated
-- with /@manager@/. Actions in earlier groups hide actions with the same
-- name in later groups.
-- 
-- If /@pos@/ is larger than the number of action groups in /@manager@/, or
-- negative, /@actionGroup@/ will be inserted at the end of the internal
-- list.
-- 
-- /Since: 2.4/
uIManagerInsertActionGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a, Gtk.ActionGroup.IsActionGroup b) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> b
    -- ^ /@actionGroup@/: the action group to be inserted
    -> Int32
    -- ^ /@pos@/: the position at which the group will be inserted.
    -> m ()
uIManagerInsertActionGroup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsUIManager a, IsActionGroup b) =>
a -> b -> Int32 -> m ()
uIManagerInsertActionGroup a
manager b
actionGroup Int32
pos = 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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr ActionGroup
actionGroup' <- b -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actionGroup
    Ptr UIManager -> Ptr ActionGroup -> Int32 -> IO ()
gtk_ui_manager_insert_action_group Ptr UIManager
manager' Ptr ActionGroup
actionGroup' Int32
pos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actionGroup
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UIManagerInsertActionGroupMethodInfo
instance (signature ~ (b -> Int32 -> m ()), MonadIO m, IsUIManager a, Gtk.ActionGroup.IsActionGroup b) => O.OverloadedMethod UIManagerInsertActionGroupMethodInfo a signature where
    overloadedMethod = uIManagerInsertActionGroup

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


#endif

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

foreign import ccall "gtk_ui_manager_new_merge_id" gtk_ui_manager_new_merge_id :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    IO Word32

{-# DEPRECATED uIManagerNewMergeId ["(Since version 3.10)"] #-}
-- | Returns an unused merge id, suitable for use with
-- 'GI.Gtk.Objects.UIManager.uIManagerAddUi'.
-- 
-- /Since: 2.4/
uIManagerNewMergeId ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> m Word32
    -- ^ __Returns:__ an unused merge id.
uIManagerNewMergeId :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> m Word32
uIManagerNewMergeId a
manager = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Word32
result <- Ptr UIManager -> IO Word32
gtk_ui_manager_new_merge_id Ptr UIManager
manager'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data UIManagerNewMergeIdMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerNewMergeIdMethodInfo a signature where
    overloadedMethod = uIManagerNewMergeId

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


#endif

-- method UIManager::remove_action_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_group"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ActionGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the action group 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_ui_manager_remove_action_group" gtk_ui_manager_remove_action_group :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    Ptr Gtk.ActionGroup.ActionGroup ->      -- action_group : TInterface (Name {namespace = "Gtk", name = "ActionGroup"})
    IO ()

{-# DEPRECATED uIManagerRemoveActionGroup ["(Since version 3.10)"] #-}
-- | Removes an action group from the list of action groups associated
-- with /@manager@/.
-- 
-- /Since: 2.4/
uIManagerRemoveActionGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a, Gtk.ActionGroup.IsActionGroup b) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> b
    -- ^ /@actionGroup@/: the action group to be removed
    -> m ()
uIManagerRemoveActionGroup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsUIManager a, IsActionGroup b) =>
a -> b -> m ()
uIManagerRemoveActionGroup a
manager b
actionGroup = 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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr ActionGroup
actionGroup' <- b -> IO (Ptr ActionGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actionGroup
    Ptr UIManager -> Ptr ActionGroup -> IO ()
gtk_ui_manager_remove_action_group Ptr UIManager
manager' Ptr ActionGroup
actionGroup'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actionGroup
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UIManagerRemoveActionGroupMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsUIManager a, Gtk.ActionGroup.IsActionGroup b) => O.OverloadedMethod UIManagerRemoveActionGroupMethodInfo a signature where
    overloadedMethod = uIManagerRemoveActionGroup

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


#endif

-- method UIManager::remove_ui
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "merge_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a merge id as returned by gtk_ui_manager_add_ui_from_string()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_ui_manager_remove_ui" gtk_ui_manager_remove_ui :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    Word32 ->                               -- merge_id : TBasicType TUInt
    IO ()

{-# DEPRECATED uIManagerRemoveUi ["(Since version 3.10)"] #-}
-- | Unmerges the part of /@manager@/\'s content identified by /@mergeId@/.
-- 
-- /Since: 2.4/
uIManagerRemoveUi ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager' object
    -> Word32
    -- ^ /@mergeId@/: a merge id as returned by 'GI.Gtk.Objects.UIManager.uIManagerAddUiFromString'
    -> m ()
uIManagerRemoveUi :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> Word32 -> m ()
uIManagerRemoveUi a
manager Word32
mergeId = 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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr UIManager -> Word32 -> IO ()
gtk_ui_manager_remove_ui Ptr UIManager
manager' Word32
mergeId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UIManagerRemoveUiMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerRemoveUiMethodInfo a signature where
    overloadedMethod = uIManagerRemoveUi

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


#endif

-- method UIManager::set_add_tearoffs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UIManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkUIManager" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "add_tearoffs"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether tearoff menu items are added"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_ui_manager_set_add_tearoffs" gtk_ui_manager_set_add_tearoffs :: 
    Ptr UIManager ->                        -- manager : TInterface (Name {namespace = "Gtk", name = "UIManager"})
    CInt ->                                 -- add_tearoffs : TBasicType TBoolean
    IO ()

{-# DEPRECATED uIManagerSetAddTearoffs ["(Since version 3.4)","Tearoff menus are deprecated and should not","    be used in newly written code."] #-}
-- | Sets the “add_tearoffs” property, which controls whether menus
-- generated by this t'GI.Gtk.Objects.UIManager.UIManager' will have tearoff menu items.
-- 
-- Note that this only affects regular menus. Generated popup
-- menus never have tearoff menu items.
-- 
-- /Since: 2.4/
uIManagerSetAddTearoffs ::
    (B.CallStack.HasCallStack, MonadIO m, IsUIManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gtk.Objects.UIManager.UIManager'
    -> Bool
    -- ^ /@addTearoffs@/: whether tearoff menu items are added
    -> m ()
uIManagerSetAddTearoffs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUIManager a) =>
a -> Bool -> m ()
uIManagerSetAddTearoffs a
manager Bool
addTearoffs = 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 UIManager
manager' <- a -> IO (Ptr UIManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    let addTearoffs' :: CInt
addTearoffs' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
addTearoffs
    Ptr UIManager -> CInt -> IO ()
gtk_ui_manager_set_add_tearoffs Ptr UIManager
manager' CInt
addTearoffs'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UIManagerSetAddTearoffsMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsUIManager a) => O.OverloadedMethod UIManagerSetAddTearoffsMethodInfo a signature where
    overloadedMethod = uIManagerSetAddTearoffs

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


#endif