{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Clutter.Objects.BehaviourPath
(
BehaviourPath(..) ,
IsBehaviourPath ,
toBehaviourPath ,
#if defined(ENABLE_OVERLOADING)
ResolveBehaviourPathMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
BehaviourPathGetPathMethodInfo ,
#endif
behaviourPathGetPath ,
behaviourPathNew ,
behaviourPathNewWithDescription ,
behaviourPathNewWithKnots ,
#if defined(ENABLE_OVERLOADING)
BehaviourPathSetPathMethodInfo ,
#endif
behaviourPathSetPath ,
#if defined(ENABLE_OVERLOADING)
BehaviourPathPathPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourPathPath ,
#endif
constructBehaviourPathPath ,
getBehaviourPathPath ,
setBehaviourPathPath ,
BehaviourPathKnotReachedCallback ,
#if defined(ENABLE_OVERLOADING)
BehaviourPathKnotReachedSignalInfo ,
#endif
afterBehaviourPathKnotReached ,
onBehaviourPathKnotReached ,
) 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)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Path as Cairo.Path
import qualified GI.Cairo.Structs.RectangleInt as Cairo.RectangleInt
import qualified GI.Clutter.Callbacks as Clutter.Callbacks
import {-# SOURCE #-} qualified GI.Clutter.Enums as Clutter.Enums
import {-# SOURCE #-} qualified GI.Clutter.Flags as Clutter.Flags
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Animatable as Clutter.Animatable
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Container as Clutter.Container
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Content as Clutter.Content
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Scriptable as Clutter.Scriptable
import {-# SOURCE #-} qualified GI.Clutter.Objects.Action as Clutter.Action
import {-# SOURCE #-} qualified GI.Clutter.Objects.Actor as Clutter.Actor
import {-# SOURCE #-} qualified GI.Clutter.Objects.ActorMeta as Clutter.ActorMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Alpha as Clutter.Alpha
import {-# SOURCE #-} qualified GI.Clutter.Objects.Animation as Clutter.Animation
import {-# SOURCE #-} qualified GI.Clutter.Objects.Animator as Clutter.Animator
import {-# SOURCE #-} qualified GI.Clutter.Objects.Backend as Clutter.Backend
import {-# SOURCE #-} qualified GI.Clutter.Objects.Behaviour as Clutter.Behaviour
import {-# SOURCE #-} qualified GI.Clutter.Objects.ChildMeta as Clutter.ChildMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Constraint as Clutter.Constraint
import {-# SOURCE #-} qualified GI.Clutter.Objects.DeviceManager as Clutter.DeviceManager
import {-# SOURCE #-} qualified GI.Clutter.Objects.Effect as Clutter.Effect
import {-# SOURCE #-} qualified GI.Clutter.Objects.Group as Clutter.Group
import {-# SOURCE #-} qualified GI.Clutter.Objects.InputDevice as Clutter.InputDevice
import {-# SOURCE #-} qualified GI.Clutter.Objects.Interval as Clutter.Interval
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutManager as Clutter.LayoutManager
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutMeta as Clutter.LayoutMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Path as Clutter.Path
import {-# SOURCE #-} qualified GI.Clutter.Objects.Script as Clutter.Script
import {-# SOURCE #-} qualified GI.Clutter.Objects.Shader as Clutter.Shader
import {-# SOURCE #-} qualified GI.Clutter.Objects.Stage as Clutter.Stage
import {-# SOURCE #-} qualified GI.Clutter.Objects.State as Clutter.State
import {-# SOURCE #-} qualified GI.Clutter.Objects.Timeline as Clutter.Timeline
import {-# SOURCE #-} qualified GI.Clutter.Objects.Transition as Clutter.Transition
import {-# SOURCE #-} qualified GI.Clutter.Structs.ActorBox as Clutter.ActorBox
import {-# SOURCE #-} qualified GI.Clutter.Structs.AnimatorKey as Clutter.AnimatorKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.ButtonEvent as Clutter.ButtonEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Color as Clutter.Color
import {-# SOURCE #-} qualified GI.Clutter.Structs.CrossingEvent as Clutter.CrossingEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.EventSequence as Clutter.EventSequence
import {-# SOURCE #-} qualified GI.Clutter.Structs.Fog as Clutter.Fog
import {-# SOURCE #-} qualified GI.Clutter.Structs.Geometry as Clutter.Geometry
import {-# SOURCE #-} qualified GI.Clutter.Structs.KeyEvent as Clutter.KeyEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Knot as Clutter.Knot
import {-# SOURCE #-} qualified GI.Clutter.Structs.Margin as Clutter.Margin
import {-# SOURCE #-} qualified GI.Clutter.Structs.Matrix as Clutter.Matrix
import {-# SOURCE #-} qualified GI.Clutter.Structs.MotionEvent as Clutter.MotionEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.PaintVolume as Clutter.PaintVolume
import {-# SOURCE #-} qualified GI.Clutter.Structs.PathNode as Clutter.PathNode
import {-# SOURCE #-} qualified GI.Clutter.Structs.Perspective as Clutter.Perspective
import {-# SOURCE #-} qualified GI.Clutter.Structs.Point as Clutter.Point
import {-# SOURCE #-} qualified GI.Clutter.Structs.Rect as Clutter.Rect
import {-# SOURCE #-} qualified GI.Clutter.Structs.ScrollEvent as Clutter.ScrollEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Size as Clutter.Size
import {-# SOURCE #-} qualified GI.Clutter.Structs.StateKey as Clutter.StateKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.Vertex as Clutter.Vertex
import {-# SOURCE #-} qualified GI.Clutter.Unions.Event as Clutter.Event
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ObjectClass as GObject.ObjectClass
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Json.Structs.Node as Json.Node
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.Layout as Pango.Layout
#else
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Scriptable as Clutter.Scriptable
import {-# SOURCE #-} qualified GI.Clutter.Objects.Alpha as Clutter.Alpha
import {-# SOURCE #-} qualified GI.Clutter.Objects.Behaviour as Clutter.Behaviour
import {-# SOURCE #-} qualified GI.Clutter.Objects.Path as Clutter.Path
import {-# SOURCE #-} qualified GI.Clutter.Structs.Knot as Clutter.Knot
import qualified GI.GObject.Objects.Object as GObject.Object
#endif
newtype BehaviourPath = BehaviourPath (SP.ManagedPtr BehaviourPath)
deriving (BehaviourPath -> BehaviourPath -> Bool
(BehaviourPath -> BehaviourPath -> Bool)
-> (BehaviourPath -> BehaviourPath -> Bool) -> Eq BehaviourPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BehaviourPath -> BehaviourPath -> Bool
== :: BehaviourPath -> BehaviourPath -> Bool
$c/= :: BehaviourPath -> BehaviourPath -> Bool
/= :: BehaviourPath -> BehaviourPath -> Bool
Eq)
instance SP.ManagedPtrNewtype BehaviourPath where
toManagedPtr :: BehaviourPath -> ManagedPtr BehaviourPath
toManagedPtr (BehaviourPath ManagedPtr BehaviourPath
p) = ManagedPtr BehaviourPath
p
foreign import ccall "clutter_behaviour_path_get_type"
c_clutter_behaviour_path_get_type :: IO B.Types.GType
instance B.Types.TypedObject BehaviourPath where
glibType :: IO GType
glibType = IO GType
c_clutter_behaviour_path_get_type
instance B.Types.GObject BehaviourPath
class (SP.GObject o, O.IsDescendantOf BehaviourPath o) => IsBehaviourPath o
instance (SP.GObject o, O.IsDescendantOf BehaviourPath o) => IsBehaviourPath o
instance O.HasParentTypes BehaviourPath
type instance O.ParentTypes BehaviourPath = '[Clutter.Behaviour.Behaviour, GObject.Object.Object, Clutter.Scriptable.Scriptable]
toBehaviourPath :: (MIO.MonadIO m, IsBehaviourPath o) => o -> m BehaviourPath
toBehaviourPath :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourPath o) =>
o -> m BehaviourPath
toBehaviourPath = IO BehaviourPath -> m BehaviourPath
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO BehaviourPath -> m BehaviourPath)
-> (o -> IO BehaviourPath) -> o -> m BehaviourPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr BehaviourPath -> BehaviourPath)
-> o -> IO BehaviourPath
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr BehaviourPath -> BehaviourPath
BehaviourPath
instance B.GValue.IsGValue (Maybe BehaviourPath) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_behaviour_path_get_type
gvalueSet_ :: Ptr GValue -> Maybe BehaviourPath -> IO ()
gvalueSet_ Ptr GValue
gv Maybe BehaviourPath
P.Nothing = Ptr GValue -> Ptr BehaviourPath -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr BehaviourPath
forall a. Ptr a
FP.nullPtr :: FP.Ptr BehaviourPath)
gvalueSet_ Ptr GValue
gv (P.Just BehaviourPath
obj) = BehaviourPath -> (Ptr BehaviourPath -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BehaviourPath
obj (Ptr GValue -> Ptr BehaviourPath -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe BehaviourPath)
gvalueGet_ Ptr GValue
gv = do
Ptr BehaviourPath
ptr <- Ptr GValue -> IO (Ptr BehaviourPath)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr BehaviourPath)
if Ptr BehaviourPath
ptr Ptr BehaviourPath -> Ptr BehaviourPath -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr BehaviourPath
forall a. Ptr a
FP.nullPtr
then BehaviourPath -> Maybe BehaviourPath
forall a. a -> Maybe a
P.Just (BehaviourPath -> Maybe BehaviourPath)
-> IO BehaviourPath -> IO (Maybe BehaviourPath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr BehaviourPath -> BehaviourPath)
-> Ptr BehaviourPath -> IO BehaviourPath
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr BehaviourPath -> BehaviourPath
BehaviourPath Ptr BehaviourPath
ptr
else Maybe BehaviourPath -> IO (Maybe BehaviourPath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BehaviourPath
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveBehaviourPathMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveBehaviourPathMethod "actorsForeach" o = Clutter.Behaviour.BehaviourActorsForeachMethodInfo
ResolveBehaviourPathMethod "apply" o = Clutter.Behaviour.BehaviourApplyMethodInfo
ResolveBehaviourPathMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveBehaviourPathMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveBehaviourPathMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveBehaviourPathMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveBehaviourPathMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveBehaviourPathMethod "isApplied" o = Clutter.Behaviour.BehaviourIsAppliedMethodInfo
ResolveBehaviourPathMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveBehaviourPathMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveBehaviourPathMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveBehaviourPathMethod "parseCustomNode" o = Clutter.Scriptable.ScriptableParseCustomNodeMethodInfo
ResolveBehaviourPathMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveBehaviourPathMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveBehaviourPathMethod "remove" o = Clutter.Behaviour.BehaviourRemoveMethodInfo
ResolveBehaviourPathMethod "removeAll" o = Clutter.Behaviour.BehaviourRemoveAllMethodInfo
ResolveBehaviourPathMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveBehaviourPathMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveBehaviourPathMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveBehaviourPathMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveBehaviourPathMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveBehaviourPathMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveBehaviourPathMethod "getActors" o = Clutter.Behaviour.BehaviourGetActorsMethodInfo
ResolveBehaviourPathMethod "getAlpha" o = Clutter.Behaviour.BehaviourGetAlphaMethodInfo
ResolveBehaviourPathMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveBehaviourPathMethod "getId" o = Clutter.Scriptable.ScriptableGetIdMethodInfo
ResolveBehaviourPathMethod "getNActors" o = Clutter.Behaviour.BehaviourGetNActorsMethodInfo
ResolveBehaviourPathMethod "getNthActor" o = Clutter.Behaviour.BehaviourGetNthActorMethodInfo
ResolveBehaviourPathMethod "getPath" o = BehaviourPathGetPathMethodInfo
ResolveBehaviourPathMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveBehaviourPathMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveBehaviourPathMethod "setAlpha" o = Clutter.Behaviour.BehaviourSetAlphaMethodInfo
ResolveBehaviourPathMethod "setCustomProperty" o = Clutter.Scriptable.ScriptableSetCustomPropertyMethodInfo
ResolveBehaviourPathMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveBehaviourPathMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveBehaviourPathMethod "setId" o = Clutter.Scriptable.ScriptableSetIdMethodInfo
ResolveBehaviourPathMethod "setPath" o = BehaviourPathSetPathMethodInfo
ResolveBehaviourPathMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveBehaviourPathMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveBehaviourPathMethod t BehaviourPath, O.OverloadedMethod info BehaviourPath p) => OL.IsLabel t (BehaviourPath -> 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 ~ ResolveBehaviourPathMethod t BehaviourPath, O.OverloadedMethod info BehaviourPath p, R.HasField t BehaviourPath p) => R.HasField t BehaviourPath p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveBehaviourPathMethod t BehaviourPath, O.OverloadedMethodInfo info BehaviourPath) => OL.IsLabel t (O.MethodProxy info BehaviourPath) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
{-# DEPRECATED BehaviourPathKnotReachedCallback ["(Since version 1.6)"] #-}
type BehaviourPathKnotReachedCallback =
Word32
-> IO ()
type C_BehaviourPathKnotReachedCallback =
Ptr BehaviourPath ->
Word32 ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_BehaviourPathKnotReachedCallback :: C_BehaviourPathKnotReachedCallback -> IO (FunPtr C_BehaviourPathKnotReachedCallback)
wrap_BehaviourPathKnotReachedCallback ::
GObject a => (a -> BehaviourPathKnotReachedCallback) ->
C_BehaviourPathKnotReachedCallback
wrap_BehaviourPathKnotReachedCallback :: forall a.
GObject a =>
(a -> BehaviourPathKnotReachedCallback)
-> C_BehaviourPathKnotReachedCallback
wrap_BehaviourPathKnotReachedCallback a -> BehaviourPathKnotReachedCallback
gi'cb Ptr BehaviourPath
gi'selfPtr Word32
knotNum Ptr ()
_ = do
Ptr BehaviourPath -> (BehaviourPath -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr BehaviourPath
gi'selfPtr ((BehaviourPath -> IO ()) -> IO ())
-> (BehaviourPath -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \BehaviourPath
gi'self -> a -> BehaviourPathKnotReachedCallback
gi'cb (BehaviourPath -> a
forall a b. Coercible a b => a -> b
Coerce.coerce BehaviourPath
gi'self) Word32
knotNum
onBehaviourPathKnotReached :: (IsBehaviourPath a, MonadIO m) => a -> ((?self :: a) => BehaviourPathKnotReachedCallback) -> m SignalHandlerId
onBehaviourPathKnotReached :: forall a (m :: * -> *).
(IsBehaviourPath a, MonadIO m) =>
a
-> ((?self::a) => BehaviourPathKnotReachedCallback)
-> m SignalHandlerId
onBehaviourPathKnotReached a
obj (?self::a) => BehaviourPathKnotReachedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> BehaviourPathKnotReachedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => BehaviourPathKnotReachedCallback
BehaviourPathKnotReachedCallback
cb
let wrapped' :: C_BehaviourPathKnotReachedCallback
wrapped' = (a -> BehaviourPathKnotReachedCallback)
-> C_BehaviourPathKnotReachedCallback
forall a.
GObject a =>
(a -> BehaviourPathKnotReachedCallback)
-> C_BehaviourPathKnotReachedCallback
wrap_BehaviourPathKnotReachedCallback a -> BehaviourPathKnotReachedCallback
wrapped
FunPtr C_BehaviourPathKnotReachedCallback
wrapped'' <- C_BehaviourPathKnotReachedCallback
-> IO (FunPtr C_BehaviourPathKnotReachedCallback)
mk_BehaviourPathKnotReachedCallback C_BehaviourPathKnotReachedCallback
wrapped'
a
-> Text
-> FunPtr C_BehaviourPathKnotReachedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"knot-reached" FunPtr C_BehaviourPathKnotReachedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterBehaviourPathKnotReached :: (IsBehaviourPath a, MonadIO m) => a -> ((?self :: a) => BehaviourPathKnotReachedCallback) -> m SignalHandlerId
afterBehaviourPathKnotReached :: forall a (m :: * -> *).
(IsBehaviourPath a, MonadIO m) =>
a
-> ((?self::a) => BehaviourPathKnotReachedCallback)
-> m SignalHandlerId
afterBehaviourPathKnotReached a
obj (?self::a) => BehaviourPathKnotReachedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> BehaviourPathKnotReachedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => BehaviourPathKnotReachedCallback
BehaviourPathKnotReachedCallback
cb
let wrapped' :: C_BehaviourPathKnotReachedCallback
wrapped' = (a -> BehaviourPathKnotReachedCallback)
-> C_BehaviourPathKnotReachedCallback
forall a.
GObject a =>
(a -> BehaviourPathKnotReachedCallback)
-> C_BehaviourPathKnotReachedCallback
wrap_BehaviourPathKnotReachedCallback a -> BehaviourPathKnotReachedCallback
wrapped
FunPtr C_BehaviourPathKnotReachedCallback
wrapped'' <- C_BehaviourPathKnotReachedCallback
-> IO (FunPtr C_BehaviourPathKnotReachedCallback)
mk_BehaviourPathKnotReachedCallback C_BehaviourPathKnotReachedCallback
wrapped'
a
-> Text
-> FunPtr C_BehaviourPathKnotReachedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"knot-reached" FunPtr C_BehaviourPathKnotReachedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data BehaviourPathKnotReachedSignalInfo
instance SignalInfo BehaviourPathKnotReachedSignalInfo where
type HaskellCallbackType BehaviourPathKnotReachedSignalInfo = BehaviourPathKnotReachedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_BehaviourPathKnotReachedCallback cb
cb'' <- mk_BehaviourPathKnotReachedCallback cb'
connectSignalFunPtr obj "knot-reached" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourPath::knot-reached"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourPath.html#g:signal:knotReached"})
#endif
getBehaviourPathPath :: (MonadIO m, IsBehaviourPath o) => o -> m Clutter.Path.Path
getBehaviourPathPath :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourPath o) =>
o -> m Path
getBehaviourPathPath o
obj = IO Path -> m Path
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Path -> m Path) -> IO Path -> m Path
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Path) -> IO Path
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getBehaviourPathPath" (IO (Maybe Path) -> IO Path) -> IO (Maybe Path) -> IO Path
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Path -> Path) -> IO (Maybe Path)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"path" ManagedPtr Path -> Path
Clutter.Path.Path
setBehaviourPathPath :: (MonadIO m, IsBehaviourPath o, Clutter.Path.IsPath a) => o -> a -> m ()
setBehaviourPathPath :: forall (m :: * -> *) o a.
(MonadIO m, IsBehaviourPath o, IsPath a) =>
o -> a -> m ()
setBehaviourPathPath o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"path" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructBehaviourPathPath :: (IsBehaviourPath o, MIO.MonadIO m, Clutter.Path.IsPath a) => a -> m (GValueConstruct o)
constructBehaviourPathPath :: forall o (m :: * -> *) a.
(IsBehaviourPath o, MonadIO m, IsPath a) =>
a -> m (GValueConstruct o)
constructBehaviourPathPath a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"path" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data BehaviourPathPathPropertyInfo
instance AttrInfo BehaviourPathPathPropertyInfo where
type AttrAllowedOps BehaviourPathPathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourPathPathPropertyInfo = IsBehaviourPath
type AttrSetTypeConstraint BehaviourPathPathPropertyInfo = Clutter.Path.IsPath
type AttrTransferTypeConstraint BehaviourPathPathPropertyInfo = Clutter.Path.IsPath
type AttrTransferType BehaviourPathPathPropertyInfo = Clutter.Path.Path
type AttrGetType BehaviourPathPathPropertyInfo = Clutter.Path.Path
type AttrLabel BehaviourPathPathPropertyInfo = "path"
type AttrOrigin BehaviourPathPathPropertyInfo = BehaviourPath
attrGet = getBehaviourPathPath
attrSet = setBehaviourPathPath
attrTransfer _ v = do
unsafeCastTo Clutter.Path.Path v
attrConstruct = constructBehaviourPathPath
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourPath.path"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourPath.html#g:attr:path"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BehaviourPath
type instance O.AttributeList BehaviourPath = BehaviourPathAttributeList
type BehaviourPathAttributeList = ('[ '("alpha", Clutter.Behaviour.BehaviourAlphaPropertyInfo), '("path", BehaviourPathPathPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
behaviourPathPath :: AttrLabelProxy "path"
behaviourPathPath = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList BehaviourPath = BehaviourPathSignalList
type BehaviourPathSignalList = ('[ '("applied", Clutter.Behaviour.BehaviourAppliedSignalInfo), '("knotReached", BehaviourPathKnotReachedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("removed", Clutter.Behaviour.BehaviourRemovedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "clutter_behaviour_path_new" clutter_behaviour_path_new ::
Ptr Clutter.Alpha.Alpha ->
Ptr Clutter.Path.Path ->
IO (Ptr BehaviourPath)
{-# DEPRECATED behaviourPathNew ["(Since version 1.6)"] #-}
behaviourPathNew ::
(B.CallStack.HasCallStack, MonadIO m, Clutter.Alpha.IsAlpha a, Clutter.Path.IsPath b) =>
Maybe (a)
-> b
-> m BehaviourPath
behaviourPathNew :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAlpha a, IsPath b) =>
Maybe a -> b -> m BehaviourPath
behaviourPathNew Maybe a
alpha b
path = IO BehaviourPath -> m BehaviourPath
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BehaviourPath -> m BehaviourPath)
-> IO BehaviourPath -> m BehaviourPath
forall a b. (a -> b) -> a -> b
$ do
Ptr Alpha
maybeAlpha <- case Maybe a
alpha of
Maybe a
Nothing -> Ptr Alpha -> IO (Ptr Alpha)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Alpha
forall a. Ptr a
nullPtr
Just a
jAlpha -> do
Ptr Alpha
jAlpha' <- a -> IO (Ptr Alpha)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jAlpha
Ptr Alpha -> IO (Ptr Alpha)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Alpha
jAlpha'
Ptr Path
path' <- b -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
path
Ptr BehaviourPath
result <- Ptr Alpha -> Ptr Path -> IO (Ptr BehaviourPath)
clutter_behaviour_path_new Ptr Alpha
maybeAlpha Ptr Path
path'
Text -> Ptr BehaviourPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"behaviourPathNew" Ptr BehaviourPath
result
BehaviourPath
result' <- ((ManagedPtr BehaviourPath -> BehaviourPath)
-> Ptr BehaviourPath -> IO BehaviourPath
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BehaviourPath -> BehaviourPath
BehaviourPath) Ptr BehaviourPath
result
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
alpha a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
path
BehaviourPath -> IO BehaviourPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BehaviourPath
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "clutter_behaviour_path_new_with_description" clutter_behaviour_path_new_with_description ::
Ptr Clutter.Alpha.Alpha ->
CString ->
IO (Ptr BehaviourPath)
{-# DEPRECATED behaviourPathNewWithDescription ["(Since version 1.6)"] #-}
behaviourPathNewWithDescription ::
(B.CallStack.HasCallStack, MonadIO m, Clutter.Alpha.IsAlpha a) =>
Maybe (a)
-> T.Text
-> m BehaviourPath
behaviourPathNewWithDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAlpha a) =>
Maybe a -> Text -> m BehaviourPath
behaviourPathNewWithDescription Maybe a
alpha Text
desc = IO BehaviourPath -> m BehaviourPath
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BehaviourPath -> m BehaviourPath)
-> IO BehaviourPath -> m BehaviourPath
forall a b. (a -> b) -> a -> b
$ do
Ptr Alpha
maybeAlpha <- case Maybe a
alpha of
Maybe a
Nothing -> Ptr Alpha -> IO (Ptr Alpha)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Alpha
forall a. Ptr a
nullPtr
Just a
jAlpha -> do
Ptr Alpha
jAlpha' <- a -> IO (Ptr Alpha)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jAlpha
Ptr Alpha -> IO (Ptr Alpha)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Alpha
jAlpha'
CString
desc' <- Text -> IO CString
textToCString Text
desc
Ptr BehaviourPath
result <- Ptr Alpha -> CString -> IO (Ptr BehaviourPath)
clutter_behaviour_path_new_with_description Ptr Alpha
maybeAlpha CString
desc'
Text -> Ptr BehaviourPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"behaviourPathNewWithDescription" Ptr BehaviourPath
result
BehaviourPath
result' <- ((ManagedPtr BehaviourPath -> BehaviourPath)
-> Ptr BehaviourPath -> IO BehaviourPath
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BehaviourPath -> BehaviourPath
BehaviourPath) Ptr BehaviourPath
result
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
alpha a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
desc'
BehaviourPath -> IO BehaviourPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BehaviourPath
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "clutter_behaviour_path_new_with_knots" clutter_behaviour_path_new_with_knots ::
Ptr Clutter.Alpha.Alpha ->
Ptr Clutter.Knot.Knot ->
Word32 ->
IO (Ptr BehaviourPath)
{-# DEPRECATED behaviourPathNewWithKnots ["(Since version 1.6)"] #-}
behaviourPathNewWithKnots ::
(B.CallStack.HasCallStack, MonadIO m, Clutter.Alpha.IsAlpha a) =>
Maybe (a)
-> [Clutter.Knot.Knot]
-> m BehaviourPath
behaviourPathNewWithKnots :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAlpha a) =>
Maybe a -> [Knot] -> m BehaviourPath
behaviourPathNewWithKnots Maybe a
alpha [Knot]
knots = IO BehaviourPath -> m BehaviourPath
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BehaviourPath -> m BehaviourPath)
-> IO BehaviourPath -> m BehaviourPath
forall a b. (a -> b) -> a -> b
$ do
let nKnots :: Word32
nKnots = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Knot] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Knot]
knots
Ptr Alpha
maybeAlpha <- case Maybe a
alpha of
Maybe a
Nothing -> Ptr Alpha -> IO (Ptr Alpha)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Alpha
forall a. Ptr a
nullPtr
Just a
jAlpha -> do
Ptr Alpha
jAlpha' <- a -> IO (Ptr Alpha)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jAlpha
Ptr Alpha -> IO (Ptr Alpha)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Alpha
jAlpha'
[Ptr Knot]
knots' <- (Knot -> IO (Ptr Knot)) -> [Knot] -> IO [Ptr Knot]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Knot -> IO (Ptr Knot)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [Knot]
knots
Ptr Knot
knots'' <- Int -> [Ptr Knot] -> IO (Ptr Knot)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
8 [Ptr Knot]
knots'
Ptr BehaviourPath
result <- Ptr Alpha -> Ptr Knot -> Word32 -> IO (Ptr BehaviourPath)
clutter_behaviour_path_new_with_knots Ptr Alpha
maybeAlpha Ptr Knot
knots'' Word32
nKnots
Text -> Ptr BehaviourPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"behaviourPathNewWithKnots" Ptr BehaviourPath
result
BehaviourPath
result' <- ((ManagedPtr BehaviourPath -> BehaviourPath)
-> Ptr BehaviourPath -> IO BehaviourPath
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BehaviourPath -> BehaviourPath
BehaviourPath) Ptr BehaviourPath
result
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
alpha a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
(Knot -> IO ()) -> [Knot] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Knot -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Knot]
knots
Ptr Knot -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Knot
knots''
BehaviourPath -> IO BehaviourPath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BehaviourPath
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "clutter_behaviour_path_get_path" clutter_behaviour_path_get_path ::
Ptr BehaviourPath ->
IO (Ptr Clutter.Path.Path)
{-# DEPRECATED behaviourPathGetPath ["(Since version 1.6)"] #-}
behaviourPathGetPath ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourPath a) =>
a
-> m Clutter.Path.Path
behaviourPathGetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourPath a) =>
a -> m Path
behaviourPathGetPath a
pathb = IO Path -> m Path
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Path -> m Path) -> IO Path -> m Path
forall a b. (a -> b) -> a -> b
$ do
Ptr BehaviourPath
pathb' <- a -> IO (Ptr BehaviourPath)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pathb
Ptr Path
result <- Ptr BehaviourPath -> IO (Ptr Path)
clutter_behaviour_path_get_path Ptr BehaviourPath
pathb'
Text -> Ptr Path -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"behaviourPathGetPath" Ptr Path
result
Path
result' <- ((ManagedPtr Path -> Path) -> Ptr Path -> IO Path
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Path -> Path
Clutter.Path.Path) Ptr Path
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pathb
Path -> IO Path
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Path
result'
#if defined(ENABLE_OVERLOADING)
data BehaviourPathGetPathMethodInfo
instance (signature ~ (m Clutter.Path.Path), MonadIO m, IsBehaviourPath a) => O.OverloadedMethod BehaviourPathGetPathMethodInfo a signature where
overloadedMethod = behaviourPathGetPath
instance O.OverloadedMethodInfo BehaviourPathGetPathMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourPath.behaviourPathGetPath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourPath.html#v:behaviourPathGetPath"
})
#endif
foreign import ccall "clutter_behaviour_path_set_path" clutter_behaviour_path_set_path ::
Ptr BehaviourPath ->
Ptr Clutter.Path.Path ->
IO ()
{-# DEPRECATED behaviourPathSetPath ["(Since version 1.6)"] #-}
behaviourPathSetPath ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourPath a, Clutter.Path.IsPath b) =>
a
-> b
-> m ()
behaviourPathSetPath :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBehaviourPath a, IsPath b) =>
a -> b -> m ()
behaviourPathSetPath a
pathb b
path = 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 BehaviourPath
pathb' <- a -> IO (Ptr BehaviourPath)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pathb
Ptr Path
path' <- b -> IO (Ptr Path)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
path
Ptr BehaviourPath -> Ptr Path -> IO ()
clutter_behaviour_path_set_path Ptr BehaviourPath
pathb' Ptr Path
path'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pathb
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
path
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BehaviourPathSetPathMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsBehaviourPath a, Clutter.Path.IsPath b) => O.OverloadedMethod BehaviourPathSetPathMethodInfo a signature where
overloadedMethod = behaviourPathSetPath
instance O.OverloadedMethodInfo BehaviourPathSetPathMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourPath.behaviourPathSetPath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourPath.html#v:behaviourPathSetPath"
})
#endif