{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.MenuAttributeIter.MenuAttributeIter' 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.MenuAttributeIter
    ( 

-- * Exported types
    MenuAttributeIter(..)                   ,
    IsMenuAttributeIter                     ,
    toMenuAttributeIter                     ,


 -- * 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"), [next]("GI.Gio.Objects.MenuAttributeIter#g:method:next"), [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
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getName]("GI.Gio.Objects.MenuAttributeIter#g:method:getName"), [getNext]("GI.Gio.Objects.MenuAttributeIter#g:method:getNext"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getValue]("GI.Gio.Objects.MenuAttributeIter#g:method:getValue").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveMenuAttributeIterMethod          ,
#endif

-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    MenuAttributeIterGetNameMethodInfo      ,
#endif
    menuAttributeIterGetName                ,


-- ** getNext #method:getNext#

#if defined(ENABLE_OVERLOADING)
    MenuAttributeIterGetNextMethodInfo      ,
#endif
    menuAttributeIterGetNext                ,


-- ** getValue #method:getValue#

#if defined(ENABLE_OVERLOADING)
    MenuAttributeIterGetValueMethodInfo     ,
#endif
    menuAttributeIterGetValue               ,


-- ** next #method:next#

#if defined(ENABLE_OVERLOADING)
    MenuAttributeIterNextMethodInfo         ,
#endif
    menuAttributeIterNext                   ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "g_menu_attribute_iter_get_type"
    c_g_menu_attribute_iter_get_type :: IO B.Types.GType

instance B.Types.TypedObject MenuAttributeIter where
    glibType :: IO GType
glibType = IO GType
c_g_menu_attribute_iter_get_type

instance B.Types.GObject MenuAttributeIter

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveMenuAttributeIterMethod (t :: Symbol) (o :: *) :: * where
    ResolveMenuAttributeIterMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveMenuAttributeIterMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveMenuAttributeIterMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveMenuAttributeIterMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveMenuAttributeIterMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveMenuAttributeIterMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveMenuAttributeIterMethod "next" o = MenuAttributeIterNextMethodInfo
    ResolveMenuAttributeIterMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveMenuAttributeIterMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveMenuAttributeIterMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveMenuAttributeIterMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveMenuAttributeIterMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveMenuAttributeIterMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveMenuAttributeIterMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveMenuAttributeIterMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveMenuAttributeIterMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveMenuAttributeIterMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveMenuAttributeIterMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveMenuAttributeIterMethod "getName" o = MenuAttributeIterGetNameMethodInfo
    ResolveMenuAttributeIterMethod "getNext" o = MenuAttributeIterGetNextMethodInfo
    ResolveMenuAttributeIterMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveMenuAttributeIterMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveMenuAttributeIterMethod "getValue" o = MenuAttributeIterGetValueMethodInfo
    ResolveMenuAttributeIterMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveMenuAttributeIterMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveMenuAttributeIterMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveMenuAttributeIterMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method MenuAttributeIter::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuAttributeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuAttributeIter"
--                 , 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 "g_menu_attribute_iter_get_name" g_menu_attribute_iter_get_name :: 
    Ptr MenuAttributeIter ->                -- iter : TInterface (Name {namespace = "Gio", name = "MenuAttributeIter"})
    IO CString

-- | Gets the name of the attribute at the current iterator position, as
-- a string.
-- 
-- The iterator is not advanced.
-- 
-- /Since: 2.32/
menuAttributeIterGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
    a
    -- ^ /@iter@/: a t'GI.Gio.Objects.MenuAttributeIter.MenuAttributeIter'
    -> m T.Text
    -- ^ __Returns:__ the name of the attribute
menuAttributeIterGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
a -> m Text
menuAttributeIterGetName a
iter = IO Text -> m Text
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 MenuAttributeIter
iter' <- a -> IO (Ptr MenuAttributeIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
    CString
result <- Ptr MenuAttributeIter -> IO CString
g_menu_attribute_iter_get_name Ptr MenuAttributeIter
iter'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuAttributeIterGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MenuAttributeIterGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMenuAttributeIter a) => O.OverloadedMethod MenuAttributeIterGetNameMethodInfo a signature where
    overloadedMethod = menuAttributeIterGetName

instance O.OverloadedMethodInfo MenuAttributeIterGetNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MenuAttributeIter.menuAttributeIterGetName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MenuAttributeIter.html#v:menuAttributeIterGetName"
        }


#endif

-- method MenuAttributeIter::get_next
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuAttributeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuAttributeIter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the type of the attribute"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_menu_attribute_iter_get_next" g_menu_attribute_iter_get_next :: 
    Ptr MenuAttributeIter ->                -- iter : TInterface (Name {namespace = "Gio", name = "MenuAttributeIter"})
    Ptr CString ->                          -- out_name : TBasicType TUTF8
    Ptr (Ptr GVariant) ->                   -- value : TVariant
    IO CInt

-- | This function combines 'GI.Gio.Objects.MenuAttributeIter.menuAttributeIterNext' with
-- 'GI.Gio.Objects.MenuAttributeIter.menuAttributeIterGetName' and 'GI.Gio.Objects.MenuAttributeIter.menuAttributeIterGetValue'.
-- 
-- First the iterator is advanced to the next (possibly first) attribute.
-- If that fails, then 'P.False' is returned and there are no other
-- effects.
-- 
-- If successful, /@name@/ and /@value@/ are set to the name and value of the
-- attribute that has just been advanced to.  At this point,
-- 'GI.Gio.Objects.MenuAttributeIter.menuAttributeIterGetName' and 'GI.Gio.Objects.MenuAttributeIter.menuAttributeIterGetValue' will
-- return the same values again.
-- 
-- The value returned in /@name@/ remains valid for as long as the iterator
-- remains at the current position.  The value returned in /@value@/ must
-- be unreffed using 'GI.GLib.Structs.Variant.variantUnref' when it is no longer in use.
-- 
-- /Since: 2.32/
menuAttributeIterGetNext ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
    a
    -- ^ /@iter@/: a t'GI.Gio.Objects.MenuAttributeIter.MenuAttributeIter'
    -> m ((Bool, T.Text, GVariant))
    -- ^ __Returns:__ 'P.True' on success, or 'P.False' if there is no additional
    --     attribute
menuAttributeIterGetNext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
a -> m (Bool, Text, GVariant)
menuAttributeIterGetNext a
iter = IO (Bool, Text, GVariant) -> m (Bool, Text, GVariant)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Text, GVariant) -> m (Bool, Text, GVariant))
-> IO (Bool, Text, GVariant) -> m (Bool, Text, GVariant)
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuAttributeIter
iter' <- a -> IO (Ptr MenuAttributeIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
    Ptr CString
outName <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    Ptr (Ptr GVariant)
value <- IO (Ptr (Ptr GVariant))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr GVariant))
    CInt
result <- Ptr MenuAttributeIter
-> Ptr CString -> Ptr (Ptr GVariant) -> IO CInt
g_menu_attribute_iter_get_next Ptr MenuAttributeIter
iter' Ptr CString
outName Ptr (Ptr GVariant)
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    CString
outName' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
outName
    Text
outName'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
outName'
    Ptr GVariant
value' <- Ptr (Ptr GVariant) -> IO (Ptr GVariant)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr GVariant)
value
    GVariant
value'' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
outName
    Ptr (Ptr GVariant) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr GVariant)
value
    (Bool, Text, GVariant) -> IO (Bool, Text, GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Text
outName'', GVariant
value'')

#if defined(ENABLE_OVERLOADING)
data MenuAttributeIterGetNextMethodInfo
instance (signature ~ (m ((Bool, T.Text, GVariant))), MonadIO m, IsMenuAttributeIter a) => O.OverloadedMethod MenuAttributeIterGetNextMethodInfo a signature where
    overloadedMethod = menuAttributeIterGetNext

instance O.OverloadedMethodInfo MenuAttributeIterGetNextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MenuAttributeIter.menuAttributeIterGetNext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MenuAttributeIter.html#v:menuAttributeIterGetNext"
        }


#endif

-- method MenuAttributeIter::get_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuAttributeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuAttributeIter"
--                 , 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_attribute_iter_get_value" g_menu_attribute_iter_get_value :: 
    Ptr MenuAttributeIter ->                -- iter : TInterface (Name {namespace = "Gio", name = "MenuAttributeIter"})
    IO (Ptr GVariant)

-- | Gets the value of the attribute at the current iterator position.
-- 
-- The iterator is not advanced.
-- 
-- /Since: 2.32/
menuAttributeIterGetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
    a
    -- ^ /@iter@/: a t'GI.Gio.Objects.MenuAttributeIter.MenuAttributeIter'
    -> m GVariant
    -- ^ __Returns:__ the value of the current attribute
menuAttributeIterGetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
a -> m GVariant
menuAttributeIterGetValue a
iter = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuAttributeIter
iter' <- a -> IO (Ptr MenuAttributeIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
    Ptr GVariant
result <- Ptr MenuAttributeIter -> IO (Ptr GVariant)
g_menu_attribute_iter_get_value Ptr MenuAttributeIter
iter'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuAttributeIterGetValue" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iter
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data MenuAttributeIterGetValueMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsMenuAttributeIter a) => O.OverloadedMethod MenuAttributeIterGetValueMethodInfo a signature where
    overloadedMethod = menuAttributeIterGetValue

instance O.OverloadedMethodInfo MenuAttributeIterGetValueMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MenuAttributeIter.menuAttributeIterGetValue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MenuAttributeIter.html#v:menuAttributeIterGetValue"
        }


#endif

-- method MenuAttributeIter::next
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuAttributeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuAttributeIter"
--                 , 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 "g_menu_attribute_iter_next" g_menu_attribute_iter_next :: 
    Ptr MenuAttributeIter ->                -- iter : TInterface (Name {namespace = "Gio", name = "MenuAttributeIter"})
    IO CInt

-- | Attempts to advance the iterator to the next (possibly first)
-- attribute.
-- 
-- 'P.True' is returned on success, or 'P.False' if there are no more
-- attributes.
-- 
-- You must call this function when you first acquire the iterator
-- to advance it to the first attribute (and determine if the first
-- attribute exists at all).
-- 
-- /Since: 2.32/
menuAttributeIterNext ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
    a
    -- ^ /@iter@/: a t'GI.Gio.Objects.MenuAttributeIter.MenuAttributeIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' on success, or 'P.False' when there are no more attributes
menuAttributeIterNext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuAttributeIter a) =>
a -> m Bool
menuAttributeIterNext a
iter = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr MenuAttributeIter
iter' <- a -> IO (Ptr MenuAttributeIter)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iter
    CInt
result <- Ptr MenuAttributeIter -> IO CInt
g_menu_attribute_iter_next Ptr MenuAttributeIter
iter'
    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
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuAttributeIterNextMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMenuAttributeIter a) => O.OverloadedMethod MenuAttributeIterNextMethodInfo a signature where
    overloadedMethod = menuAttributeIterNext

instance O.OverloadedMethodInfo MenuAttributeIterNextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MenuAttributeIter.menuAttributeIterNext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MenuAttributeIter.html#v:menuAttributeIterNext"
        }


#endif