{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.MenuItem.MenuItem' is an opaque structure type.  You must access it using the
-- functions below.
-- 
-- /Since: 2.32/

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

module GI.Gio.Objects.MenuItem
    ( 

-- * Exported types
    MenuItem(..)                            ,
    IsMenuItem                              ,
    toMenuItem                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [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
-- [getAttributeValue]("GI.Gio.Objects.MenuItem#g:method:getAttributeValue"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getLink]("GI.Gio.Objects.MenuItem#g:method:getLink"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setActionAndTargetValue]("GI.Gio.Objects.MenuItem#g:method:setActionAndTargetValue"), [setAttributeValue]("GI.Gio.Objects.MenuItem#g:method:setAttributeValue"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDetailedAction]("GI.Gio.Objects.MenuItem#g:method:setDetailedAction"), [setIcon]("GI.Gio.Objects.MenuItem#g:method:setIcon"), [setLabel]("GI.Gio.Objects.MenuItem#g:method:setLabel"), [setLink]("GI.Gio.Objects.MenuItem#g:method:setLink"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSection]("GI.Gio.Objects.MenuItem#g:method:setSection"), [setSubmenu]("GI.Gio.Objects.MenuItem#g:method:setSubmenu").

#if defined(ENABLE_OVERLOADING)
    ResolveMenuItemMethod                   ,
#endif

-- ** getAttributeValue #method:getAttributeValue#

#if defined(ENABLE_OVERLOADING)
    MenuItemGetAttributeValueMethodInfo     ,
#endif
    menuItemGetAttributeValue               ,


-- ** getLink #method:getLink#

#if defined(ENABLE_OVERLOADING)
    MenuItemGetLinkMethodInfo               ,
#endif
    menuItemGetLink                         ,


-- ** new #method:new#

    menuItemNew                             ,


-- ** newFromModel #method:newFromModel#

    menuItemNewFromModel                    ,


-- ** newSection #method:newSection#

    menuItemNewSection                      ,


-- ** newSubmenu #method:newSubmenu#

    menuItemNewSubmenu                      ,


-- ** setActionAndTargetValue #method:setActionAndTargetValue#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetActionAndTargetValueMethodInfo,
#endif
    menuItemSetActionAndTargetValue         ,


-- ** setAttributeValue #method:setAttributeValue#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetAttributeValueMethodInfo     ,
#endif
    menuItemSetAttributeValue               ,


-- ** setDetailedAction #method:setDetailedAction#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetDetailedActionMethodInfo     ,
#endif
    menuItemSetDetailedAction               ,


-- ** setIcon #method:setIcon#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetIconMethodInfo               ,
#endif
    menuItemSetIcon                         ,


-- ** setLabel #method:setLabel#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetLabelMethodInfo              ,
#endif
    menuItemSetLabel                        ,


-- ** setLink #method:setLink#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetLinkMethodInfo               ,
#endif
    menuItemSetLink                         ,


-- ** setSection #method:setSection#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetSectionMethodInfo            ,
#endif
    menuItemSetSection                      ,


-- ** setSubmenu #method:setSubmenu#

#if defined(ENABLE_OVERLOADING)
    MenuItemSetSubmenuMethodInfo            ,
#endif
    menuItemSetSubmenu                      ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Objects.MenuModel as Gio.MenuModel

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

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

foreign import ccall "g_menu_item_get_type"
    c_g_menu_item_get_type :: IO B.Types.GType

instance B.Types.TypedObject MenuItem where
    glibType :: IO GType
glibType = IO GType
c_g_menu_item_get_type

instance B.Types.GObject MenuItem

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

instance O.HasParentTypes MenuItem
type instance O.ParentTypes MenuItem = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveMenuItemMethod (t :: Symbol) (o :: *) :: * where
    ResolveMenuItemMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveMenuItemMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveMenuItemMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveMenuItemMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveMenuItemMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveMenuItemMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveMenuItemMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveMenuItemMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveMenuItemMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveMenuItemMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveMenuItemMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveMenuItemMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveMenuItemMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveMenuItemMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveMenuItemMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveMenuItemMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveMenuItemMethod "getAttributeValue" o = MenuItemGetAttributeValueMethodInfo
    ResolveMenuItemMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveMenuItemMethod "getLink" o = MenuItemGetLinkMethodInfo
    ResolveMenuItemMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveMenuItemMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveMenuItemMethod "setActionAndTargetValue" o = MenuItemSetActionAndTargetValueMethodInfo
    ResolveMenuItemMethod "setAttributeValue" o = MenuItemSetAttributeValueMethodInfo
    ResolveMenuItemMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveMenuItemMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveMenuItemMethod "setDetailedAction" o = MenuItemSetDetailedActionMethodInfo
    ResolveMenuItemMethod "setIcon" o = MenuItemSetIconMethodInfo
    ResolveMenuItemMethod "setLabel" o = MenuItemSetLabelMethodInfo
    ResolveMenuItemMethod "setLink" o = MenuItemSetLinkMethodInfo
    ResolveMenuItemMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveMenuItemMethod "setSection" o = MenuItemSetSectionMethodInfo
    ResolveMenuItemMethod "setSubmenu" o = MenuItemSetSubmenuMethodInfo
    ResolveMenuItemMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MenuItem
type instance O.AttributeList MenuItem = MenuItemAttributeList
type MenuItemAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method MenuItem::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the section label, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detailed_action"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the detailed action string, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "MenuItem" })
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_new" g_menu_item_new :: 
    CString ->                              -- label : TBasicType TUTF8
    CString ->                              -- detailed_action : TBasicType TUTF8
    IO (Ptr MenuItem)

-- | Creates a new t'GI.Gio.Objects.MenuItem.MenuItem'.
-- 
-- If /@label@/ is non-'P.Nothing' it is used to set the \"label\" attribute of the
-- new item.
-- 
-- If /@detailedAction@/ is non-'P.Nothing' it is used to set the \"action\" and
-- possibly the \"target\" attribute of the new item.  See
-- 'GI.Gio.Objects.MenuItem.menuItemSetDetailedAction' for more information.
-- 
-- /Since: 2.32/
menuItemNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@label@/: the section label, or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@detailedAction@/: the detailed action string, or 'P.Nothing'
    -> m MenuItem
    -- ^ __Returns:__ a new t'GI.Gio.Objects.MenuItem.MenuItem'
menuItemNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> Maybe Text -> m MenuItem
menuItemNew Maybe Text
label Maybe Text
detailedAction = IO MenuItem -> m MenuItem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuItem -> m MenuItem) -> IO MenuItem -> m MenuItem
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            Ptr CChar
jLabel' <- Text -> IO (Ptr CChar)
textToCString Text
jLabel
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jLabel'
    Ptr CChar
maybeDetailedAction <- case Maybe Text
detailedAction of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jDetailedAction -> do
            Ptr CChar
jDetailedAction' <- Text -> IO (Ptr CChar)
textToCString Text
jDetailedAction
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jDetailedAction'
    Ptr MenuItem
result <- Ptr CChar -> Ptr CChar -> IO (Ptr MenuItem)
g_menu_item_new Ptr CChar
maybeLabel Ptr CChar
maybeDetailedAction
    Text -> Ptr MenuItem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuItemNew" Ptr MenuItem
result
    MenuItem
result' <- ((ManagedPtr MenuItem -> MenuItem) -> Ptr MenuItem -> IO MenuItem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MenuItem -> MenuItem
MenuItem) Ptr MenuItem
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeLabel
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeDetailedAction
    MenuItem -> IO MenuItem
forall (m :: * -> *) a. Monad m => a -> m a
return MenuItem
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MenuItem::new_from_model
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuModel" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item_index"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of an item in @model"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "MenuItem" })
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_new_from_model" g_menu_item_new_from_model :: 
    Ptr Gio.MenuModel.MenuModel ->          -- model : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    Int32 ->                                -- item_index : TBasicType TInt
    IO (Ptr MenuItem)

-- | Creates a t'GI.Gio.Objects.MenuItem.MenuItem' as an exact copy of an existing menu item in a
-- t'GI.Gio.Objects.MenuModel.MenuModel'.
-- 
-- /@itemIndex@/ must be valid (ie: be sure to call
-- 'GI.Gio.Objects.MenuModel.menuModelGetNItems' first).
-- 
-- /Since: 2.34/
menuItemNewFromModel ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.MenuModel.IsMenuModel a) =>
    a
    -- ^ /@model@/: a t'GI.Gio.Objects.MenuModel.MenuModel'
    -> Int32
    -- ^ /@itemIndex@/: the index of an item in /@model@/
    -> m MenuItem
    -- ^ __Returns:__ a new t'GI.Gio.Objects.MenuItem.MenuItem'.
menuItemNewFromModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuModel a) =>
a -> Int32 -> m MenuItem
menuItemNewFromModel a
model Int32
itemIndex = IO MenuItem -> m MenuItem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuItem -> m MenuItem) -> IO MenuItem -> m MenuItem
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuModel
model' <- a -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
    Ptr MenuItem
result <- Ptr MenuModel -> Int32 -> IO (Ptr MenuItem)
g_menu_item_new_from_model Ptr MenuModel
model' Int32
itemIndex
    Text -> Ptr MenuItem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuItemNewFromModel" Ptr MenuItem
result
    MenuItem
result' <- ((ManagedPtr MenuItem -> MenuItem) -> Ptr MenuItem -> IO MenuItem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MenuItem -> MenuItem
MenuItem) Ptr MenuItem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
model
    MenuItem -> IO MenuItem
forall (m :: * -> *) a. Monad m => a -> m a
return MenuItem
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MenuItem::new_section
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the section label, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "section"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuModel with the items of the section"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "MenuItem" })
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_new_section" g_menu_item_new_section :: 
    CString ->                              -- label : TBasicType TUTF8
    Ptr Gio.MenuModel.MenuModel ->          -- section : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO (Ptr MenuItem)

-- | Creates a new t'GI.Gio.Objects.MenuItem.MenuItem' representing a section.
-- 
-- This is a convenience API around 'GI.Gio.Objects.MenuItem.menuItemNew' and
-- 'GI.Gio.Objects.MenuItem.menuItemSetSection'.
-- 
-- The effect of having one menu appear as a section of another is
-- exactly as it sounds: the items from /@section@/ become a direct part of
-- the menu that /@menuItem@/ is added to.
-- 
-- Visual separation is typically displayed between two non-empty
-- sections.  If /@label@/ is non-'P.Nothing' then it will be encorporated into
-- this visual indication.  This allows for labeled subsections of a
-- menu.
-- 
-- As a simple example, consider a typical \"Edit\" menu from a simple
-- program.  It probably contains an \"Undo\" and \"Redo\" item, followed by
-- a separator, followed by \"Cut\", \"Copy\" and \"Paste\".
-- 
-- This would be accomplished by creating three t'GI.Gio.Objects.Menu.Menu' instances.  The
-- first would be populated with the \"Undo\" and \"Redo\" items, and the
-- second with the \"Cut\", \"Copy\" and \"Paste\" items.  The first and
-- second menus would then be added as submenus of the third.  In XML
-- format, this would look something like the following:
-- >
-- ><menu id='edit-menu'>
-- >  <section>
-- >    <item label='Undo'/>
-- >    <item label='Redo'/>
-- >  </section>
-- >  <section>
-- >    <item label='Cut'/>
-- >    <item label='Copy'/>
-- >    <item label='Paste'/>
-- >  </section>
-- ></menu>
-- 
-- 
-- The following example is exactly equivalent.  It is more illustrative
-- of the exact relationship between the menus and items (keeping in
-- mind that the \'link\' element defines a new menu that is linked to the
-- containing one).  The style of the second example is more verbose and
-- difficult to read (and therefore not recommended except for the
-- purpose of understanding what is really going on).
-- >
-- ><menu id='edit-menu'>
-- >  <item>
-- >    <link name='section'>
-- >      <item label='Undo'/>
-- >      <item label='Redo'/>
-- >    </link>
-- >  </item>
-- >  <item>
-- >    <link name='section'>
-- >      <item label='Cut'/>
-- >      <item label='Copy'/>
-- >      <item label='Paste'/>
-- >    </link>
-- >  </item>
-- ></menu>
-- 
-- 
-- /Since: 2.32/
menuItemNewSection ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.MenuModel.IsMenuModel a) =>
    Maybe (T.Text)
    -- ^ /@label@/: the section label, or 'P.Nothing'
    -> a
    -- ^ /@section@/: a t'GI.Gio.Objects.MenuModel.MenuModel' with the items of the section
    -> m MenuItem
    -- ^ __Returns:__ a new t'GI.Gio.Objects.MenuItem.MenuItem'
menuItemNewSection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuModel a) =>
Maybe Text -> a -> m MenuItem
menuItemNewSection Maybe Text
label a
section = IO MenuItem -> m MenuItem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuItem -> m MenuItem) -> IO MenuItem -> m MenuItem
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            Ptr CChar
jLabel' <- Text -> IO (Ptr CChar)
textToCString Text
jLabel
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jLabel'
    Ptr MenuModel
section' <- a -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
section
    Ptr MenuItem
result <- Ptr CChar -> Ptr MenuModel -> IO (Ptr MenuItem)
g_menu_item_new_section Ptr CChar
maybeLabel Ptr MenuModel
section'
    Text -> Ptr MenuItem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuItemNewSection" Ptr MenuItem
result
    MenuItem
result' <- ((ManagedPtr MenuItem -> MenuItem) -> Ptr MenuItem -> IO MenuItem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MenuItem -> MenuItem
MenuItem) Ptr MenuItem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
section
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeLabel
    MenuItem -> IO MenuItem
forall (m :: * -> *) a. Monad m => a -> m a
return MenuItem
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MenuItem::new_submenu
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the section label, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "submenu"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuModel with the items of the submenu"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "MenuItem" })
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_new_submenu" g_menu_item_new_submenu :: 
    CString ->                              -- label : TBasicType TUTF8
    Ptr Gio.MenuModel.MenuModel ->          -- submenu : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO (Ptr MenuItem)

-- | Creates a new t'GI.Gio.Objects.MenuItem.MenuItem' representing a submenu.
-- 
-- This is a convenience API around 'GI.Gio.Objects.MenuItem.menuItemNew' and
-- 'GI.Gio.Objects.MenuItem.menuItemSetSubmenu'.
-- 
-- /Since: 2.32/
menuItemNewSubmenu ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.MenuModel.IsMenuModel a) =>
    Maybe (T.Text)
    -- ^ /@label@/: the section label, or 'P.Nothing'
    -> a
    -- ^ /@submenu@/: a t'GI.Gio.Objects.MenuModel.MenuModel' with the items of the submenu
    -> m MenuItem
    -- ^ __Returns:__ a new t'GI.Gio.Objects.MenuItem.MenuItem'
menuItemNewSubmenu :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuModel a) =>
Maybe Text -> a -> m MenuItem
menuItemNewSubmenu Maybe Text
label a
submenu = IO MenuItem -> m MenuItem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuItem -> m MenuItem) -> IO MenuItem -> m MenuItem
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            Ptr CChar
jLabel' <- Text -> IO (Ptr CChar)
textToCString Text
jLabel
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jLabel'
    Ptr MenuModel
submenu' <- a -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
submenu
    Ptr MenuItem
result <- Ptr CChar -> Ptr MenuModel -> IO (Ptr MenuItem)
g_menu_item_new_submenu Ptr CChar
maybeLabel Ptr MenuModel
submenu'
    Text -> Ptr MenuItem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuItemNewSubmenu" Ptr MenuItem
result
    MenuItem
result' <- ((ManagedPtr MenuItem -> MenuItem) -> Ptr MenuItem -> IO MenuItem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MenuItem -> MenuItem
MenuItem) Ptr MenuItem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
submenu
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeLabel
    MenuItem -> IO MenuItem
forall (m :: * -> *) a. Monad m => a -> m a
return MenuItem
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MenuItem::get_attribute_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attribute"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute name to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "expected_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the expected type of the attribute"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_get_attribute_value" g_menu_item_get_attribute_value :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    CString ->                              -- attribute : TBasicType TUTF8
    Ptr GLib.VariantType.VariantType ->     -- expected_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr GVariant)

-- | Queries the named /@attribute@/ on /@menuItem@/.
-- 
-- If /@expectedType@/ is specified and the attribute does not have this
-- type, 'P.Nothing' is returned.  'P.Nothing' is also returned if the attribute
-- simply does not exist.
-- 
-- /Since: 2.34/
menuItemGetAttributeValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> T.Text
    -- ^ /@attribute@/: the attribute name to query
    -> Maybe (GLib.VariantType.VariantType)
    -- ^ /@expectedType@/: the expected type of the attribute
    -> m (Maybe GVariant)
    -- ^ __Returns:__ the attribute value, or 'P.Nothing'
menuItemGetAttributeValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuItem a) =>
a -> Text -> Maybe VariantType -> m (Maybe GVariant)
menuItemGetAttributeValue a
menuItem Text
attribute Maybe VariantType
expectedType = IO (Maybe GVariant) -> m (Maybe GVariant)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GVariant) -> m (Maybe GVariant))
-> IO (Maybe GVariant) -> m (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr CChar
attribute' <- Text -> IO (Ptr CChar)
textToCString Text
attribute
    Ptr VariantType
maybeExpectedType <- case Maybe VariantType
expectedType of
        Maybe VariantType
Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
nullPtr
        Just VariantType
jExpectedType -> do
            Ptr VariantType
jExpectedType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jExpectedType
            Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
jExpectedType'
    Ptr GVariant
result <- Ptr MenuItem -> Ptr CChar -> Ptr VariantType -> IO (Ptr GVariant)
g_menu_item_get_attribute_value Ptr MenuItem
menuItem' Ptr CChar
attribute' Ptr VariantType
maybeExpectedType
    Maybe GVariant
maybeResult <- Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GVariant
result ((Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant))
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ \Ptr GVariant
result' -> do
        GVariant
result'' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Maybe VariantType -> (VariantType -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe VariantType
expectedType VariantType -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
attribute'
    Maybe GVariant -> IO (Maybe GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GVariant
maybeResult

#if defined(ENABLE_OVERLOADING)
data MenuItemGetAttributeValueMethodInfo
instance (signature ~ (T.Text -> Maybe (GLib.VariantType.VariantType) -> m (Maybe GVariant)), MonadIO m, IsMenuItem a) => O.OverloadedMethod MenuItemGetAttributeValueMethodInfo a signature where
    overloadedMethod = menuItemGetAttributeValue

instance O.OverloadedMethodInfo MenuItemGetAttributeValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemGetAttributeValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemGetAttributeValue"
        })


#endif

-- method MenuItem::get_link
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "link"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the link name to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "MenuModel" })
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_get_link" g_menu_item_get_link :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    CString ->                              -- link : TBasicType TUTF8
    IO (Ptr Gio.MenuModel.MenuModel)

-- | Queries the named /@link@/ on /@menuItem@/.
-- 
-- /Since: 2.34/
menuItemGetLink ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> T.Text
    -- ^ /@link@/: the link name to query
    -> m (Maybe Gio.MenuModel.MenuModel)
    -- ^ __Returns:__ the link, or 'P.Nothing'
menuItemGetLink :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuItem a) =>
a -> Text -> m (Maybe MenuModel)
menuItemGetLink a
menuItem Text
link = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr CChar
link' <- Text -> IO (Ptr CChar)
textToCString Text
link
    Ptr MenuModel
result <- Ptr MenuItem -> Ptr CChar -> IO (Ptr MenuModel)
g_menu_item_get_link Ptr MenuItem
menuItem' Ptr CChar
link'
    Maybe MenuModel
maybeResult <- Ptr MenuModel
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MenuModel
result ((Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel))
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ \Ptr MenuModel
result' -> do
        MenuModel
result'' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result'
        MenuModel -> IO MenuModel
forall (m :: * -> *) a. Monad m => a -> m a
return MenuModel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
link'
    Maybe MenuModel -> IO (Maybe MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MenuModel
maybeResult

#if defined(ENABLE_OVERLOADING)
data MenuItemGetLinkMethodInfo
instance (signature ~ (T.Text -> m (Maybe Gio.MenuModel.MenuModel)), MonadIO m, IsMenuItem a) => O.OverloadedMethod MenuItemGetLinkMethodInfo a signature where
    overloadedMethod = menuItemGetLink

instance O.OverloadedMethodInfo MenuItemGetLinkMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemGetLink",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemGetLink"
        })


#endif

-- method MenuItem::set_action_and_target_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , 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 for this item"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariant to use as the action target"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_action_and_target_value" g_menu_item_set_action_and_target_value :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    CString ->                              -- action : TBasicType TUTF8
    Ptr GVariant ->                         -- target_value : TVariant
    IO ()

-- | Sets or unsets the \"action\" and \"target\" attributes of /@menuItem@/.
-- 
-- If /@action@/ is 'P.Nothing' then both the \"action\" and \"target\" attributes
-- are unset (and /@targetValue@/ is ignored).
-- 
-- If /@action@/ is non-'P.Nothing' then the \"action\" attribute is set.  The
-- \"target\" attribute is then set to the value of /@targetValue@/ if it is
-- non-'P.Nothing' or unset otherwise.
-- 
-- Normal menu items (ie: not submenu, section or other custom item
-- types) are expected to have the \"action\" attribute set to identify
-- the action that they are associated with.  The state type of the
-- action help to determine the disposition of the menu item.  See
-- t'GI.Gio.Interfaces.Action.Action' and t'GI.Gio.Interfaces.ActionGroup.ActionGroup' for an overview of actions.
-- 
-- In general, clicking on the menu item will result in activation of
-- the named action with the \"target\" attribute given as the parameter
-- to the action invocation.  If the \"target\" attribute is not set then
-- the action is invoked with no parameter.
-- 
-- If the action has no state then the menu item is usually drawn as a
-- plain menu item (ie: with no additional decoration).
-- 
-- If the action has a boolean state then the menu item is usually drawn
-- as a toggle menu item (ie: with a checkmark or equivalent
-- indication).  The item should be marked as \'toggled\' or \'checked\'
-- when the boolean state is 'P.True'.
-- 
-- If the action has a string state then the menu item is usually drawn
-- as a radio menu item (ie: with a radio bullet or equivalent
-- indication).  The item should be marked as \'selected\' when the string
-- state is equal to the value of the /@target@/ property.
-- 
-- See @/g_menu_item_set_action_and_target()/@ or
-- 'GI.Gio.Objects.MenuItem.menuItemSetDetailedAction' for two equivalent calls that are
-- probably more convenient for most uses.
-- 
-- /Since: 2.32/
menuItemSetActionAndTargetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> Maybe (T.Text)
    -- ^ /@action@/: the name of the action for this item
    -> Maybe (GVariant)
    -- ^ /@targetValue@/: a t'GVariant' to use as the action target
    -> m ()
menuItemSetActionAndTargetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuItem a) =>
a -> Maybe Text -> Maybe GVariant -> m ()
menuItemSetActionAndTargetValue a
menuItem Maybe Text
action Maybe GVariant
targetValue = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr CChar
maybeAction <- case Maybe Text
action of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jAction -> do
            Ptr CChar
jAction' <- Text -> IO (Ptr CChar)
textToCString Text
jAction
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jAction'
    Ptr GVariant
maybeTargetValue <- case Maybe GVariant
targetValue of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just GVariant
jTargetValue -> do
            Ptr GVariant
jTargetValue' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jTargetValue
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jTargetValue'
    Ptr MenuItem -> Ptr CChar -> Ptr GVariant -> IO ()
g_menu_item_set_action_and_target_value Ptr MenuItem
menuItem' Ptr CChar
maybeAction Ptr GVariant
maybeTargetValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
targetValue GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeAction
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuItemSetActionAndTargetValueMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (GVariant) -> m ()), MonadIO m, IsMenuItem a) => O.OverloadedMethod MenuItemSetActionAndTargetValueMethodInfo a signature where
    overloadedMethod = menuItemSetActionAndTargetValue

instance O.OverloadedMethodInfo MenuItemSetActionAndTargetValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetActionAndTargetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetActionAndTargetValue"
        })


#endif

-- method MenuItem::set_attribute_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attribute"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariant to use as the value, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_attribute_value" g_menu_item_set_attribute_value :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    CString ->                              -- attribute : TBasicType TUTF8
    Ptr GVariant ->                         -- value : TVariant
    IO ()

-- | Sets or unsets an attribute on /@menuItem@/.
-- 
-- The attribute to set or unset is specified by /@attribute@/. This
-- can be one of the standard attribute names 'GI.Gio.Constants.MENU_ATTRIBUTE_LABEL',
-- 'GI.Gio.Constants.MENU_ATTRIBUTE_ACTION', 'GI.Gio.Constants.MENU_ATTRIBUTE_TARGET', or a custom
-- attribute name.
-- Attribute names are restricted to lowercase characters, numbers
-- and \'-\'. Furthermore, the names must begin with a lowercase character,
-- must not end with a \'-\', and must not contain consecutive dashes.
-- 
-- must consist only of lowercase
-- ASCII characters, digits and \'-\'.
-- 
-- If /@value@/ is non-'P.Nothing' then it is used as the new value for the
-- attribute.  If /@value@/ is 'P.Nothing' then the attribute is unset. If
-- the /@value@/ t'GVariant' is floating, it is consumed.
-- 
-- See also @/g_menu_item_set_attribute()/@ for a more convenient way to do
-- the same.
-- 
-- /Since: 2.32/
menuItemSetAttributeValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> T.Text
    -- ^ /@attribute@/: the attribute to set
    -> Maybe (GVariant)
    -- ^ /@value@/: a t'GVariant' to use as the value, or 'P.Nothing'
    -> m ()
menuItemSetAttributeValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuItem a) =>
a -> Text -> Maybe GVariant -> m ()
menuItemSetAttributeValue a
menuItem Text
attribute Maybe GVariant
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr CChar
attribute' <- Text -> IO (Ptr CChar)
textToCString Text
attribute
    Ptr GVariant
maybeValue <- case Maybe GVariant
value of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just GVariant
jValue -> do
            Ptr GVariant
jValue' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jValue
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jValue'
    Ptr MenuItem -> Ptr CChar -> Ptr GVariant -> IO ()
g_menu_item_set_attribute_value Ptr MenuItem
menuItem' Ptr CChar
attribute' Ptr GVariant
maybeValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
value GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuItemSetAttributeValueMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> m ()), MonadIO m, IsMenuItem a) => O.OverloadedMethod MenuItemSetAttributeValueMethodInfo a signature where
    overloadedMethod = menuItemSetAttributeValue

instance O.OverloadedMethodInfo MenuItemSetAttributeValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetAttributeValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetAttributeValue"
        })


#endif

-- method MenuItem::set_detailed_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detailed_action"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the \"detailed\" action string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_detailed_action" g_menu_item_set_detailed_action :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    CString ->                              -- detailed_action : TBasicType TUTF8
    IO ()

-- | Sets the \"action\" and possibly the \"target\" attribute of /@menuItem@/.
-- 
-- The format of /@detailedAction@/ is the same format parsed by
-- 'GI.Gio.Functions.actionParseDetailedName'.
-- 
-- See @/g_menu_item_set_action_and_target()/@ or
-- 'GI.Gio.Objects.MenuItem.menuItemSetActionAndTargetValue' for more flexible (but
-- slightly less convenient) alternatives.
-- 
-- See also 'GI.Gio.Objects.MenuItem.menuItemSetActionAndTargetValue' for a description of
-- the semantics of the action and target attributes.
-- 
-- /Since: 2.32/
menuItemSetDetailedAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> T.Text
    -- ^ /@detailedAction@/: the \"detailed\" action string
    -> m ()
menuItemSetDetailedAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuItem a) =>
a -> Text -> m ()
menuItemSetDetailedAction a
menuItem Text
detailedAction = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr CChar
detailedAction' <- Text -> IO (Ptr CChar)
textToCString Text
detailedAction
    Ptr MenuItem -> Ptr CChar -> IO ()
g_menu_item_set_detailed_action Ptr MenuItem
menuItem' Ptr CChar
detailedAction'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
detailedAction'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuItemSetDetailedActionMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMenuItem a) => O.OverloadedMethod MenuItemSetDetailedActionMethodInfo a signature where
    overloadedMethod = menuItemSetDetailedAction

instance O.OverloadedMethodInfo MenuItemSetDetailedActionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetDetailedAction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetDetailedAction"
        })


#endif

-- method MenuItem::set_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon, or %NULL" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_icon" g_menu_item_set_icon :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO ()

-- | Sets (or unsets) the icon on /@menuItem@/.
-- 
-- This call is the same as calling 'GI.Gio.Interfaces.Icon.iconSerialize' and using the
-- result as the value to 'GI.Gio.Objects.MenuItem.menuItemSetAttributeValue' for
-- 'GI.Gio.Constants.MENU_ATTRIBUTE_ICON'.
-- 
-- This API is only intended for use with \"noun\" menu items; things like
-- bookmarks or applications in an \"Open With\" menu.  Don\'t use it on
-- menu items corresponding to verbs (eg: stock icons for \'Save\' or
-- \'Quit\').
-- 
-- If /@icon@/ is 'P.Nothing' then the icon is unset.
-- 
-- /Since: 2.38/
menuItemSetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> b
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon', or 'P.Nothing'
    -> m ()
menuItemSetIcon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsMenuItem a, IsIcon b) =>
a -> b -> m ()
menuItemSetIcon a
menuItem b
icon = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    Ptr MenuItem -> Ptr Icon -> IO ()
g_menu_item_set_icon Ptr MenuItem
menuItem' Ptr Icon
icon'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuItemSetIconMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsMenuItem a, Gio.Icon.IsIcon b) => O.OverloadedMethod MenuItemSetIconMethodInfo a signature where
    overloadedMethod = menuItemSetIcon

instance O.OverloadedMethodInfo MenuItemSetIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetIcon"
        })


#endif

-- method MenuItem::set_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the label to set, or %NULL to unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_label" g_menu_item_set_label :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    CString ->                              -- label : TBasicType TUTF8
    IO ()

-- | Sets or unsets the \"label\" attribute of /@menuItem@/.
-- 
-- If /@label@/ is non-'P.Nothing' it is used as the label for the menu item.  If
-- it is 'P.Nothing' then the label attribute is unset.
-- 
-- /Since: 2.32/
menuItemSetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> Maybe (T.Text)
    -- ^ /@label@/: the label to set, or 'P.Nothing' to unset
    -> m ()
menuItemSetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuItem a) =>
a -> Maybe Text -> m ()
menuItemSetLabel a
menuItem Maybe Text
label = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr CChar
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            Ptr CChar
jLabel' <- Text -> IO (Ptr CChar)
textToCString Text
jLabel
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jLabel'
    Ptr MenuItem -> Ptr CChar -> IO ()
g_menu_item_set_label Ptr MenuItem
menuItem' Ptr CChar
maybeLabel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeLabel
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuItemSetLabelMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsMenuItem a) => O.OverloadedMethod MenuItemSetLabelMethodInfo a signature where
    overloadedMethod = menuItemSetLabel

instance O.OverloadedMethodInfo MenuItemSetLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetLabel"
        })


#endif

-- method MenuItem::set_link
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "link"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "type of link to establish or unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GMenuModel to link to (or %NULL to unset)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_link" g_menu_item_set_link :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    CString ->                              -- link : TBasicType TUTF8
    Ptr Gio.MenuModel.MenuModel ->          -- model : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO ()

-- | Creates a link from /@menuItem@/ to /@model@/ if non-'P.Nothing', or unsets it.
-- 
-- Links are used to establish a relationship between a particular menu
-- item and another menu.  For example, 'GI.Gio.Constants.MENU_LINK_SUBMENU' is used to
-- associate a submenu with a particular menu item, and 'GI.Gio.Constants.MENU_LINK_SECTION'
-- is used to create a section. Other types of link can be used, but there
-- is no guarantee that clients will be able to make sense of them.
-- Link types are restricted to lowercase characters, numbers
-- and \'-\'. Furthermore, the names must begin with a lowercase character,
-- must not end with a \'-\', and must not contain consecutive dashes.
-- 
-- /Since: 2.32/
menuItemSetLink ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a, Gio.MenuModel.IsMenuModel b) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> T.Text
    -- ^ /@link@/: type of link to establish or unset
    -> Maybe (b)
    -- ^ /@model@/: the t'GI.Gio.Objects.MenuModel.MenuModel' to link to (or 'P.Nothing' to unset)
    -> m ()
menuItemSetLink :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsMenuItem a, IsMenuModel b) =>
a -> Text -> Maybe b -> m ()
menuItemSetLink a
menuItem Text
link Maybe b
model = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr CChar
link' <- Text -> IO (Ptr CChar)
textToCString Text
link
    Ptr MenuModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr MenuModel
jModel' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jModel'
    Ptr MenuItem -> Ptr CChar -> Ptr MenuModel -> IO ()
g_menu_item_set_link Ptr MenuItem
menuItem' Ptr CChar
link' Ptr MenuModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
link'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuItemSetLinkMethodInfo
instance (signature ~ (T.Text -> Maybe (b) -> m ()), MonadIO m, IsMenuItem a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod MenuItemSetLinkMethodInfo a signature where
    overloadedMethod = menuItemSetLink

instance O.OverloadedMethodInfo MenuItemSetLinkMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetLink",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetLink"
        })


#endif

-- method MenuItem::set_section
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "section"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuModel, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_section" g_menu_item_set_section :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    Ptr Gio.MenuModel.MenuModel ->          -- section : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO ()

-- | Sets or unsets the \"section\" link of /@menuItem@/ to /@section@/.
-- 
-- The effect of having one menu appear as a section of another is
-- exactly as it sounds: the items from /@section@/ become a direct part of
-- the menu that /@menuItem@/ is added to.  See 'GI.Gio.Objects.MenuItem.menuItemNewSection'
-- for more information about what it means for a menu item to be a
-- section.
-- 
-- /Since: 2.32/
menuItemSetSection ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a, Gio.MenuModel.IsMenuModel b) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> Maybe (b)
    -- ^ /@section@/: a t'GI.Gio.Objects.MenuModel.MenuModel', or 'P.Nothing'
    -> m ()
menuItemSetSection :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsMenuItem a, IsMenuModel b) =>
a -> Maybe b -> m ()
menuItemSetSection a
menuItem Maybe b
section = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr MenuModel
maybeSection <- case Maybe b
section of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jSection -> do
            Ptr MenuModel
jSection' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jSection
            Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jSection'
    Ptr MenuItem -> Ptr MenuModel -> IO ()
g_menu_item_set_section Ptr MenuItem
menuItem' Ptr MenuModel
maybeSection
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
section b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo MenuItemSetSectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetSection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetSection"
        })


#endif

-- method MenuItem::set_submenu
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "menu_item"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuItem" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "submenu"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuModel, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_item_set_submenu" g_menu_item_set_submenu :: 
    Ptr MenuItem ->                         -- menu_item : TInterface (Name {namespace = "Gio", name = "MenuItem"})
    Ptr Gio.MenuModel.MenuModel ->          -- submenu : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO ()

-- | Sets or unsets the \"submenu\" link of /@menuItem@/ to /@submenu@/.
-- 
-- If /@submenu@/ is non-'P.Nothing', it is linked to.  If it is 'P.Nothing' then the
-- link is unset.
-- 
-- The effect of having one menu appear as a submenu of another is
-- exactly as it sounds.
-- 
-- /Since: 2.32/
menuItemSetSubmenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuItem a, Gio.MenuModel.IsMenuModel b) =>
    a
    -- ^ /@menuItem@/: a t'GI.Gio.Objects.MenuItem.MenuItem'
    -> Maybe (b)
    -- ^ /@submenu@/: a t'GI.Gio.Objects.MenuModel.MenuModel', or 'P.Nothing'
    -> m ()
menuItemSetSubmenu :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsMenuItem a, IsMenuModel b) =>
a -> Maybe b -> m ()
menuItemSetSubmenu a
menuItem Maybe b
submenu = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuItem
menuItem' <- a -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
menuItem
    Ptr MenuModel
maybeSubmenu <- case Maybe b
submenu of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jSubmenu -> do
            Ptr MenuModel
jSubmenu' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jSubmenu
            Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jSubmenu'
    Ptr MenuItem -> Ptr MenuModel -> IO ()
g_menu_item_set_submenu Ptr MenuItem
menuItem' Ptr MenuModel
maybeSubmenu
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
menuItem
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
submenu b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo MenuItemSetSubmenuMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.MenuItem.menuItemSetSubmenu",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-MenuItem.html#v:menuItemSetSubmenu"
        })


#endif