{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.Bitset
(
Bitset(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveBitsetMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
BitsetAddMethodInfo ,
#endif
bitsetAdd ,
#if defined(ENABLE_OVERLOADING)
BitsetAddRangeMethodInfo ,
#endif
bitsetAddRange ,
#if defined(ENABLE_OVERLOADING)
BitsetAddRangeClosedMethodInfo ,
#endif
bitsetAddRangeClosed ,
#if defined(ENABLE_OVERLOADING)
BitsetAddRectangleMethodInfo ,
#endif
bitsetAddRectangle ,
#if defined(ENABLE_OVERLOADING)
BitsetContainsMethodInfo ,
#endif
bitsetContains ,
#if defined(ENABLE_OVERLOADING)
BitsetCopyMethodInfo ,
#endif
bitsetCopy ,
#if defined(ENABLE_OVERLOADING)
BitsetDifferenceMethodInfo ,
#endif
bitsetDifference ,
#if defined(ENABLE_OVERLOADING)
BitsetEqualsMethodInfo ,
#endif
bitsetEquals ,
#if defined(ENABLE_OVERLOADING)
BitsetGetMaximumMethodInfo ,
#endif
bitsetGetMaximum ,
#if defined(ENABLE_OVERLOADING)
BitsetGetMinimumMethodInfo ,
#endif
bitsetGetMinimum ,
#if defined(ENABLE_OVERLOADING)
BitsetGetNthMethodInfo ,
#endif
bitsetGetNth ,
#if defined(ENABLE_OVERLOADING)
BitsetGetSizeMethodInfo ,
#endif
bitsetGetSize ,
#if defined(ENABLE_OVERLOADING)
BitsetGetSizeInRangeMethodInfo ,
#endif
bitsetGetSizeInRange ,
#if defined(ENABLE_OVERLOADING)
BitsetIntersectMethodInfo ,
#endif
bitsetIntersect ,
#if defined(ENABLE_OVERLOADING)
BitsetIsEmptyMethodInfo ,
#endif
bitsetIsEmpty ,
bitsetNewEmpty ,
bitsetNewRange ,
#if defined(ENABLE_OVERLOADING)
BitsetRefMethodInfo ,
#endif
bitsetRef ,
#if defined(ENABLE_OVERLOADING)
BitsetRemoveMethodInfo ,
#endif
bitsetRemove ,
#if defined(ENABLE_OVERLOADING)
BitsetRemoveAllMethodInfo ,
#endif
bitsetRemoveAll ,
#if defined(ENABLE_OVERLOADING)
BitsetRemoveRangeMethodInfo ,
#endif
bitsetRemoveRange ,
#if defined(ENABLE_OVERLOADING)
BitsetRemoveRangeClosedMethodInfo ,
#endif
bitsetRemoveRangeClosed ,
#if defined(ENABLE_OVERLOADING)
BitsetRemoveRectangleMethodInfo ,
#endif
bitsetRemoveRectangle ,
#if defined(ENABLE_OVERLOADING)
BitsetShiftLeftMethodInfo ,
#endif
bitsetShiftLeft ,
#if defined(ENABLE_OVERLOADING)
BitsetShiftRightMethodInfo ,
#endif
bitsetShiftRight ,
#if defined(ENABLE_OVERLOADING)
BitsetSpliceMethodInfo ,
#endif
bitsetSplice ,
#if defined(ENABLE_OVERLOADING)
BitsetSubtractMethodInfo ,
#endif
bitsetSubtract ,
#if defined(ENABLE_OVERLOADING)
BitsetUnionMethodInfo ,
#endif
bitsetUnion ,
#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
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
#else
#endif
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
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 <- Ptr GValue -> IO (Ptr Bitset)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Bitset)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed Bitset ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Bitset
type instance O.AttributeList Bitset = BitsetAttributeList
type BitsetAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_bitset_new_empty" gtk_bitset_new_empty ::
IO (Ptr Bitset)
bitsetNewEmpty ::
(B.CallStack.HasCallStack, MonadIO m) =>
m 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
result <- IO (Ptr Bitset)
gtk_bitset_new_empty
checkUnexpectedReturnNULL "bitsetNewEmpty" result
result' <- (wrapBoxed Bitset) result
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_bitset_new_range" gtk_bitset_new_range ::
Word32 ->
Word32 ->
IO (Ptr Bitset)
bitsetNewRange ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word32
-> Word32
-> m 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
result <- Word32 -> Word32 -> IO (Ptr Bitset)
gtk_bitset_new_range Word32
start Word32
nItems
checkUnexpectedReturnNULL "bitsetNewRange" result
result' <- (wrapBoxed Bitset) result
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_bitset_add" gtk_bitset_add ::
Ptr Bitset ->
Word32 ->
IO CInt
bitsetAdd ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> m Bool
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_add self' value
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetAdd"
})
#endif
foreign import ccall "gtk_bitset_add_range" gtk_bitset_add_range ::
Ptr Bitset ->
Word32 ->
Word32 ->
IO ()
bitsetAddRange ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_add_range self' start nItems
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetAddRange"
})
#endif
foreign import ccall "gtk_bitset_add_range_closed" gtk_bitset_add_range_closed ::
Ptr Bitset ->
Word32 ->
Word32 ->
IO ()
bitsetAddRangeClosed ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_add_range_closed self' first last
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetAddRangeClosed"
})
#endif
foreign import ccall "gtk_bitset_add_rectangle" gtk_bitset_add_rectangle ::
Ptr Bitset ->
Word32 ->
Word32 ->
Word32 ->
Word32 ->
IO ()
bitsetAddRectangle ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> Word32
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_add_rectangle self' start width height stride
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetAddRectangle"
})
#endif
foreign import ccall "gtk_bitset_contains" gtk_bitset_contains ::
Ptr Bitset ->
Word32 ->
IO CInt
bitsetContains ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> m Bool
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_contains self' value
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetContains"
})
#endif
foreign import ccall "gtk_bitset_copy" gtk_bitset_copy ::
Ptr Bitset ->
IO (Ptr Bitset)
bitsetCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> m Bitset
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_copy self'
checkUnexpectedReturnNULL "bitsetCopy" result
result' <- (wrapBoxed Bitset) result
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetCopy"
})
#endif
foreign import ccall "gtk_bitset_difference" gtk_bitset_difference ::
Ptr Bitset ->
Ptr Bitset ->
IO ()
bitsetDifference ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Bitset
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
other' <- unsafeManagedPtrGetPtr other
gtk_bitset_difference self' other'
touchManagedPtr self
touchManagedPtr other
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetDifference"
})
#endif
foreign import ccall "gtk_bitset_equals" gtk_bitset_equals ::
Ptr Bitset ->
Ptr Bitset ->
IO CInt
bitsetEquals ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Bitset
-> m Bool
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
other' <- unsafeManagedPtrGetPtr other
result <- gtk_bitset_equals self' other'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr self
touchManagedPtr other
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetEquals"
})
#endif
foreign import ccall "gtk_bitset_get_maximum" gtk_bitset_get_maximum ::
Ptr Bitset ->
IO Word32
bitsetGetMaximum ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> m Word32
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_get_maximum self'
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetGetMaximum"
})
#endif
foreign import ccall "gtk_bitset_get_minimum" gtk_bitset_get_minimum ::
Ptr Bitset ->
IO Word32
bitsetGetMinimum ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> m Word32
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_get_minimum self'
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetGetMinimum"
})
#endif
foreign import ccall "gtk_bitset_get_nth" gtk_bitset_get_nth ::
Ptr Bitset ->
Word32 ->
IO Word32
bitsetGetNth ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> m Word32
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_get_nth self' nth
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetGetNth"
})
#endif
foreign import ccall "gtk_bitset_get_size" gtk_bitset_get_size ::
Ptr Bitset ->
IO Word64
bitsetGetSize ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> m Word64
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_get_size self'
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetGetSize"
})
#endif
foreign import ccall "gtk_bitset_get_size_in_range" gtk_bitset_get_size_in_range ::
Ptr Bitset ->
Word32 ->
Word32 ->
IO Word64
bitsetGetSizeInRange ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> m Word64
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_get_size_in_range self' first last
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetGetSizeInRange"
})
#endif
foreign import ccall "gtk_bitset_intersect" gtk_bitset_intersect ::
Ptr Bitset ->
Ptr Bitset ->
IO ()
bitsetIntersect ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Bitset
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
other' <- unsafeManagedPtrGetPtr other
gtk_bitset_intersect self' other'
touchManagedPtr self
touchManagedPtr other
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetIntersect"
})
#endif
foreign import ccall "gtk_bitset_is_empty" gtk_bitset_is_empty ::
Ptr Bitset ->
IO CInt
bitsetIsEmpty ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> m Bool
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_is_empty self'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetIsEmpty"
})
#endif
foreign import ccall "gtk_bitset_ref" gtk_bitset_ref ::
Ptr Bitset ->
IO (Ptr Bitset)
bitsetRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> m Bitset
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_ref self'
checkUnexpectedReturnNULL "bitsetRef" result
result' <- (newBoxed Bitset) result
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetRef"
})
#endif
foreign import ccall "gtk_bitset_remove" gtk_bitset_remove ::
Ptr Bitset ->
Word32 ->
IO CInt
bitsetRemove ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> m Bool
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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
result <- gtk_bitset_remove self' value
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr self
return 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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetRemove"
})
#endif
foreign import ccall "gtk_bitset_remove_all" gtk_bitset_remove_all ::
Ptr Bitset ->
IO ()
bitsetRemoveAll ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_remove_all self'
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetRemoveAll"
})
#endif
foreign import ccall "gtk_bitset_remove_range" gtk_bitset_remove_range ::
Ptr Bitset ->
Word32 ->
Word32 ->
IO ()
bitsetRemoveRange ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_remove_range self' start nItems
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetRemoveRange"
})
#endif
foreign import ccall "gtk_bitset_remove_range_closed" gtk_bitset_remove_range_closed ::
Ptr Bitset ->
Word32 ->
Word32 ->
IO ()
bitsetRemoveRangeClosed ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_remove_range_closed self' first last
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetRemoveRangeClosed"
})
#endif
foreign import ccall "gtk_bitset_remove_rectangle" gtk_bitset_remove_rectangle ::
Ptr Bitset ->
Word32 ->
Word32 ->
Word32 ->
Word32 ->
IO ()
bitsetRemoveRectangle ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> Word32
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_remove_rectangle self' start width height stride
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetRemoveRectangle"
})
#endif
foreign import ccall "gtk_bitset_shift_left" gtk_bitset_shift_left ::
Ptr Bitset ->
Word32 ->
IO ()
bitsetShiftLeft ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_shift_left self' amount
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetShiftLeft"
})
#endif
foreign import ccall "gtk_bitset_shift_right" gtk_bitset_shift_right ::
Ptr Bitset ->
Word32 ->
IO ()
bitsetShiftRight ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_shift_right self' amount
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetShiftRight"
})
#endif
foreign import ccall "gtk_bitset_splice" gtk_bitset_splice ::
Ptr Bitset ->
Word32 ->
Word32 ->
Word32 ->
IO ()
bitsetSplice ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Word32
-> Word32
-> Word32
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
gtk_bitset_splice self' position removed added
touchManagedPtr self
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetSplice"
})
#endif
foreign import ccall "gtk_bitset_subtract" gtk_bitset_subtract ::
Ptr Bitset ->
Ptr Bitset ->
IO ()
bitsetSubtract ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Bitset
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
other' <- unsafeManagedPtrGetPtr other
gtk_bitset_subtract self' other'
touchManagedPtr self
touchManagedPtr other
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetSubtract"
})
#endif
foreign import ccall "gtk_bitset_union" gtk_bitset_union ::
Ptr Bitset ->
Ptr Bitset ->
IO ()
bitsetUnion ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> Bitset
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bitset
self
other' <- unsafeManagedPtrGetPtr other
gtk_bitset_union self' other'
touchManagedPtr self
touchManagedPtr other
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-gtk4-4.0.12/docs/GI-Gtk-Structs-Bitset.html#v:bitsetUnion"
})
#endif
foreign import ccall "gtk_bitset_unref" gtk_bitset_unref ::
Ptr Bitset ->
IO ()
bitsetUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bitset
-> 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
self' <- Bitset -> IO (Ptr Bitset)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Bitset
self
gtk_bitset_unref self'
touchManagedPtr self
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-gtk4-4.0.12/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