{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Clutter.Structs.ActorIter
(
ActorIter(..) ,
newZeroActorIter ,
#if defined(ENABLE_OVERLOADING)
ResolveActorIterMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ActorIterDestroyMethodInfo ,
#endif
actorIterDestroy ,
#if defined(ENABLE_OVERLOADING)
ActorIterInitMethodInfo ,
#endif
actorIterInit ,
#if defined(ENABLE_OVERLOADING)
ActorIterIsValidMethodInfo ,
#endif
actorIterIsValid ,
#if defined(ENABLE_OVERLOADING)
ActorIterNextMethodInfo ,
#endif
actorIterNext ,
#if defined(ENABLE_OVERLOADING)
ActorIterPrevMethodInfo ,
#endif
actorIterPrev ,
#if defined(ENABLE_OVERLOADING)
ActorIterRemoveMethodInfo ,
#endif
actorIterRemove ,
) 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.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import {-# SOURCE #-} qualified GI.Clutter.Objects.Actor as Clutter.Actor
newtype ActorIter = ActorIter (SP.ManagedPtr ActorIter)
deriving (ActorIter -> ActorIter -> Bool
(ActorIter -> ActorIter -> Bool)
-> (ActorIter -> ActorIter -> Bool) -> Eq ActorIter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActorIter -> ActorIter -> Bool
== :: ActorIter -> ActorIter -> Bool
$c/= :: ActorIter -> ActorIter -> Bool
/= :: ActorIter -> ActorIter -> Bool
Eq)
instance SP.ManagedPtrNewtype ActorIter where
toManagedPtr :: ActorIter -> ManagedPtr ActorIter
toManagedPtr (ActorIter ManagedPtr ActorIter
p) = ManagedPtr ActorIter
p
instance BoxedPtr ActorIter where
boxedPtrCopy :: ActorIter -> IO ActorIter
boxedPtrCopy = \ActorIter
p -> ActorIter -> (Ptr ActorIter -> IO ActorIter) -> IO ActorIter
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ActorIter
p (Int -> Ptr ActorIter -> IO (Ptr ActorIter)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
40 (Ptr ActorIter -> IO (Ptr ActorIter))
-> (Ptr ActorIter -> IO ActorIter) -> Ptr ActorIter -> IO ActorIter
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ActorIter -> ActorIter)
-> Ptr ActorIter -> IO ActorIter
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr ActorIter -> ActorIter
ActorIter)
boxedPtrFree :: ActorIter -> IO ()
boxedPtrFree = \ActorIter
x -> ActorIter -> (Ptr ActorIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr ActorIter
x Ptr ActorIter -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr ActorIter where
boxedPtrCalloc :: IO (Ptr ActorIter)
boxedPtrCalloc = Int -> IO (Ptr ActorIter)
forall a. Int -> IO (Ptr a)
callocBytes Int
40
newZeroActorIter :: MonadIO m => m ActorIter
newZeroActorIter :: forall (m :: * -> *). MonadIO m => m ActorIter
newZeroActorIter = IO ActorIter -> m ActorIter
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ActorIter -> m ActorIter) -> IO ActorIter -> m ActorIter
forall a b. (a -> b) -> a -> b
$ IO (Ptr ActorIter)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr ActorIter)
-> (Ptr ActorIter -> IO ActorIter) -> IO ActorIter
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr ActorIter -> ActorIter)
-> Ptr ActorIter -> IO ActorIter
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ActorIter -> ActorIter
ActorIter
instance tag ~ 'AttrSet => Constructible ActorIter tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr ActorIter -> ActorIter)
-> [AttrOp ActorIter tag] -> m ActorIter
new ManagedPtr ActorIter -> ActorIter
_ [AttrOp ActorIter tag]
attrs = do
ActorIter
o <- m ActorIter
forall (m :: * -> *). MonadIO m => m ActorIter
newZeroActorIter
ActorIter -> [AttrOp ActorIter 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set ActorIter
o [AttrOp ActorIter tag]
[AttrOp ActorIter 'AttrSet]
attrs
ActorIter -> m ActorIter
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ActorIter
o
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ActorIter
type instance O.AttributeList ActorIter = ActorIterAttributeList
type ActorIterAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "clutter_actor_iter_destroy" clutter_actor_iter_destroy ::
Ptr ActorIter ->
IO ()
actorIterDestroy ::
(B.CallStack.HasCallStack, MonadIO m) =>
ActorIter
-> m ()
actorIterDestroy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ActorIter -> m ()
actorIterDestroy ActorIter
iter = 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 ActorIter
iter' <- ActorIter -> IO (Ptr ActorIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ActorIter
iter
Ptr ActorIter -> IO ()
clutter_actor_iter_destroy Ptr ActorIter
iter'
ActorIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ActorIter
iter
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActorIterDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ActorIterDestroyMethodInfo ActorIter signature where
overloadedMethod = actorIterDestroy
instance O.OverloadedMethodInfo ActorIterDestroyMethodInfo ActorIter where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Structs.ActorIter.actorIterDestroy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Structs-ActorIter.html#v:actorIterDestroy"
})
#endif
foreign import ccall "clutter_actor_iter_init" clutter_actor_iter_init ::
Ptr ActorIter ->
Ptr Clutter.Actor.Actor ->
IO ()
actorIterInit ::
(B.CallStack.HasCallStack, MonadIO m, Clutter.Actor.IsActor a) =>
ActorIter
-> a
-> m ()
actorIterInit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActor a) =>
ActorIter -> a -> m ()
actorIterInit ActorIter
iter a
root = 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 ActorIter
iter' <- ActorIter -> IO (Ptr ActorIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ActorIter
iter
Ptr Actor
root' <- a -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
root
Ptr ActorIter -> Ptr Actor -> IO ()
clutter_actor_iter_init Ptr ActorIter
iter' Ptr Actor
root'
ActorIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ActorIter
iter
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
root
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActorIterInitMethodInfo
instance (signature ~ (a -> m ()), MonadIO m, Clutter.Actor.IsActor a) => O.OverloadedMethod ActorIterInitMethodInfo ActorIter signature where
overloadedMethod = actorIterInit
instance O.OverloadedMethodInfo ActorIterInitMethodInfo ActorIter where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Structs.ActorIter.actorIterInit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Structs-ActorIter.html#v:actorIterInit"
})
#endif
foreign import ccall "clutter_actor_iter_is_valid" clutter_actor_iter_is_valid ::
Ptr ActorIter ->
IO CInt
actorIterIsValid ::
(B.CallStack.HasCallStack, MonadIO m) =>
ActorIter
-> m Bool
actorIterIsValid :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ActorIter -> m Bool
actorIterIsValid ActorIter
iter = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr ActorIter
iter' <- ActorIter -> IO (Ptr ActorIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ActorIter
iter
CInt
result <- Ptr ActorIter -> IO CInt
clutter_actor_iter_is_valid Ptr ActorIter
iter'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
ActorIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ActorIter
iter
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActorIterIsValidMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod ActorIterIsValidMethodInfo ActorIter signature where
overloadedMethod = actorIterIsValid
instance O.OverloadedMethodInfo ActorIterIsValidMethodInfo ActorIter where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Structs.ActorIter.actorIterIsValid",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Structs-ActorIter.html#v:actorIterIsValid"
})
#endif
foreign import ccall "clutter_actor_iter_next" clutter_actor_iter_next ::
Ptr ActorIter ->
Ptr (Ptr Clutter.Actor.Actor) ->
IO CInt
actorIterNext ::
(B.CallStack.HasCallStack, MonadIO m) =>
ActorIter
-> m ((Bool, Clutter.Actor.Actor))
actorIterNext :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ActorIter -> m (Bool, Actor)
actorIterNext ActorIter
iter = IO (Bool, Actor) -> m (Bool, Actor)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Actor) -> m (Bool, Actor))
-> IO (Bool, Actor) -> m (Bool, Actor)
forall a b. (a -> b) -> a -> b
$ do
Ptr ActorIter
iter' <- ActorIter -> IO (Ptr ActorIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ActorIter
iter
Ptr (Ptr Actor)
child <- IO (Ptr (Ptr Actor))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Clutter.Actor.Actor))
CInt
result <- Ptr ActorIter -> Ptr (Ptr Actor) -> IO CInt
clutter_actor_iter_next Ptr ActorIter
iter' Ptr (Ptr Actor)
child
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Ptr Actor
child' <- Ptr (Ptr Actor) -> IO (Ptr Actor)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Actor)
child
Actor
child'' <- ((ManagedPtr Actor -> Actor) -> Ptr Actor -> IO Actor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Actor -> Actor
Clutter.Actor.Actor) Ptr Actor
child'
ActorIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ActorIter
iter
Ptr (Ptr Actor) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Actor)
child
(Bool, Actor) -> IO (Bool, Actor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Actor
child'')
#if defined(ENABLE_OVERLOADING)
data ActorIterNextMethodInfo
instance (signature ~ (m ((Bool, Clutter.Actor.Actor))), MonadIO m) => O.OverloadedMethod ActorIterNextMethodInfo ActorIter signature where
overloadedMethod = actorIterNext
instance O.OverloadedMethodInfo ActorIterNextMethodInfo ActorIter where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Structs.ActorIter.actorIterNext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Structs-ActorIter.html#v:actorIterNext"
})
#endif
foreign import ccall "clutter_actor_iter_prev" clutter_actor_iter_prev ::
Ptr ActorIter ->
Ptr (Ptr Clutter.Actor.Actor) ->
IO CInt
actorIterPrev ::
(B.CallStack.HasCallStack, MonadIO m) =>
ActorIter
-> m ((Bool, Clutter.Actor.Actor))
actorIterPrev :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ActorIter -> m (Bool, Actor)
actorIterPrev ActorIter
iter = IO (Bool, Actor) -> m (Bool, Actor)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Actor) -> m (Bool, Actor))
-> IO (Bool, Actor) -> m (Bool, Actor)
forall a b. (a -> b) -> a -> b
$ do
Ptr ActorIter
iter' <- ActorIter -> IO (Ptr ActorIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ActorIter
iter
Ptr (Ptr Actor)
child <- IO (Ptr (Ptr Actor))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Clutter.Actor.Actor))
CInt
result <- Ptr ActorIter -> Ptr (Ptr Actor) -> IO CInt
clutter_actor_iter_prev Ptr ActorIter
iter' Ptr (Ptr Actor)
child
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Ptr Actor
child' <- Ptr (Ptr Actor) -> IO (Ptr Actor)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Actor)
child
Actor
child'' <- ((ManagedPtr Actor -> Actor) -> Ptr Actor -> IO Actor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Actor -> Actor
Clutter.Actor.Actor) Ptr Actor
child'
ActorIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ActorIter
iter
Ptr (Ptr Actor) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Actor)
child
(Bool, Actor) -> IO (Bool, Actor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Actor
child'')
#if defined(ENABLE_OVERLOADING)
data ActorIterPrevMethodInfo
instance (signature ~ (m ((Bool, Clutter.Actor.Actor))), MonadIO m) => O.OverloadedMethod ActorIterPrevMethodInfo ActorIter signature where
overloadedMethod = actorIterPrev
instance O.OverloadedMethodInfo ActorIterPrevMethodInfo ActorIter where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Structs.ActorIter.actorIterPrev",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Structs-ActorIter.html#v:actorIterPrev"
})
#endif
foreign import ccall "clutter_actor_iter_remove" clutter_actor_iter_remove ::
Ptr ActorIter ->
IO ()
actorIterRemove ::
(B.CallStack.HasCallStack, MonadIO m) =>
ActorIter
-> m ()
actorIterRemove :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ActorIter -> m ()
actorIterRemove ActorIter
iter = 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 ActorIter
iter' <- ActorIter -> IO (Ptr ActorIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ActorIter
iter
Ptr ActorIter -> IO ()
clutter_actor_iter_remove Ptr ActorIter
iter'
ActorIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ActorIter
iter
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActorIterRemoveMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ActorIterRemoveMethodInfo ActorIter signature where
overloadedMethod = actorIterRemove
instance O.OverloadedMethodInfo ActorIterRemoveMethodInfo ActorIter where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Structs.ActorIter.actorIterRemove",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Structs-ActorIter.html#v:actorIterRemove"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveActorIterMethod (t :: Symbol) (o :: *) :: * where
ResolveActorIterMethod "destroy" o = ActorIterDestroyMethodInfo
ResolveActorIterMethod "init" o = ActorIterInitMethodInfo
ResolveActorIterMethod "isValid" o = ActorIterIsValidMethodInfo
ResolveActorIterMethod "next" o = ActorIterNextMethodInfo
ResolveActorIterMethod "prev" o = ActorIterPrevMethodInfo
ResolveActorIterMethod "remove" o = ActorIterRemoveMethodInfo
ResolveActorIterMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveActorIterMethod t ActorIter, O.OverloadedMethod info ActorIter p) => OL.IsLabel t (ActorIter -> 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 ~ ResolveActorIterMethod t ActorIter, O.OverloadedMethod info ActorIter p, R.HasField t ActorIter p) => R.HasField t ActorIter p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveActorIterMethod t ActorIter, O.OverloadedMethodInfo info ActorIter) => OL.IsLabel t (O.MethodProxy info ActorIter) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif