{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Clutter.Objects.RotateAction
(
RotateAction(..) ,
IsRotateAction ,
toRotateAction ,
#if defined(ENABLE_OVERLOADING)
ResolveRotateActionMethod ,
#endif
rotateActionNew ,
RotateActionRotateCallback ,
#if defined(ENABLE_OVERLOADING)
RotateActionRotateSignalInfo ,
#endif
afterRotateActionRotate ,
onRotateActionRotate ,
) 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.FontOptions as Cairo.FontOptions
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.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.GestureAction as Clutter.GestureAction
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.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.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.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.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.GestureAction as Clutter.GestureAction
import qualified GI.GObject.Objects.Object as GObject.Object
#endif
newtype RotateAction = RotateAction (SP.ManagedPtr RotateAction)
deriving (RotateAction -> RotateAction -> Bool
(RotateAction -> RotateAction -> Bool)
-> (RotateAction -> RotateAction -> Bool) -> Eq RotateAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RotateAction -> RotateAction -> Bool
== :: RotateAction -> RotateAction -> Bool
$c/= :: RotateAction -> RotateAction -> Bool
/= :: RotateAction -> RotateAction -> Bool
Eq)
instance SP.ManagedPtrNewtype RotateAction where
toManagedPtr :: RotateAction -> ManagedPtr RotateAction
toManagedPtr (RotateAction ManagedPtr RotateAction
p) = ManagedPtr RotateAction
p
foreign import ccall "clutter_rotate_action_get_type"
c_clutter_rotate_action_get_type :: IO B.Types.GType
instance B.Types.TypedObject RotateAction where
glibType :: IO GType
glibType = IO GType
c_clutter_rotate_action_get_type
instance B.Types.GObject RotateAction
class (SP.GObject o, O.IsDescendantOf RotateAction o) => IsRotateAction o
instance (SP.GObject o, O.IsDescendantOf RotateAction o) => IsRotateAction o
instance O.HasParentTypes RotateAction
type instance O.ParentTypes RotateAction = '[Clutter.GestureAction.GestureAction, Clutter.Action.Action, Clutter.ActorMeta.ActorMeta, GObject.Object.Object]
toRotateAction :: (MIO.MonadIO m, IsRotateAction o) => o -> m RotateAction
toRotateAction :: forall (m :: * -> *) o.
(MonadIO m, IsRotateAction o) =>
o -> m RotateAction
toRotateAction = IO RotateAction -> m RotateAction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO RotateAction -> m RotateAction)
-> (o -> IO RotateAction) -> o -> m RotateAction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr RotateAction -> RotateAction) -> o -> IO RotateAction
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr RotateAction -> RotateAction
RotateAction
instance B.GValue.IsGValue (Maybe RotateAction) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_rotate_action_get_type
gvalueSet_ :: Ptr GValue -> Maybe RotateAction -> IO ()
gvalueSet_ Ptr GValue
gv Maybe RotateAction
P.Nothing = Ptr GValue -> Ptr RotateAction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr RotateAction
forall a. Ptr a
FP.nullPtr :: FP.Ptr RotateAction)
gvalueSet_ Ptr GValue
gv (P.Just RotateAction
obj) = RotateAction -> (Ptr RotateAction -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RotateAction
obj (Ptr GValue -> Ptr RotateAction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe RotateAction)
gvalueGet_ Ptr GValue
gv = do
Ptr RotateAction
ptr <- Ptr GValue -> IO (Ptr RotateAction)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr RotateAction)
if Ptr RotateAction
ptr Ptr RotateAction -> Ptr RotateAction -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr RotateAction
forall a. Ptr a
FP.nullPtr
then RotateAction -> Maybe RotateAction
forall a. a -> Maybe a
P.Just (RotateAction -> Maybe RotateAction)
-> IO RotateAction -> IO (Maybe RotateAction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr RotateAction -> RotateAction)
-> Ptr RotateAction -> IO RotateAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr RotateAction -> RotateAction
RotateAction Ptr RotateAction
ptr
else Maybe RotateAction -> IO (Maybe RotateAction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RotateAction
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveRotateActionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveRotateActionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveRotateActionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveRotateActionMethod "cancel" o = Clutter.GestureAction.GestureActionCancelMethodInfo
ResolveRotateActionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveRotateActionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveRotateActionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveRotateActionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveRotateActionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveRotateActionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveRotateActionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveRotateActionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveRotateActionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveRotateActionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveRotateActionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveRotateActionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveRotateActionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveRotateActionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveRotateActionMethod "getActor" o = Clutter.ActorMeta.ActorMetaGetActorMethodInfo
ResolveRotateActionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveRotateActionMethod "getDevice" o = Clutter.GestureAction.GestureActionGetDeviceMethodInfo
ResolveRotateActionMethod "getEnabled" o = Clutter.ActorMeta.ActorMetaGetEnabledMethodInfo
ResolveRotateActionMethod "getLastEvent" o = Clutter.GestureAction.GestureActionGetLastEventMethodInfo
ResolveRotateActionMethod "getMotionCoords" o = Clutter.GestureAction.GestureActionGetMotionCoordsMethodInfo
ResolveRotateActionMethod "getMotionDelta" o = Clutter.GestureAction.GestureActionGetMotionDeltaMethodInfo
ResolveRotateActionMethod "getNCurrentPoints" o = Clutter.GestureAction.GestureActionGetNCurrentPointsMethodInfo
ResolveRotateActionMethod "getNTouchPoints" o = Clutter.GestureAction.GestureActionGetNTouchPointsMethodInfo
ResolveRotateActionMethod "getName" o = Clutter.ActorMeta.ActorMetaGetNameMethodInfo
ResolveRotateActionMethod "getPressCoords" o = Clutter.GestureAction.GestureActionGetPressCoordsMethodInfo
ResolveRotateActionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveRotateActionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveRotateActionMethod "getReleaseCoords" o = Clutter.GestureAction.GestureActionGetReleaseCoordsMethodInfo
ResolveRotateActionMethod "getSequence" o = Clutter.GestureAction.GestureActionGetSequenceMethodInfo
ResolveRotateActionMethod "getThresholdTriggerDistance" o = Clutter.GestureAction.GestureActionGetThresholdTriggerDistanceMethodInfo
ResolveRotateActionMethod "getThresholdTriggerEdge" o = Clutter.GestureAction.GestureActionGetThresholdTriggerEdgeMethodInfo
ResolveRotateActionMethod "getThresholdTriggerEgde" o = Clutter.GestureAction.GestureActionGetThresholdTriggerEgdeMethodInfo
ResolveRotateActionMethod "getVelocity" o = Clutter.GestureAction.GestureActionGetVelocityMethodInfo
ResolveRotateActionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveRotateActionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveRotateActionMethod "setEnabled" o = Clutter.ActorMeta.ActorMetaSetEnabledMethodInfo
ResolveRotateActionMethod "setNTouchPoints" o = Clutter.GestureAction.GestureActionSetNTouchPointsMethodInfo
ResolveRotateActionMethod "setName" o = Clutter.ActorMeta.ActorMetaSetNameMethodInfo
ResolveRotateActionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveRotateActionMethod "setThresholdTriggerDistance" o = Clutter.GestureAction.GestureActionSetThresholdTriggerDistanceMethodInfo
ResolveRotateActionMethod "setThresholdTriggerEdge" o = Clutter.GestureAction.GestureActionSetThresholdTriggerEdgeMethodInfo
ResolveRotateActionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRotateActionMethod t RotateAction, O.OverloadedMethod info RotateAction p) => OL.IsLabel t (RotateAction -> 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 ~ ResolveRotateActionMethod t RotateAction, O.OverloadedMethod info RotateAction p, R.HasField t RotateAction p) => R.HasField t RotateAction p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveRotateActionMethod t RotateAction, O.OverloadedMethodInfo info RotateAction) => OL.IsLabel t (O.MethodProxy info RotateAction) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type RotateActionRotateCallback =
Clutter.Actor.Actor
-> Double
-> IO Bool
type C_RotateActionRotateCallback =
Ptr RotateAction ->
Ptr Clutter.Actor.Actor ->
CDouble ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_RotateActionRotateCallback :: C_RotateActionRotateCallback -> IO (FunPtr C_RotateActionRotateCallback)
wrap_RotateActionRotateCallback ::
GObject a => (a -> RotateActionRotateCallback) ->
C_RotateActionRotateCallback
wrap_RotateActionRotateCallback :: forall a.
GObject a =>
(a -> RotateActionRotateCallback) -> C_RotateActionRotateCallback
wrap_RotateActionRotateCallback a -> RotateActionRotateCallback
gi'cb Ptr RotateAction
gi'selfPtr Ptr Actor
actor CDouble
angle Ptr ()
_ = do
Actor
actor' <- ((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
actor
let angle' :: Double
angle' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
angle
Bool
result <- Ptr RotateAction -> (RotateAction -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr RotateAction
gi'selfPtr ((RotateAction -> IO Bool) -> IO Bool)
-> (RotateAction -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \RotateAction
gi'self -> a -> RotateActionRotateCallback
gi'cb (RotateAction -> a
forall a b. Coercible a b => a -> b
Coerce.coerce RotateAction
gi'self) Actor
actor' Double
angle'
let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
result
CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onRotateActionRotate :: (IsRotateAction a, MonadIO m) => a -> ((?self :: a) => RotateActionRotateCallback) -> m SignalHandlerId
onRotateActionRotate :: forall a (m :: * -> *).
(IsRotateAction a, MonadIO m) =>
a
-> ((?self::a) => RotateActionRotateCallback) -> m SignalHandlerId
onRotateActionRotate a
obj (?self::a) => RotateActionRotateCallback
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 -> RotateActionRotateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => RotateActionRotateCallback
RotateActionRotateCallback
cb
let wrapped' :: C_RotateActionRotateCallback
wrapped' = (a -> RotateActionRotateCallback) -> C_RotateActionRotateCallback
forall a.
GObject a =>
(a -> RotateActionRotateCallback) -> C_RotateActionRotateCallback
wrap_RotateActionRotateCallback a -> RotateActionRotateCallback
wrapped
FunPtr C_RotateActionRotateCallback
wrapped'' <- C_RotateActionRotateCallback
-> IO (FunPtr C_RotateActionRotateCallback)
mk_RotateActionRotateCallback C_RotateActionRotateCallback
wrapped'
a
-> Text
-> FunPtr C_RotateActionRotateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"rotate" FunPtr C_RotateActionRotateCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterRotateActionRotate :: (IsRotateAction a, MonadIO m) => a -> ((?self :: a) => RotateActionRotateCallback) -> m SignalHandlerId
afterRotateActionRotate :: forall a (m :: * -> *).
(IsRotateAction a, MonadIO m) =>
a
-> ((?self::a) => RotateActionRotateCallback) -> m SignalHandlerId
afterRotateActionRotate a
obj (?self::a) => RotateActionRotateCallback
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 -> RotateActionRotateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => RotateActionRotateCallback
RotateActionRotateCallback
cb
let wrapped' :: C_RotateActionRotateCallback
wrapped' = (a -> RotateActionRotateCallback) -> C_RotateActionRotateCallback
forall a.
GObject a =>
(a -> RotateActionRotateCallback) -> C_RotateActionRotateCallback
wrap_RotateActionRotateCallback a -> RotateActionRotateCallback
wrapped
FunPtr C_RotateActionRotateCallback
wrapped'' <- C_RotateActionRotateCallback
-> IO (FunPtr C_RotateActionRotateCallback)
mk_RotateActionRotateCallback C_RotateActionRotateCallback
wrapped'
a
-> Text
-> FunPtr C_RotateActionRotateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"rotate" FunPtr C_RotateActionRotateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data RotateActionRotateSignalInfo
instance SignalInfo RotateActionRotateSignalInfo where
type HaskellCallbackType RotateActionRotateSignalInfo = RotateActionRotateCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_RotateActionRotateCallback cb
cb'' <- mk_RotateActionRotateCallback cb'
connectSignalFunPtr obj "rotate" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.RotateAction::rotate"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-RotateAction.html#g:signal:rotate"})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RotateAction
type instance O.AttributeList RotateAction = RotateActionAttributeList
type RotateActionAttributeList = ('[ '("actor", Clutter.ActorMeta.ActorMetaActorPropertyInfo), '("enabled", Clutter.ActorMeta.ActorMetaEnabledPropertyInfo), '("nTouchPoints", Clutter.GestureAction.GestureActionNTouchPointsPropertyInfo), '("name", Clutter.ActorMeta.ActorMetaNamePropertyInfo), '("thresholdTriggerDistanceX", Clutter.GestureAction.GestureActionThresholdTriggerDistanceXPropertyInfo), '("thresholdTriggerDistanceY", Clutter.GestureAction.GestureActionThresholdTriggerDistanceYPropertyInfo), '("thresholdTriggerEdge", Clutter.GestureAction.GestureActionThresholdTriggerEdgePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList RotateAction = RotateActionSignalList
type RotateActionSignalList = ('[ '("gestureBegin", Clutter.GestureAction.GestureActionGestureBeginSignalInfo), '("gestureCancel", Clutter.GestureAction.GestureActionGestureCancelSignalInfo), '("gestureEnd", Clutter.GestureAction.GestureActionGestureEndSignalInfo), '("gestureProgress", Clutter.GestureAction.GestureActionGestureProgressSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("rotate", RotateActionRotateSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "clutter_rotate_action_new" clutter_rotate_action_new ::
IO (Ptr RotateAction)
rotateActionNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m RotateAction
rotateActionNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m RotateAction
rotateActionNew = IO RotateAction -> m RotateAction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RotateAction -> m RotateAction)
-> IO RotateAction -> m RotateAction
forall a b. (a -> b) -> a -> b
$ do
Ptr RotateAction
result <- IO (Ptr RotateAction)
clutter_rotate_action_new
Text -> Ptr RotateAction -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"rotateActionNew" Ptr RotateAction
result
RotateAction
result' <- ((ManagedPtr RotateAction -> RotateAction)
-> Ptr RotateAction -> IO RotateAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr RotateAction -> RotateAction
RotateAction) Ptr RotateAction
result
RotateAction -> IO RotateAction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RotateAction
result'
#if defined(ENABLE_OVERLOADING)
#endif