{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Objects.StateSet
(
StateSet(..) ,
IsStateSet ,
toStateSet ,
#if defined(ENABLE_OVERLOADING)
ResolveStateSetMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
StateSetAddStateMethodInfo ,
#endif
stateSetAddState ,
#if defined(ENABLE_OVERLOADING)
StateSetAddStatesMethodInfo ,
#endif
stateSetAddStates ,
#if defined(ENABLE_OVERLOADING)
StateSetAndSetsMethodInfo ,
#endif
stateSetAndSets ,
#if defined(ENABLE_OVERLOADING)
StateSetClearStatesMethodInfo ,
#endif
stateSetClearStates ,
#if defined(ENABLE_OVERLOADING)
StateSetContainsStateMethodInfo ,
#endif
stateSetContainsState ,
#if defined(ENABLE_OVERLOADING)
StateSetContainsStatesMethodInfo ,
#endif
stateSetContainsStates ,
#if defined(ENABLE_OVERLOADING)
StateSetIsEmptyMethodInfo ,
#endif
stateSetIsEmpty ,
stateSetNew ,
#if defined(ENABLE_OVERLOADING)
StateSetOrSetsMethodInfo ,
#endif
stateSetOrSets ,
#if defined(ENABLE_OVERLOADING)
StateSetRemoveStateMethodInfo ,
#endif
stateSetRemoveState ,
#if defined(ENABLE_OVERLOADING)
StateSetXorSetsMethodInfo ,
#endif
stateSetXorSets ,
) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import {-# SOURCE #-} qualified GI.Atk.Enums as Atk.Enums
import qualified GI.GObject.Objects.Object as GObject.Object
newtype StateSet = StateSet (SP.ManagedPtr StateSet)
deriving (StateSet -> StateSet -> Bool
(StateSet -> StateSet -> Bool)
-> (StateSet -> StateSet -> Bool) -> Eq StateSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StateSet -> StateSet -> Bool
$c/= :: StateSet -> StateSet -> Bool
== :: StateSet -> StateSet -> Bool
$c== :: StateSet -> StateSet -> Bool
Eq)
instance SP.ManagedPtrNewtype StateSet where
toManagedPtr :: StateSet -> ManagedPtr StateSet
toManagedPtr (StateSet ManagedPtr StateSet
p) = ManagedPtr StateSet
p
foreign import ccall "atk_state_set_get_type"
c_atk_state_set_get_type :: IO B.Types.GType
instance B.Types.TypedObject StateSet where
glibType :: IO GType
glibType = IO GType
c_atk_state_set_get_type
instance B.Types.GObject StateSet
instance B.GValue.IsGValue StateSet where
toGValue :: StateSet -> IO GValue
toGValue StateSet
o = do
GType
gtype <- IO GType
c_atk_state_set_get_type
StateSet -> (Ptr StateSet -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StateSet
o (GType
-> (GValue -> Ptr StateSet -> IO ()) -> Ptr StateSet -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr StateSet -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO StateSet
fromGValue GValue
gv = do
Ptr StateSet
ptr <- GValue -> IO (Ptr StateSet)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr StateSet)
(ManagedPtr StateSet -> StateSet) -> Ptr StateSet -> IO StateSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr StateSet -> StateSet
StateSet Ptr StateSet
ptr
class (SP.GObject o, O.IsDescendantOf StateSet o) => IsStateSet o
instance (SP.GObject o, O.IsDescendantOf StateSet o) => IsStateSet o
instance O.HasParentTypes StateSet
type instance O.ParentTypes StateSet = '[GObject.Object.Object]
toStateSet :: (MonadIO m, IsStateSet o) => o -> m StateSet
toStateSet :: o -> m StateSet
toStateSet = IO StateSet -> m StateSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StateSet -> m StateSet)
-> (o -> IO StateSet) -> o -> m StateSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr StateSet -> StateSet) -> o -> IO StateSet
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr StateSet -> StateSet
StateSet
#if defined(ENABLE_OVERLOADING)
type family ResolveStateSetMethod (t :: Symbol) (o :: *) :: * where
ResolveStateSetMethod "addState" o = StateSetAddStateMethodInfo
ResolveStateSetMethod "addStates" o = StateSetAddStatesMethodInfo
ResolveStateSetMethod "andSets" o = StateSetAndSetsMethodInfo
ResolveStateSetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveStateSetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveStateSetMethod "clearStates" o = StateSetClearStatesMethodInfo
ResolveStateSetMethod "containsState" o = StateSetContainsStateMethodInfo
ResolveStateSetMethod "containsStates" o = StateSetContainsStatesMethodInfo
ResolveStateSetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveStateSetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveStateSetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveStateSetMethod "isEmpty" o = StateSetIsEmptyMethodInfo
ResolveStateSetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveStateSetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveStateSetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveStateSetMethod "orSets" o = StateSetOrSetsMethodInfo
ResolveStateSetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveStateSetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveStateSetMethod "removeState" o = StateSetRemoveStateMethodInfo
ResolveStateSetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveStateSetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveStateSetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveStateSetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveStateSetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveStateSetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveStateSetMethod "xorSets" o = StateSetXorSetsMethodInfo
ResolveStateSetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveStateSetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveStateSetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveStateSetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveStateSetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveStateSetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveStateSetMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveStateSetMethod t StateSet, O.MethodInfo info StateSet p) => OL.IsLabel t (StateSet -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StateSet
type instance O.AttributeList StateSet = StateSetAttributeList
type StateSetAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StateSet = StateSetSignalList
type StateSetSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "atk_state_set_new" atk_state_set_new ::
IO (Ptr StateSet)
stateSetNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m StateSet
stateSetNew :: m StateSet
stateSetNew = IO StateSet -> m StateSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StateSet -> m StateSet) -> IO StateSet -> m StateSet
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
result <- IO (Ptr StateSet)
atk_state_set_new
Text -> Ptr StateSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateSetNew" Ptr StateSet
result
StateSet
result' <- ((ManagedPtr StateSet -> StateSet) -> Ptr StateSet -> IO StateSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StateSet -> StateSet
StateSet) Ptr StateSet
result
StateSet -> IO StateSet
forall (m :: * -> *) a. Monad m => a -> m a
return StateSet
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "atk_state_set_add_state" atk_state_set_add_state ::
Ptr StateSet ->
CUInt ->
IO CInt
stateSetAddState ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a) =>
a
-> Atk.Enums.StateType
-> m Bool
stateSetAddState :: a -> StateType -> m Bool
stateSetAddState a
set StateType
type_ = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
type_
CInt
result <- Ptr StateSet -> CUInt -> IO CInt
atk_state_set_add_state Ptr StateSet
set' CUInt
type_'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data StateSetAddStateMethodInfo
instance (signature ~ (Atk.Enums.StateType -> m Bool), MonadIO m, IsStateSet a) => O.MethodInfo StateSetAddStateMethodInfo a signature where
overloadedMethod = stateSetAddState
#endif
foreign import ccall "atk_state_set_add_states" atk_state_set_add_states ::
Ptr StateSet ->
Ptr CUInt ->
Int32 ->
IO ()
stateSetAddStates ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a) =>
a
-> [Atk.Enums.StateType]
-> m ()
stateSetAddStates :: a -> [StateType] -> m ()
stateSetAddStates a
set [StateType]
types = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nTypes :: Int32
nTypes = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [StateType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [StateType]
types
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
let types' :: [CUInt]
types' = (StateType -> CUInt) -> [StateType] -> [CUInt]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) [StateType]
types
Ptr CUInt
types'' <- [CUInt] -> IO (Ptr CUInt)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [CUInt]
types'
Ptr StateSet -> Ptr CUInt -> Int32 -> IO ()
atk_state_set_add_states Ptr StateSet
set' Ptr CUInt
types'' Int32
nTypes
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
types''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StateSetAddStatesMethodInfo
instance (signature ~ ([Atk.Enums.StateType] -> m ()), MonadIO m, IsStateSet a) => O.MethodInfo StateSetAddStatesMethodInfo a signature where
overloadedMethod = stateSetAddStates
#endif
foreign import ccall "atk_state_set_and_sets" atk_state_set_and_sets ::
Ptr StateSet ->
Ptr StateSet ->
IO (Ptr StateSet)
stateSetAndSets ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a, IsStateSet b) =>
a
-> b
-> m StateSet
stateSetAndSets :: a -> b -> m StateSet
stateSetAndSets a
set b
compareSet = IO StateSet -> m StateSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StateSet -> m StateSet) -> IO StateSet -> m StateSet
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Ptr StateSet
compareSet' <- b -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
compareSet
Ptr StateSet
result <- Ptr StateSet -> Ptr StateSet -> IO (Ptr StateSet)
atk_state_set_and_sets Ptr StateSet
set' Ptr StateSet
compareSet'
Text -> Ptr StateSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateSetAndSets" Ptr StateSet
result
StateSet
result' <- ((ManagedPtr StateSet -> StateSet) -> Ptr StateSet -> IO StateSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StateSet -> StateSet
StateSet) Ptr StateSet
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
compareSet
StateSet -> IO StateSet
forall (m :: * -> *) a. Monad m => a -> m a
return StateSet
result'
#if defined(ENABLE_OVERLOADING)
data StateSetAndSetsMethodInfo
instance (signature ~ (b -> m StateSet), MonadIO m, IsStateSet a, IsStateSet b) => O.MethodInfo StateSetAndSetsMethodInfo a signature where
overloadedMethod = stateSetAndSets
#endif
foreign import ccall "atk_state_set_clear_states" atk_state_set_clear_states ::
Ptr StateSet ->
IO ()
stateSetClearStates ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a) =>
a
-> m ()
stateSetClearStates :: a -> m ()
stateSetClearStates a
set = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Ptr StateSet -> IO ()
atk_state_set_clear_states Ptr StateSet
set'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StateSetClearStatesMethodInfo
instance (signature ~ (m ()), MonadIO m, IsStateSet a) => O.MethodInfo StateSetClearStatesMethodInfo a signature where
overloadedMethod = stateSetClearStates
#endif
foreign import ccall "atk_state_set_contains_state" atk_state_set_contains_state ::
Ptr StateSet ->
CUInt ->
IO CInt
stateSetContainsState ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a) =>
a
-> Atk.Enums.StateType
-> m Bool
stateSetContainsState :: a -> StateType -> m Bool
stateSetContainsState a
set StateType
type_ = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
type_
CInt
result <- Ptr StateSet -> CUInt -> IO CInt
atk_state_set_contains_state Ptr StateSet
set' CUInt
type_'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data StateSetContainsStateMethodInfo
instance (signature ~ (Atk.Enums.StateType -> m Bool), MonadIO m, IsStateSet a) => O.MethodInfo StateSetContainsStateMethodInfo a signature where
overloadedMethod = stateSetContainsState
#endif
foreign import ccall "atk_state_set_contains_states" atk_state_set_contains_states ::
Ptr StateSet ->
Ptr CUInt ->
Int32 ->
IO CInt
stateSetContainsStates ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a) =>
a
-> [Atk.Enums.StateType]
-> m Bool
stateSetContainsStates :: a -> [StateType] -> m Bool
stateSetContainsStates a
set [StateType]
types = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
let nTypes :: Int32
nTypes = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [StateType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [StateType]
types
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
let types' :: [CUInt]
types' = (StateType -> CUInt) -> [StateType] -> [CUInt]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) [StateType]
types
Ptr CUInt
types'' <- [CUInt] -> IO (Ptr CUInt)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [CUInt]
types'
CInt
result <- Ptr StateSet -> Ptr CUInt -> Int32 -> IO CInt
atk_state_set_contains_states Ptr StateSet
set' Ptr CUInt
types'' Int32
nTypes
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
types''
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data StateSetContainsStatesMethodInfo
instance (signature ~ ([Atk.Enums.StateType] -> m Bool), MonadIO m, IsStateSet a) => O.MethodInfo StateSetContainsStatesMethodInfo a signature where
overloadedMethod = stateSetContainsStates
#endif
foreign import ccall "atk_state_set_is_empty" atk_state_set_is_empty ::
Ptr StateSet ->
IO CInt
stateSetIsEmpty ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a) =>
a
-> m Bool
stateSetIsEmpty :: a -> m Bool
stateSetIsEmpty a
set = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
CInt
result <- Ptr StateSet -> IO CInt
atk_state_set_is_empty Ptr StateSet
set'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data StateSetIsEmptyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsStateSet a) => O.MethodInfo StateSetIsEmptyMethodInfo a signature where
overloadedMethod = stateSetIsEmpty
#endif
foreign import ccall "atk_state_set_or_sets" atk_state_set_or_sets ::
Ptr StateSet ->
Ptr StateSet ->
IO (Ptr StateSet)
stateSetOrSets ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a, IsStateSet b) =>
a
-> b
-> m (Maybe StateSet)
stateSetOrSets :: a -> b -> m (Maybe StateSet)
stateSetOrSets a
set b
compareSet = IO (Maybe StateSet) -> m (Maybe StateSet)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe StateSet) -> m (Maybe StateSet))
-> IO (Maybe StateSet) -> m (Maybe StateSet)
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Ptr StateSet
compareSet' <- b -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
compareSet
Ptr StateSet
result <- Ptr StateSet -> Ptr StateSet -> IO (Ptr StateSet)
atk_state_set_or_sets Ptr StateSet
set' Ptr StateSet
compareSet'
Maybe StateSet
maybeResult <- Ptr StateSet
-> (Ptr StateSet -> IO StateSet) -> IO (Maybe StateSet)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr StateSet
result ((Ptr StateSet -> IO StateSet) -> IO (Maybe StateSet))
-> (Ptr StateSet -> IO StateSet) -> IO (Maybe StateSet)
forall a b. (a -> b) -> a -> b
$ \Ptr StateSet
result' -> do
StateSet
result'' <- ((ManagedPtr StateSet -> StateSet) -> Ptr StateSet -> IO StateSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StateSet -> StateSet
StateSet) Ptr StateSet
result'
StateSet -> IO StateSet
forall (m :: * -> *) a. Monad m => a -> m a
return StateSet
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
compareSet
Maybe StateSet -> IO (Maybe StateSet)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StateSet
maybeResult
#if defined(ENABLE_OVERLOADING)
data StateSetOrSetsMethodInfo
instance (signature ~ (b -> m (Maybe StateSet)), MonadIO m, IsStateSet a, IsStateSet b) => O.MethodInfo StateSetOrSetsMethodInfo a signature where
overloadedMethod = stateSetOrSets
#endif
foreign import ccall "atk_state_set_remove_state" atk_state_set_remove_state ::
Ptr StateSet ->
CUInt ->
IO CInt
stateSetRemoveState ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a) =>
a
-> Atk.Enums.StateType
-> m Bool
stateSetRemoveState :: a -> StateType -> m Bool
stateSetRemoveState a
set StateType
type_ = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
type_
CInt
result <- Ptr StateSet -> CUInt -> IO CInt
atk_state_set_remove_state Ptr StateSet
set' CUInt
type_'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data StateSetRemoveStateMethodInfo
instance (signature ~ (Atk.Enums.StateType -> m Bool), MonadIO m, IsStateSet a) => O.MethodInfo StateSetRemoveStateMethodInfo a signature where
overloadedMethod = stateSetRemoveState
#endif
foreign import ccall "atk_state_set_xor_sets" atk_state_set_xor_sets ::
Ptr StateSet ->
Ptr StateSet ->
IO (Ptr StateSet)
stateSetXorSets ::
(B.CallStack.HasCallStack, MonadIO m, IsStateSet a, IsStateSet b) =>
a
-> b
-> m StateSet
stateSetXorSets :: a -> b -> m StateSet
stateSetXorSets a
set b
compareSet = IO StateSet -> m StateSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StateSet -> m StateSet) -> IO StateSet -> m StateSet
forall a b. (a -> b) -> a -> b
$ do
Ptr StateSet
set' <- a -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Ptr StateSet
compareSet' <- b -> IO (Ptr StateSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
compareSet
Ptr StateSet
result <- Ptr StateSet -> Ptr StateSet -> IO (Ptr StateSet)
atk_state_set_xor_sets Ptr StateSet
set' Ptr StateSet
compareSet'
Text -> Ptr StateSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateSetXorSets" Ptr StateSet
result
StateSet
result' <- ((ManagedPtr StateSet -> StateSet) -> Ptr StateSet -> IO StateSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StateSet -> StateSet
StateSet) Ptr StateSet
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
compareSet
StateSet -> IO StateSet
forall (m :: * -> *) a. Monad m => a -> m a
return StateSet
result'
#if defined(ENABLE_OVERLOADING)
data StateSetXorSetsMethodInfo
instance (signature ~ (b -> m StateSet), MonadIO m, IsStateSet a, IsStateSet b) => O.MethodInfo StateSetXorSetsMethodInfo a signature where
overloadedMethod = stateSetXorSets
#endif