{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque, stack-allocated struct for iterating
-- over the elements of a @GtkBitset@.
-- 
-- Before a @GtkBitsetIter@ can be used, it needs to be initialized with
-- [func/@gtk@/.BitsetIter.init_first], [func/@gtk@/.BitsetIter.init_last]
-- or [func/@gtk@/.BitsetIter.init_at].

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

module GI.Gtk.Structs.BitsetIter
    ( 

-- * Exported types
    BitsetIter(..)                          ,
    newZeroBitsetIter                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [isValid]("GI.Gtk.Structs.BitsetIter#g:method:isValid"), [next]("GI.Gtk.Structs.BitsetIter#g:method:next"), [previous]("GI.Gtk.Structs.BitsetIter#g:method:previous").
-- 
-- ==== Getters
-- [getValue]("GI.Gtk.Structs.BitsetIter#g:method:getValue").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveBitsetIterMethod                 ,
#endif

-- ** getValue #method:getValue#

#if defined(ENABLE_OVERLOADING)
    BitsetIterGetValueMethodInfo            ,
#endif
    bitsetIterGetValue                      ,


-- ** initAt #method:initAt#

    bitsetIterInitAt                        ,


-- ** initFirst #method:initFirst#

    bitsetIterInitFirst                     ,


-- ** initLast #method:initLast#

    bitsetIterInitLast                      ,


-- ** isValid #method:isValid#

#if defined(ENABLE_OVERLOADING)
    BitsetIterIsValidMethodInfo             ,
#endif
    bitsetIterIsValid                       ,


-- ** next #method:next#

#if defined(ENABLE_OVERLOADING)
    BitsetIterNextMethodInfo                ,
#endif
    bitsetIterNext                          ,


-- ** previous #method:previous#

#if defined(ENABLE_OVERLOADING)
    BitsetIterPreviousMethodInfo            ,
#endif
    bitsetIterPrevious                      ,




    ) where

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

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

import {-# SOURCE #-} qualified GI.Gtk.Structs.Bitset as Gtk.Bitset

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

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

foreign import ccall "gtk_bitset_iter_get_type" c_gtk_bitset_iter_get_type :: 
    IO GType

type instance O.ParentTypes BitsetIter = '[]
instance O.HasParentTypes BitsetIter

instance B.Types.TypedObject BitsetIter where
    glibType :: IO GType
glibType = IO GType
c_gtk_bitset_iter_get_type

instance B.Types.GBoxed BitsetIter

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

-- | Construct a `BitsetIter` struct initialized to zero.
newZeroBitsetIter :: MonadIO m => m BitsetIter
newZeroBitsetIter :: forall (m :: * -> *). MonadIO m => m BitsetIter
newZeroBitsetIter = IO BitsetIter -> m BitsetIter
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BitsetIter -> m BitsetIter) -> IO BitsetIter -> m BitsetIter
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr BitsetIter)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
80 IO (Ptr BitsetIter)
-> (Ptr BitsetIter -> IO BitsetIter) -> IO BitsetIter
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr BitsetIter -> BitsetIter)
-> Ptr BitsetIter -> IO BitsetIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BitsetIter -> BitsetIter
BitsetIter

instance tag ~ 'AttrSet => Constructible BitsetIter tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr BitsetIter -> BitsetIter)
-> [AttrOp BitsetIter tag] -> m BitsetIter
new ManagedPtr BitsetIter -> BitsetIter
_ [AttrOp BitsetIter tag]
attrs = do
        BitsetIter
o <- m BitsetIter
forall (m :: * -> *). MonadIO m => m BitsetIter
newZeroBitsetIter
        BitsetIter -> [AttrOp BitsetIter 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set BitsetIter
o [AttrOp BitsetIter tag]
[AttrOp BitsetIter 'AttrSet]
attrs
        BitsetIter -> m BitsetIter
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return BitsetIter
o



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BitsetIter
type instance O.AttributeList BitsetIter = BitsetIterAttributeList
type BitsetIterAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

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

foreign import ccall "gtk_bitset_iter_get_value" gtk_bitset_iter_get_value :: 
    Ptr BitsetIter ->                       -- iter : TInterface (Name {namespace = "Gtk", name = "BitsetIter"})
    IO Word32

-- | Gets the current value that /@iter@/ points to.
-- 
-- If /@iter@/ is not valid and 'GI.Gtk.Structs.BitsetIter.bitsetIterIsValid'
-- returns 'P.False', this function returns 0.
bitsetIterGetValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BitsetIter
    -- ^ /@iter@/: a @GtkBitsetIter@
    -> m Word32
    -- ^ __Returns:__ The current value pointer to by /@iter@/
bitsetIterGetValue :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BitsetIter -> m Word32
bitsetIterGetValue BitsetIter
iter = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr BitsetIter
iter' <- BitsetIter -> IO (Ptr BitsetIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BitsetIter
iter
    Word32
result <- Ptr BitsetIter -> IO Word32
gtk_bitset_iter_get_value Ptr BitsetIter
iter'
    BitsetIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BitsetIter
iter
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data BitsetIterGetValueMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod BitsetIterGetValueMethodInfo BitsetIter signature where
    overloadedMethod = bitsetIterGetValue

instance O.OverloadedMethodInfo BitsetIterGetValueMethodInfo BitsetIter where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.BitsetIter.bitsetIterGetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Structs-BitsetIter.html#v:bitsetIterGetValue"
        })


#endif

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

foreign import ccall "gtk_bitset_iter_is_valid" gtk_bitset_iter_is_valid :: 
    Ptr BitsetIter ->                       -- iter : TInterface (Name {namespace = "Gtk", name = "BitsetIter"})
    IO CInt

-- | Checks if /@iter@/ points to a valid value.
bitsetIterIsValid ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BitsetIter
    -- ^ /@iter@/: a @GtkBitsetIter@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ points to a valid value
bitsetIterIsValid :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BitsetIter -> m Bool
bitsetIterIsValid BitsetIter
iter = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr BitsetIter
iter' <- BitsetIter -> IO (Ptr BitsetIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BitsetIter
iter
    CInt
result <- Ptr BitsetIter -> IO CInt
gtk_bitset_iter_is_valid Ptr BitsetIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    BitsetIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BitsetIter
iter
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BitsetIterIsValidMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod BitsetIterIsValidMethodInfo BitsetIter signature where
    overloadedMethod = bitsetIterIsValid

instance O.OverloadedMethodInfo BitsetIterIsValidMethodInfo BitsetIter where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.BitsetIter.bitsetIterIsValid",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Structs-BitsetIter.html#v:bitsetIterIsValid"
        })


#endif

-- method BitsetIter::next
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BitsetIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a valid `GtkBitsetIter`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Set to the next 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 "gtk_bitset_iter_next" gtk_bitset_iter_next :: 
    Ptr BitsetIter ->                       -- iter : TInterface (Name {namespace = "Gtk", name = "BitsetIter"})
    Ptr Word32 ->                           -- value : TBasicType TUInt
    IO CInt

-- | Moves /@iter@/ to the next value in the set.
-- 
-- If it was already pointing to the last value in the set,
-- 'P.False' is returned and /@iter@/ is invalidated.
bitsetIterNext ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BitsetIter
    -- ^ /@iter@/: a pointer to a valid @GtkBitsetIter@
    -> m ((Bool, Word32))
    -- ^ __Returns:__ 'P.True' if a next value existed
bitsetIterNext :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BitsetIter -> m (Bool, Word32)
bitsetIterNext BitsetIter
iter = IO (Bool, Word32) -> m (Bool, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Word32) -> m (Bool, Word32))
-> IO (Bool, Word32) -> m (Bool, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BitsetIter
iter' <- BitsetIter -> IO (Ptr BitsetIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BitsetIter
iter
    Ptr Word32
value <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr BitsetIter -> Ptr Word32 -> IO CInt
gtk_bitset_iter_next Ptr BitsetIter
iter' Ptr Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Word32
value' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
value
    BitsetIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BitsetIter
iter
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
value
    (Bool, Word32) -> IO (Bool, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Word32
value')

#if defined(ENABLE_OVERLOADING)
data BitsetIterNextMethodInfo
instance (signature ~ (m ((Bool, Word32))), MonadIO m) => O.OverloadedMethod BitsetIterNextMethodInfo BitsetIter signature where
    overloadedMethod = bitsetIterNext

instance O.OverloadedMethodInfo BitsetIterNextMethodInfo BitsetIter where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.BitsetIter.bitsetIterNext",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Structs-BitsetIter.html#v:bitsetIterNext"
        })


#endif

-- method BitsetIter::previous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BitsetIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a valid `GtkBitsetIter`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Set to the previous 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 "gtk_bitset_iter_previous" gtk_bitset_iter_previous :: 
    Ptr BitsetIter ->                       -- iter : TInterface (Name {namespace = "Gtk", name = "BitsetIter"})
    Ptr Word32 ->                           -- value : TBasicType TUInt
    IO CInt

-- | Moves /@iter@/ to the previous value in the set.
-- 
-- If it was already pointing to the first value in the set,
-- 'P.False' is returned and /@iter@/ is invalidated.
bitsetIterPrevious ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BitsetIter
    -- ^ /@iter@/: a pointer to a valid @GtkBitsetIter@
    -> m ((Bool, Word32))
    -- ^ __Returns:__ 'P.True' if a previous value existed
bitsetIterPrevious :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BitsetIter -> m (Bool, Word32)
bitsetIterPrevious BitsetIter
iter = IO (Bool, Word32) -> m (Bool, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Word32) -> m (Bool, Word32))
-> IO (Bool, Word32) -> m (Bool, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BitsetIter
iter' <- BitsetIter -> IO (Ptr BitsetIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BitsetIter
iter
    Ptr Word32
value <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr BitsetIter -> Ptr Word32 -> IO CInt
gtk_bitset_iter_previous Ptr BitsetIter
iter' Ptr Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Word32
value' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
value
    BitsetIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BitsetIter
iter
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
value
    (Bool, Word32) -> IO (Bool, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Word32
value')

#if defined(ENABLE_OVERLOADING)
data BitsetIterPreviousMethodInfo
instance (signature ~ (m ((Bool, Word32))), MonadIO m) => O.OverloadedMethod BitsetIterPreviousMethodInfo BitsetIter signature where
    overloadedMethod = bitsetIterPrevious

instance O.OverloadedMethodInfo BitsetIterPreviousMethodInfo BitsetIter where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.BitsetIter.bitsetIterPrevious",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Structs-BitsetIter.html#v:bitsetIterPrevious"
        })


#endif

-- method BitsetIter::init_at
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BitsetIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to an uninitialized `GtkBitsetIter`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "set"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBitset`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "target value to start iterating at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Set to the found value in @set"
--                 , 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 "gtk_bitset_iter_init_at" gtk_bitset_iter_init_at :: 
    Ptr BitsetIter ->                       -- iter : TInterface (Name {namespace = "Gtk", name = "BitsetIter"})
    Ptr Gtk.Bitset.Bitset ->                -- set : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- target : TBasicType TUInt
    Ptr Word32 ->                           -- value : TBasicType TUInt
    IO CInt

-- | Initializes /@iter@/ to point to /@target@/.
-- 
-- If /@target@/ is not found, finds the next value after it.
-- If no value >= /@target@/ exists in /@set@/, this function returns 'P.False'.
bitsetIterInitAt ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gtk.Bitset.Bitset
    -- ^ /@set@/: a @GtkBitset@
    -> Word32
    -- ^ /@target@/: target value to start iterating at
    -> m ((Bool, BitsetIter, Word32))
    -- ^ __Returns:__ 'P.True' if a value was found.
bitsetIterInitAt :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> m (Bool, BitsetIter, Word32)
bitsetIterInitAt Bitset
set Word32
target = IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32))
-> IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BitsetIter
iter <- Int -> IO (Ptr BitsetIter)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
80 :: IO (Ptr BitsetIter)
    Ptr Bitset
set' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
set
    Ptr Word32
value <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr BitsetIter -> Ptr Bitset -> Word32 -> Ptr Word32 -> IO CInt
gtk_bitset_iter_init_at Ptr BitsetIter
iter Ptr Bitset
set' Word32
target Ptr Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    BitsetIter
iter' <- ((ManagedPtr BitsetIter -> BitsetIter)
-> Ptr BitsetIter -> IO BitsetIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BitsetIter -> BitsetIter
BitsetIter) Ptr BitsetIter
iter
    Word32
value' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
value
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
set
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
value
    (Bool, BitsetIter, Word32) -> IO (Bool, BitsetIter, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', BitsetIter
iter', Word32
value')

#if defined(ENABLE_OVERLOADING)
#endif

-- method BitsetIter::init_first
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BitsetIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to an uninitialized `GtkBitsetIter`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "set"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBitset`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Set to the first value in @set"
--                 , 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 "gtk_bitset_iter_init_first" gtk_bitset_iter_init_first :: 
    Ptr BitsetIter ->                       -- iter : TInterface (Name {namespace = "Gtk", name = "BitsetIter"})
    Ptr Gtk.Bitset.Bitset ->                -- set : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Ptr Word32 ->                           -- value : TBasicType TUInt
    IO CInt

-- | Initializes an iterator for /@set@/ and points it to the first
-- value in /@set@/.
-- 
-- If /@set@/ is empty, 'P.False' is returned and /@value@/ is set to @/G_MAXUINT/@.
bitsetIterInitFirst ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gtk.Bitset.Bitset
    -- ^ /@set@/: a @GtkBitset@
    -> m ((Bool, BitsetIter, Word32))
    -- ^ __Returns:__ 'P.True' if /@set@/ isn\'t empty.
bitsetIterInitFirst :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> m (Bool, BitsetIter, Word32)
bitsetIterInitFirst Bitset
set = IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32))
-> IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BitsetIter
iter <- Int -> IO (Ptr BitsetIter)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
80 :: IO (Ptr BitsetIter)
    Ptr Bitset
set' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
set
    Ptr Word32
value <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr BitsetIter -> Ptr Bitset -> Ptr Word32 -> IO CInt
gtk_bitset_iter_init_first Ptr BitsetIter
iter Ptr Bitset
set' Ptr Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    BitsetIter
iter' <- ((ManagedPtr BitsetIter -> BitsetIter)
-> Ptr BitsetIter -> IO BitsetIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BitsetIter -> BitsetIter
BitsetIter) Ptr BitsetIter
iter
    Word32
value' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
value
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
set
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
value
    (Bool, BitsetIter, Word32) -> IO (Bool, BitsetIter, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', BitsetIter
iter', Word32
value')

#if defined(ENABLE_OVERLOADING)
#endif

-- method BitsetIter::init_last
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BitsetIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to an uninitialized `GtkBitsetIter`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "set"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBitset`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Set to the last value in @set"
--                 , 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 "gtk_bitset_iter_init_last" gtk_bitset_iter_init_last :: 
    Ptr BitsetIter ->                       -- iter : TInterface (Name {namespace = "Gtk", name = "BitsetIter"})
    Ptr Gtk.Bitset.Bitset ->                -- set : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Ptr Word32 ->                           -- value : TBasicType TUInt
    IO CInt

-- | Initializes an iterator for /@set@/ and points it to the last
-- value in /@set@/.
-- 
-- If /@set@/ is empty, 'P.False' is returned.
bitsetIterInitLast ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gtk.Bitset.Bitset
    -- ^ /@set@/: a @GtkBitset@
    -> m ((Bool, BitsetIter, Word32))
    -- ^ __Returns:__ 'P.True' if /@set@/ isn\'t empty.
bitsetIterInitLast :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> m (Bool, BitsetIter, Word32)
bitsetIterInitLast Bitset
set = IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32))
-> IO (Bool, BitsetIter, Word32) -> m (Bool, BitsetIter, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BitsetIter
iter <- Int -> IO (Ptr BitsetIter)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
80 :: IO (Ptr BitsetIter)
    Ptr Bitset
set' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
set
    Ptr Word32
value <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr BitsetIter -> Ptr Bitset -> Ptr Word32 -> IO CInt
gtk_bitset_iter_init_last Ptr BitsetIter
iter Ptr Bitset
set' Ptr Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    BitsetIter
iter' <- ((ManagedPtr BitsetIter -> BitsetIter)
-> Ptr BitsetIter -> IO BitsetIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BitsetIter -> BitsetIter
BitsetIter) Ptr BitsetIter
iter
    Word32
value' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
value
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
set
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
value
    (Bool, BitsetIter, Word32) -> IO (Bool, BitsetIter, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', BitsetIter
iter', Word32
value')

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveBitsetIterMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveBitsetIterMethod "isValid" o = BitsetIterIsValidMethodInfo
    ResolveBitsetIterMethod "next" o = BitsetIterNextMethodInfo
    ResolveBitsetIterMethod "previous" o = BitsetIterPreviousMethodInfo
    ResolveBitsetIterMethod "getValue" o = BitsetIterGetValueMethodInfo
    ResolveBitsetIterMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif