{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkBitset@ represents a set of unsigned integers.
-- 
-- Another name for this data structure is \"bitmap\".
-- 
-- The current implementation is based on <https://roaringbitmap.org/ roaring bitmaps>.
-- 
-- A bitset allows adding a set of integers and provides support for set operations
-- like unions, intersections and checks for equality or if a value is contained
-- in the set. @GtkBitset@ also contains various functions to query metadata about
-- the bitset, such as the minimum or maximum values or its size.
-- 
-- The fastest way to iterate values in a bitset is [struct/@gtk@/.BitsetIter].
-- 
-- The main use case for @GtkBitset@ is implementing complex selections for
-- t'GI.Gtk.Interfaces.SelectionModel.SelectionModel'.

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

module GI.Gtk.Structs.Bitset
    ( 

-- * Exported types
    Bitset(..)                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [add]("GI.Gtk.Structs.Bitset#g:method:add"), [addRange]("GI.Gtk.Structs.Bitset#g:method:addRange"), [addRangeClosed]("GI.Gtk.Structs.Bitset#g:method:addRangeClosed"), [addRectangle]("GI.Gtk.Structs.Bitset#g:method:addRectangle"), [contains]("GI.Gtk.Structs.Bitset#g:method:contains"), [copy]("GI.Gtk.Structs.Bitset#g:method:copy"), [difference]("GI.Gtk.Structs.Bitset#g:method:difference"), [equals]("GI.Gtk.Structs.Bitset#g:method:equals"), [intersect]("GI.Gtk.Structs.Bitset#g:method:intersect"), [isEmpty]("GI.Gtk.Structs.Bitset#g:method:isEmpty"), [ref]("GI.Gtk.Structs.Bitset#g:method:ref"), [remove]("GI.Gtk.Structs.Bitset#g:method:remove"), [removeAll]("GI.Gtk.Structs.Bitset#g:method:removeAll"), [removeRange]("GI.Gtk.Structs.Bitset#g:method:removeRange"), [removeRangeClosed]("GI.Gtk.Structs.Bitset#g:method:removeRangeClosed"), [removeRectangle]("GI.Gtk.Structs.Bitset#g:method:removeRectangle"), [shiftLeft]("GI.Gtk.Structs.Bitset#g:method:shiftLeft"), [shiftRight]("GI.Gtk.Structs.Bitset#g:method:shiftRight"), [splice]("GI.Gtk.Structs.Bitset#g:method:splice"), [subtract]("GI.Gtk.Structs.Bitset#g:method:subtract"), [union]("GI.Gtk.Structs.Bitset#g:method:union"), [unref]("GI.Gtk.Structs.Bitset#g:method:unref").
-- 
-- ==== Getters
-- [getMaximum]("GI.Gtk.Structs.Bitset#g:method:getMaximum"), [getMinimum]("GI.Gtk.Structs.Bitset#g:method:getMinimum"), [getNth]("GI.Gtk.Structs.Bitset#g:method:getNth"), [getSize]("GI.Gtk.Structs.Bitset#g:method:getSize"), [getSizeInRange]("GI.Gtk.Structs.Bitset#g:method:getSizeInRange").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveBitsetMethod                     ,
#endif

-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    BitsetAddMethodInfo                     ,
#endif
    bitsetAdd                               ,


-- ** addRange #method:addRange#

#if defined(ENABLE_OVERLOADING)
    BitsetAddRangeMethodInfo                ,
#endif
    bitsetAddRange                          ,


-- ** addRangeClosed #method:addRangeClosed#

#if defined(ENABLE_OVERLOADING)
    BitsetAddRangeClosedMethodInfo          ,
#endif
    bitsetAddRangeClosed                    ,


-- ** addRectangle #method:addRectangle#

#if defined(ENABLE_OVERLOADING)
    BitsetAddRectangleMethodInfo            ,
#endif
    bitsetAddRectangle                      ,


-- ** contains #method:contains#

#if defined(ENABLE_OVERLOADING)
    BitsetContainsMethodInfo                ,
#endif
    bitsetContains                          ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    BitsetCopyMethodInfo                    ,
#endif
    bitsetCopy                              ,


-- ** difference #method:difference#

#if defined(ENABLE_OVERLOADING)
    BitsetDifferenceMethodInfo              ,
#endif
    bitsetDifference                        ,


-- ** equals #method:equals#

#if defined(ENABLE_OVERLOADING)
    BitsetEqualsMethodInfo                  ,
#endif
    bitsetEquals                            ,


-- ** getMaximum #method:getMaximum#

#if defined(ENABLE_OVERLOADING)
    BitsetGetMaximumMethodInfo              ,
#endif
    bitsetGetMaximum                        ,


-- ** getMinimum #method:getMinimum#

#if defined(ENABLE_OVERLOADING)
    BitsetGetMinimumMethodInfo              ,
#endif
    bitsetGetMinimum                        ,


-- ** getNth #method:getNth#

#if defined(ENABLE_OVERLOADING)
    BitsetGetNthMethodInfo                  ,
#endif
    bitsetGetNth                            ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    BitsetGetSizeMethodInfo                 ,
#endif
    bitsetGetSize                           ,


-- ** getSizeInRange #method:getSizeInRange#

#if defined(ENABLE_OVERLOADING)
    BitsetGetSizeInRangeMethodInfo          ,
#endif
    bitsetGetSizeInRange                    ,


-- ** intersect #method:intersect#

#if defined(ENABLE_OVERLOADING)
    BitsetIntersectMethodInfo               ,
#endif
    bitsetIntersect                         ,


-- ** isEmpty #method:isEmpty#

#if defined(ENABLE_OVERLOADING)
    BitsetIsEmptyMethodInfo                 ,
#endif
    bitsetIsEmpty                           ,


-- ** newEmpty #method:newEmpty#

    bitsetNewEmpty                          ,


-- ** newRange #method:newRange#

    bitsetNewRange                          ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    BitsetRefMethodInfo                     ,
#endif
    bitsetRef                               ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    BitsetRemoveMethodInfo                  ,
#endif
    bitsetRemove                            ,


-- ** removeAll #method:removeAll#

#if defined(ENABLE_OVERLOADING)
    BitsetRemoveAllMethodInfo               ,
#endif
    bitsetRemoveAll                         ,


-- ** removeRange #method:removeRange#

#if defined(ENABLE_OVERLOADING)
    BitsetRemoveRangeMethodInfo             ,
#endif
    bitsetRemoveRange                       ,


-- ** removeRangeClosed #method:removeRangeClosed#

#if defined(ENABLE_OVERLOADING)
    BitsetRemoveRangeClosedMethodInfo       ,
#endif
    bitsetRemoveRangeClosed                 ,


-- ** removeRectangle #method:removeRectangle#

#if defined(ENABLE_OVERLOADING)
    BitsetRemoveRectangleMethodInfo         ,
#endif
    bitsetRemoveRectangle                   ,


-- ** shiftLeft #method:shiftLeft#

#if defined(ENABLE_OVERLOADING)
    BitsetShiftLeftMethodInfo               ,
#endif
    bitsetShiftLeft                         ,


-- ** shiftRight #method:shiftRight#

#if defined(ENABLE_OVERLOADING)
    BitsetShiftRightMethodInfo              ,
#endif
    bitsetShiftRight                        ,


-- ** splice #method:splice#

#if defined(ENABLE_OVERLOADING)
    BitsetSpliceMethodInfo                  ,
#endif
    bitsetSplice                            ,


-- ** subtract #method:subtract#

#if defined(ENABLE_OVERLOADING)
    BitsetSubtractMethodInfo                ,
#endif
    bitsetSubtract                          ,


-- ** union #method:union#

#if defined(ENABLE_OVERLOADING)
    BitsetUnionMethodInfo                   ,
#endif
    bitsetUnion                             ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    BitsetUnrefMethodInfo                   ,
#endif
    bitsetUnref                             ,




    ) 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


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

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

foreign import ccall "gtk_bitset_get_type" c_gtk_bitset_get_type :: 
    IO GType

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

instance B.Types.TypedObject Bitset where
    glibType :: IO GType
glibType = IO GType
c_gtk_bitset_get_type

instance B.Types.GBoxed Bitset

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


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

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

foreign import ccall "gtk_bitset_new_empty" gtk_bitset_new_empty :: 
    IO (Ptr Bitset)

-- | Creates a new empty bitset.
bitsetNewEmpty ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Bitset
    -- ^ __Returns:__ A new empty bitset
bitsetNewEmpty :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Bitset
bitsetNewEmpty  = IO Bitset -> m Bitset
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bitset -> m Bitset) -> IO Bitset -> m Bitset
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
result <- IO (Ptr Bitset)
gtk_bitset_new_empty
    Text -> Ptr Bitset -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bitsetNewEmpty" Ptr Bitset
result
    Bitset
result' <- ((ManagedPtr Bitset -> Bitset) -> Ptr Bitset -> IO Bitset
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bitset -> Bitset
Bitset) Ptr Bitset
result
    Bitset -> IO Bitset
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bitset
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Bitset::new_range
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "start"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first value to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_items"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of consecutive values to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Bitset" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_new_range" gtk_bitset_new_range :: 
    Word32 ->                               -- start : TBasicType TUInt
    Word32 ->                               -- n_items : TBasicType TUInt
    IO (Ptr Bitset)

-- | Creates a bitset with the given range set.
bitsetNewRange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word32
    -- ^ /@start@/: first value to add
    -> Word32
    -- ^ /@nItems@/: number of consecutive values to add
    -> m Bitset
    -- ^ __Returns:__ A new bitset
bitsetNewRange :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word32 -> Word32 -> m Bitset
bitsetNewRange Word32
start Word32
nItems = IO Bitset -> m Bitset
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bitset -> m Bitset) -> IO Bitset -> m Bitset
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
result <- Word32 -> Word32 -> IO (Ptr Bitset)
gtk_bitset_new_range Word32
start Word32
nItems
    Text -> Ptr Bitset -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bitsetNewRange" Ptr Bitset
result
    Bitset
result' <- ((ManagedPtr Bitset -> Bitset) -> Ptr Bitset -> IO Bitset
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bitset -> Bitset
Bitset) Ptr Bitset
result
    Bitset -> IO Bitset
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bitset
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Bitset::add
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "value to add" , 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_add" gtk_bitset_add :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- value : TBasicType TUInt
    IO CInt

-- | Adds /@value@/ to /@self@/ if it wasn\'t part of it before.
bitsetAdd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@value@/: value to add
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@value@/ was not part of /@self@/ and /@self@/
    --   was changed
bitsetAdd :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> m Bool
bitsetAdd Bitset
self Word32
value = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    CInt
result <- Ptr Bitset -> Word32 -> IO CInt
gtk_bitset_add Ptr Bitset
self' Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BitsetAddMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.OverloadedMethod BitsetAddMethodInfo Bitset signature where
    overloadedMethod = bitsetAdd

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


#endif

-- method Bitset::add_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "start"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first value to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_items"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of consecutive values to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_add_range" gtk_bitset_add_range :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- start : TBasicType TUInt
    Word32 ->                               -- n_items : TBasicType TUInt
    IO ()

-- | Adds all values from /@start@/ (inclusive) to /@start@/ + /@nItems@/
-- (exclusive) in /@self@/.
bitsetAddRange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@start@/: first value to add
    -> Word32
    -- ^ /@nItems@/: number of consecutive values to add
    -> m ()
bitsetAddRange :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> m ()
bitsetAddRange Bitset
self Word32
start Word32
nItems = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> Word32 -> IO ()
gtk_bitset_add_range Ptr Bitset
self' Word32
start Word32
nItems
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetAddRangeMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetAddRangeMethodInfo Bitset signature where
    overloadedMethod = bitsetAddRange

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


#endif

-- method Bitset::add_range_closed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "first"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first value to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "last"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "last value to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_add_range_closed" gtk_bitset_add_range_closed :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- first : TBasicType TUInt
    Word32 ->                               -- last : TBasicType TUInt
    IO ()

-- | Adds the closed range [/@first@/, /@last@/], so /@first@/, /@last@/ and all
-- values in between. /@first@/ must be smaller than /@last@/.
bitsetAddRangeClosed ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@first@/: first value to add
    -> Word32
    -- ^ /@last@/: last value to add
    -> m ()
bitsetAddRangeClosed :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> m ()
bitsetAddRangeClosed Bitset
self Word32
first Word32
last = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> Word32 -> IO ()
gtk_bitset_add_range_closed Ptr Bitset
self' Word32
first Word32
last
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetAddRangeClosedMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetAddRangeClosedMethodInfo Bitset signature where
    overloadedMethod = bitsetAddRangeClosed

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


#endif

-- method Bitset::add_rectangle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "start"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first value to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width of the rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height of the rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stride"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "row stride of the grid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_add_rectangle" gtk_bitset_add_rectangle :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- start : TBasicType TUInt
    Word32 ->                               -- width : TBasicType TUInt
    Word32 ->                               -- height : TBasicType TUInt
    Word32 ->                               -- stride : TBasicType TUInt
    IO ()

-- | Interprets the values as a 2-dimensional boolean grid with the given /@stride@/
-- and inside that grid, adds a rectangle with the given /@width@/ and /@height@/.
bitsetAddRectangle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@start@/: first value to add
    -> Word32
    -- ^ /@width@/: width of the rectangle
    -> Word32
    -- ^ /@height@/: height of the rectangle
    -> Word32
    -- ^ /@stride@/: row stride of the grid
    -> m ()
bitsetAddRectangle :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> Word32 -> Word32 -> m ()
bitsetAddRectangle Bitset
self Word32
start Word32
width Word32
height Word32
stride = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> Word32 -> Word32 -> Word32 -> IO ()
gtk_bitset_add_rectangle Ptr Bitset
self' Word32
start Word32
width Word32
height Word32
stride
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetAddRectangleMethodInfo
instance (signature ~ (Word32 -> Word32 -> Word32 -> Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetAddRectangleMethodInfo Bitset signature where
    overloadedMethod = bitsetAddRectangle

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


#endif

-- method Bitset::contains
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value to check" , 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_contains" gtk_bitset_contains :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- value : TBasicType TUInt
    IO CInt

-- | Checks if the given /@value@/ has been added to /@self@/
bitsetContains ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@value@/: the value to check
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@self@/ contains /@value@/
bitsetContains :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> m Bool
bitsetContains Bitset
self Word32
value = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    CInt
result <- Ptr Bitset -> Word32 -> IO CInt
gtk_bitset_contains Ptr Bitset
self' Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BitsetContainsMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.OverloadedMethod BitsetContainsMethodInfo Bitset signature where
    overloadedMethod = bitsetContains

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


#endif

-- method Bitset::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Bitset" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_copy" gtk_bitset_copy :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO (Ptr Bitset)

-- | Creates a copy of /@self@/.
bitsetCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m Bitset
    -- ^ __Returns:__ A new bitset that contains the same
    --   values as /@self@/
bitsetCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> m Bitset
bitsetCopy Bitset
self = IO Bitset -> m Bitset
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bitset -> m Bitset) -> IO Bitset -> m Bitset
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset
result <- Ptr Bitset -> IO (Ptr Bitset)
gtk_bitset_copy Ptr Bitset
self'
    Text -> Ptr Bitset -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bitsetCopy" Ptr Bitset
result
    Bitset
result' <- ((ManagedPtr Bitset -> Bitset) -> Ptr Bitset -> IO Bitset
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bitset -> Bitset
Bitset) Ptr Bitset
result
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bitset -> IO Bitset
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bitset
result'

#if defined(ENABLE_OVERLOADING)
data BitsetCopyMethodInfo
instance (signature ~ (m Bitset), MonadIO m) => O.OverloadedMethod BitsetCopyMethodInfo Bitset signature where
    overloadedMethod = bitsetCopy

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


#endif

-- method Bitset::difference
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "other"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the `GtkBitset` to compute the difference from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_difference" gtk_bitset_difference :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Ptr Bitset ->                           -- other : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO ()

-- | Sets /@self@/ to be the symmetric difference of /@self@/ and /@other@/.
-- 
-- The symmetric difference is set /@self@/ to contain all values that
-- were either contained in /@self@/ or in /@other@/, but not in both.
-- This operation is also called an XOR.
-- 
-- It is allowed for /@self@/ and /@other@/ to be the same bitset. The bitset
-- will be emptied in that case.
bitsetDifference ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Bitset
    -- ^ /@other@/: the @GtkBitset@ to compute the difference from
    -> m ()
bitsetDifference :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Bitset -> m ()
bitsetDifference Bitset
self Bitset
other = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset
other' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
other
    Ptr Bitset -> Ptr Bitset -> IO ()
gtk_bitset_difference Ptr Bitset
self' Ptr Bitset
other'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
other
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetDifferenceMethodInfo
instance (signature ~ (Bitset -> m ()), MonadIO m) => O.OverloadedMethod BitsetDifferenceMethodInfo Bitset signature where
    overloadedMethod = bitsetDifference

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


#endif

-- method Bitset::equals
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "other"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another `GtkBitset`"
--                 , 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_equals" gtk_bitset_equals :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Ptr Bitset ->                           -- other : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO CInt

-- | Returns 'P.True' if /@self@/ and /@other@/ contain the same values.
bitsetEquals ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Bitset
    -- ^ /@other@/: another @GtkBitset@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@self@/ and /@other@/ contain the same values
bitsetEquals :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Bitset -> m Bool
bitsetEquals Bitset
self Bitset
other = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset
other' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
other
    CInt
result <- Ptr Bitset -> Ptr Bitset -> IO CInt
gtk_bitset_equals Ptr Bitset
self' Ptr Bitset
other'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
other
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BitsetEqualsMethodInfo
instance (signature ~ (Bitset -> m Bool), MonadIO m) => O.OverloadedMethod BitsetEqualsMethodInfo Bitset signature where
    overloadedMethod = bitsetEquals

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


#endif

-- method Bitset::get_maximum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_get_maximum" gtk_bitset_get_maximum :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO Word32

-- | Returns the largest value in /@self@/.
-- 
-- If /@self@/ is empty, 0 is returned.
bitsetGetMaximum ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m Word32
    -- ^ __Returns:__ The largest value in /@self@/
bitsetGetMaximum :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> m Word32
bitsetGetMaximum Bitset
self = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Word32
result <- Ptr Bitset -> IO Word32
gtk_bitset_get_maximum Ptr Bitset
self'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data BitsetGetMaximumMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod BitsetGetMaximumMethodInfo Bitset signature where
    overloadedMethod = bitsetGetMaximum

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


#endif

-- method Bitset::get_minimum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_get_minimum" gtk_bitset_get_minimum :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO Word32

-- | Returns the smallest value in /@self@/.
-- 
-- If /@self@/ is empty, @G_MAXUINT@ is returned.
bitsetGetMinimum ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m Word32
    -- ^ __Returns:__ The smallest value in /@self@/
bitsetGetMinimum :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> m Word32
bitsetGetMinimum Bitset
self = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Word32
result <- Ptr Bitset -> IO Word32
gtk_bitset_get_minimum Ptr Bitset
self'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data BitsetGetMinimumMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod BitsetGetMinimumMethodInfo Bitset signature where
    overloadedMethod = bitsetGetMinimum

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


#endif

-- method Bitset::get_nth
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "nth"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "index of the item to get"
--                 , 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_get_nth" gtk_bitset_get_nth :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- nth : TBasicType TUInt
    IO Word32

-- | Returns the value of the /@nth@/ item in self.
-- 
-- If /@nth@/ is >= the size of /@self@/, 0 is returned.
bitsetGetNth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@nth@/: index of the item to get
    -> m Word32
    -- ^ __Returns:__ the value of the /@nth@/ item in /@self@/
bitsetGetNth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> m Word32
bitsetGetNth Bitset
self Word32
nth = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Word32
result <- Ptr Bitset -> Word32 -> IO Word32
gtk_bitset_get_nth Ptr Bitset
self' Word32
nth
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data BitsetGetNthMethodInfo
instance (signature ~ (Word32 -> m Word32), MonadIO m) => O.OverloadedMethod BitsetGetNthMethodInfo Bitset signature where
    overloadedMethod = bitsetGetNth

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


#endif

-- method Bitset::get_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_get_size" gtk_bitset_get_size :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO Word64

-- | Gets the number of values that were added to the set.
-- 
-- For example, if the set is empty, 0 is returned.
-- 
-- Note that this function returns a @guint64@, because when all
-- values are set, the return value is @G_MAXUINT + 1@. Unless you
-- are sure this cannot happen (it can\'t with @GListModel@), be sure
-- to use a 64bit type.
bitsetGetSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m Word64
    -- ^ __Returns:__ The number of values in the set.
bitsetGetSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> m Word64
bitsetGetSize Bitset
self = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Word64
result <- Ptr Bitset -> IO Word64
gtk_bitset_get_size Ptr Bitset
self'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data BitsetGetSizeMethodInfo
instance (signature ~ (m Word64), MonadIO m) => O.OverloadedMethod BitsetGetSizeMethodInfo Bitset signature where
    overloadedMethod = bitsetGetSize

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


#endif

-- method Bitset::get_size_in_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "first"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the first element to include"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "last"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the last element to include"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_get_size_in_range" gtk_bitset_get_size_in_range :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- first : TBasicType TUInt
    Word32 ->                               -- last : TBasicType TUInt
    IO Word64

-- | Gets the number of values that are part of the set from /@first@/ to /@last@/
-- (inclusive).
-- 
-- Note that this function returns a @guint64@, because when all values are
-- set, the return value is @G_MAXUINT + 1@. Unless you are sure this cannot
-- happen (it can\'t with @GListModel@), be sure to use a 64bit type.
bitsetGetSizeInRange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@first@/: the first element to include
    -> Word32
    -- ^ /@last@/: the last element to include
    -> m Word64
    -- ^ __Returns:__ The number of values in the set from /@first@/ to /@last@/.
bitsetGetSizeInRange :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> m Word64
bitsetGetSizeInRange Bitset
self Word32
first Word32
last = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Word64
result <- Ptr Bitset -> Word32 -> Word32 -> IO Word64
gtk_bitset_get_size_in_range Ptr Bitset
self' Word32
first Word32
last
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data BitsetGetSizeInRangeMethodInfo
instance (signature ~ (Word32 -> Word32 -> m Word64), MonadIO m) => O.OverloadedMethod BitsetGetSizeInRangeMethodInfo Bitset signature where
    overloadedMethod = bitsetGetSizeInRange

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


#endif

-- method Bitset::intersect
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "other"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkBitset` to intersect with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_intersect" gtk_bitset_intersect :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Ptr Bitset ->                           -- other : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO ()

-- | Sets /@self@/ to be the intersection of /@self@/ and /@other@/.
-- 
-- In other words, remove all values from /@self@/ that are not part of /@other@/.
-- 
-- It is allowed for /@self@/ and /@other@/ to be the same bitset. Nothing will
-- happen in that case.
bitsetIntersect ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Bitset
    -- ^ /@other@/: the @GtkBitset@ to intersect with
    -> m ()
bitsetIntersect :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Bitset -> m ()
bitsetIntersect Bitset
self Bitset
other = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset
other' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
other
    Ptr Bitset -> Ptr Bitset -> IO ()
gtk_bitset_intersect Ptr Bitset
self' Ptr Bitset
other'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
other
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetIntersectMethodInfo
instance (signature ~ (Bitset -> m ()), MonadIO m) => O.OverloadedMethod BitsetIntersectMethodInfo Bitset signature where
    overloadedMethod = bitsetIntersect

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


#endif

-- method Bitset::is_empty
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_is_empty" gtk_bitset_is_empty :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO CInt

-- | Check if no value is contained in bitset.
bitsetIsEmpty ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@self@/ is empty
bitsetIsEmpty :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Bitset -> m Bool
bitsetIsEmpty Bitset
self = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    CInt
result <- Ptr Bitset -> IO CInt
gtk_bitset_is_empty Ptr Bitset
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BitsetIsEmptyMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod BitsetIsEmptyMethodInfo Bitset signature where
    overloadedMethod = bitsetIsEmpty

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


#endif

-- method Bitset::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Bitset" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_ref" gtk_bitset_ref :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO (Ptr Bitset)

-- | Acquires a reference on the given @GtkBitset@.
bitsetRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m Bitset
    -- ^ __Returns:__ the @GtkBitset@ with an additional reference
bitsetRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> m Bitset
bitsetRef Bitset
self = IO Bitset -> m Bitset
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bitset -> m Bitset) -> IO Bitset -> m Bitset
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset
result <- Ptr Bitset -> IO (Ptr Bitset)
gtk_bitset_ref Ptr Bitset
self'
    Text -> Ptr Bitset -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bitsetRef" Ptr Bitset
result
    Bitset
result' <- ((ManagedPtr Bitset -> Bitset) -> Ptr Bitset -> IO Bitset
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Bitset -> Bitset
Bitset) Ptr Bitset
result
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bitset -> IO Bitset
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bitset
result'

#if defined(ENABLE_OVERLOADING)
data BitsetRefMethodInfo
instance (signature ~ (m Bitset), MonadIO m) => O.OverloadedMethod BitsetRefMethodInfo Bitset signature where
    overloadedMethod = bitsetRef

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


#endif

-- method Bitset::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "value to remove" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_remove" gtk_bitset_remove :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- value : TBasicType TUInt
    IO CInt

-- | Removes /@value@/ from /@self@/ if it was part of it before.
bitsetRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@value@/: value to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@value@/ was part of /@self@/ and /@self@/
    --   was changed
bitsetRemove :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> m Bool
bitsetRemove Bitset
self Word32
value = 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 Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    CInt
result <- Ptr Bitset -> Word32 -> IO CInt
gtk_bitset_remove Ptr Bitset
self' Word32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BitsetRemoveMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.OverloadedMethod BitsetRemoveMethodInfo Bitset signature where
    overloadedMethod = bitsetRemove

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


#endif

-- method Bitset::remove_all
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_remove_all" gtk_bitset_remove_all :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO ()

-- | Removes all values from the bitset so that it is empty again.
bitsetRemoveAll ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m ()
bitsetRemoveAll :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Bitset -> m ()
bitsetRemoveAll Bitset
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> IO ()
gtk_bitset_remove_all Ptr Bitset
self'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetRemoveAllMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod BitsetRemoveAllMethodInfo Bitset signature where
    overloadedMethod = bitsetRemoveAll

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


#endif

-- method Bitset::remove_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "start"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first value to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_items"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of consecutive values to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_remove_range" gtk_bitset_remove_range :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- start : TBasicType TUInt
    Word32 ->                               -- n_items : TBasicType TUInt
    IO ()

-- | Removes all values from /@start@/ (inclusive) to /@start@/ + /@nItems@/ (exclusive)
-- in /@self@/.
bitsetRemoveRange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@start@/: first value to remove
    -> Word32
    -- ^ /@nItems@/: number of consecutive values to remove
    -> m ()
bitsetRemoveRange :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> m ()
bitsetRemoveRange Bitset
self Word32
start Word32
nItems = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> Word32 -> IO ()
gtk_bitset_remove_range Ptr Bitset
self' Word32
start Word32
nItems
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetRemoveRangeMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetRemoveRangeMethodInfo Bitset signature where
    overloadedMethod = bitsetRemoveRange

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


#endif

-- method Bitset::remove_range_closed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "first"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first value to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "last"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "last value to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_remove_range_closed" gtk_bitset_remove_range_closed :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- first : TBasicType TUInt
    Word32 ->                               -- last : TBasicType TUInt
    IO ()

-- | Removes the closed range [/@first@/, /@last@/], so /@first@/, /@last@/ and all
-- values in between. /@first@/ must be smaller than /@last@/.
bitsetRemoveRangeClosed ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@first@/: first value to remove
    -> Word32
    -- ^ /@last@/: last value to remove
    -> m ()
bitsetRemoveRangeClosed :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> m ()
bitsetRemoveRangeClosed Bitset
self Word32
first Word32
last = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> Word32 -> IO ()
gtk_bitset_remove_range_closed Ptr Bitset
self' Word32
first Word32
last
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetRemoveRangeClosedMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetRemoveRangeClosedMethodInfo Bitset signature where
    overloadedMethod = bitsetRemoveRangeClosed

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


#endif

-- method Bitset::remove_rectangle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "start"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "first value to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width of the rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height of the rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stride"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "row stride of the grid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_remove_rectangle" gtk_bitset_remove_rectangle :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- start : TBasicType TUInt
    Word32 ->                               -- width : TBasicType TUInt
    Word32 ->                               -- height : TBasicType TUInt
    Word32 ->                               -- stride : TBasicType TUInt
    IO ()

-- | Interprets the values as a 2-dimensional boolean grid with the given /@stride@/
-- and inside that grid, removes a rectangle with the given /@width@/ and /@height@/.
bitsetRemoveRectangle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@start@/: first value to remove
    -> Word32
    -- ^ /@width@/: width of the rectangle
    -> Word32
    -- ^ /@height@/: height of the rectangle
    -> Word32
    -- ^ /@stride@/: row stride of the grid
    -> m ()
bitsetRemoveRectangle :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> Word32 -> Word32 -> m ()
bitsetRemoveRectangle Bitset
self Word32
start Word32
width Word32
height Word32
stride = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> Word32 -> Word32 -> Word32 -> IO ()
gtk_bitset_remove_rectangle Ptr Bitset
self' Word32
start Word32
width Word32
height Word32
stride
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetRemoveRectangleMethodInfo
instance (signature ~ (Word32 -> Word32 -> Word32 -> Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetRemoveRectangleMethodInfo Bitset signature where
    overloadedMethod = bitsetRemoveRectangle

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


#endif

-- method Bitset::shift_left
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "amount"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "amount to shift all values to the left"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_shift_left" gtk_bitset_shift_left :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- amount : TBasicType TUInt
    IO ()

-- | Shifts all values in /@self@/ to the left by /@amount@/.
-- 
-- Values smaller than /@amount@/ are discarded.
bitsetShiftLeft ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@amount@/: amount to shift all values to the left
    -> m ()
bitsetShiftLeft :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> m ()
bitsetShiftLeft Bitset
self Word32
amount = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> IO ()
gtk_bitset_shift_left Ptr Bitset
self' Word32
amount
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetShiftLeftMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetShiftLeftMethodInfo Bitset signature where
    overloadedMethod = bitsetShiftLeft

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


#endif

-- method Bitset::shift_right
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "amount"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "amount to shift all values to the right"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_shift_right" gtk_bitset_shift_right :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- amount : TBasicType TUInt
    IO ()

-- | Shifts all values in /@self@/ to the right by /@amount@/.
-- 
-- Values that end up too large to be held in a @/guint/@ are discarded.
bitsetShiftRight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@amount@/: amount to shift all values to the right
    -> m ()
bitsetShiftRight :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> m ()
bitsetShiftRight Bitset
self Word32
amount = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> IO ()
gtk_bitset_shift_right Ptr Bitset
self' Word32
amount
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetShiftRightMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetShiftRightMethodInfo Bitset signature where
    overloadedMethod = bitsetShiftRight

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


#endif

-- method Bitset::splice
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "position"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position at which to slice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "removed"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of values to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "added"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of values to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_splice" gtk_bitset_splice :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Word32 ->                               -- position : TBasicType TUInt
    Word32 ->                               -- removed : TBasicType TUInt
    Word32 ->                               -- added : TBasicType TUInt
    IO ()

-- | This is a support function for @GListModel@ handling, by mirroring
-- the @GlistModel::items-changed@ signal.
-- 
-- First, it \"cuts\" the values from /@position@/ to /@removed@/ from
-- the bitset. That is, it removes all those values and shifts
-- all larger values to the left by /@removed@/ places.
-- 
-- Then, it \"pastes\" new room into the bitset by shifting all values
-- larger than /@position@/ by /@added@/ spaces to the right. This frees
-- up space that can then be filled.
bitsetSplice ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Word32
    -- ^ /@position@/: position at which to slice
    -> Word32
    -- ^ /@removed@/: number of values to remove
    -> Word32
    -- ^ /@added@/: number of values to add
    -> m ()
bitsetSplice :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Word32 -> Word32 -> Word32 -> m ()
bitsetSplice Bitset
self Word32
position Word32
removed Word32
added = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> Word32 -> Word32 -> Word32 -> IO ()
gtk_bitset_splice Ptr Bitset
self' Word32
position Word32
removed Word32
added
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetSpliceMethodInfo
instance (signature ~ (Word32 -> Word32 -> Word32 -> m ()), MonadIO m) => O.OverloadedMethod BitsetSpliceMethodInfo Bitset signature where
    overloadedMethod = bitsetSplice

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


#endif

-- method Bitset::subtract
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "other"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkBitset` to subtract"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_subtract" gtk_bitset_subtract :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Ptr Bitset ->                           -- other : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO ()

-- | Sets /@self@/ to be the subtraction of /@other@/ from /@self@/.
-- 
-- In other words, remove all values from /@self@/ that are part of /@other@/.
-- 
-- It is allowed for /@self@/ and /@other@/ to be the same bitset. The bitset
-- will be emptied in that case.
bitsetSubtract ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Bitset
    -- ^ /@other@/: the @GtkBitset@ to subtract
    -> m ()
bitsetSubtract :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Bitset -> m ()
bitsetSubtract Bitset
self Bitset
other = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset
other' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
other
    Ptr Bitset -> Ptr Bitset -> IO ()
gtk_bitset_subtract Ptr Bitset
self' Ptr Bitset
other'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
other
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetSubtractMethodInfo
instance (signature ~ (Bitset -> m ()), MonadIO m) => O.OverloadedMethod BitsetSubtractMethodInfo Bitset signature where
    overloadedMethod = bitsetSubtract

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


#endif

-- method Bitset::union
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 = "other"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Bitset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkBitset` to union with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_union" gtk_bitset_union :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    Ptr Bitset ->                           -- other : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO ()

-- | Sets /@self@/ to be the union of /@self@/ and /@other@/.
-- 
-- That is, add all values from /@other@/ into /@self@/ that weren\'t part of it.
-- 
-- It is allowed for /@self@/ and /@other@/ to be the same bitset. Nothing will
-- happen in that case.
bitsetUnion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> Bitset
    -- ^ /@other@/: the @GtkBitset@ to union with
    -> m ()
bitsetUnion :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bitset -> Bitset -> m ()
bitsetUnion Bitset
self Bitset
other = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset
other' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
other
    Ptr Bitset -> Ptr Bitset -> IO ()
gtk_bitset_union Ptr Bitset
self' Ptr Bitset
other'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
other
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetUnionMethodInfo
instance (signature ~ (Bitset -> m ()), MonadIO m) => O.OverloadedMethod BitsetUnionMethodInfo Bitset signature where
    overloadedMethod = bitsetUnion

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


#endif

-- method Bitset::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_bitset_unref" gtk_bitset_unref :: 
    Ptr Bitset ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Bitset"})
    IO ()

-- | Releases a reference on the given @GtkBitset@.
-- 
-- If the reference was the last, the resources associated to the /@self@/ are
-- freed.
bitsetUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bitset
    -- ^ /@self@/: a @GtkBitset@
    -> m ()
bitsetUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Bitset -> m ()
bitsetUnref Bitset
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Bitset
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
    Ptr Bitset -> IO ()
gtk_bitset_unref Ptr Bitset
self'
    Bitset -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bitset
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BitsetUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod BitsetUnrefMethodInfo Bitset signature where
    overloadedMethod = bitsetUnref

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


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveBitsetMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveBitsetMethod "add" o = BitsetAddMethodInfo
    ResolveBitsetMethod "addRange" o = BitsetAddRangeMethodInfo
    ResolveBitsetMethod "addRangeClosed" o = BitsetAddRangeClosedMethodInfo
    ResolveBitsetMethod "addRectangle" o = BitsetAddRectangleMethodInfo
    ResolveBitsetMethod "contains" o = BitsetContainsMethodInfo
    ResolveBitsetMethod "copy" o = BitsetCopyMethodInfo
    ResolveBitsetMethod "difference" o = BitsetDifferenceMethodInfo
    ResolveBitsetMethod "equals" o = BitsetEqualsMethodInfo
    ResolveBitsetMethod "intersect" o = BitsetIntersectMethodInfo
    ResolveBitsetMethod "isEmpty" o = BitsetIsEmptyMethodInfo
    ResolveBitsetMethod "ref" o = BitsetRefMethodInfo
    ResolveBitsetMethod "remove" o = BitsetRemoveMethodInfo
    ResolveBitsetMethod "removeAll" o = BitsetRemoveAllMethodInfo
    ResolveBitsetMethod "removeRange" o = BitsetRemoveRangeMethodInfo
    ResolveBitsetMethod "removeRangeClosed" o = BitsetRemoveRangeClosedMethodInfo
    ResolveBitsetMethod "removeRectangle" o = BitsetRemoveRectangleMethodInfo
    ResolveBitsetMethod "shiftLeft" o = BitsetShiftLeftMethodInfo
    ResolveBitsetMethod "shiftRight" o = BitsetShiftRightMethodInfo
    ResolveBitsetMethod "splice" o = BitsetSpliceMethodInfo
    ResolveBitsetMethod "subtract" o = BitsetSubtractMethodInfo
    ResolveBitsetMethod "union" o = BitsetUnionMethodInfo
    ResolveBitsetMethod "unref" o = BitsetUnrefMethodInfo
    ResolveBitsetMethod "getMaximum" o = BitsetGetMaximumMethodInfo
    ResolveBitsetMethod "getMinimum" o = BitsetGetMinimumMethodInfo
    ResolveBitsetMethod "getNth" o = BitsetGetNthMethodInfo
    ResolveBitsetMethod "getSize" o = BitsetGetSizeMethodInfo
    ResolveBitsetMethod "getSizeInRange" o = BitsetGetSizeInRangeMethodInfo
    ResolveBitsetMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif