{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Clutter.Objects.BehaviourRotate
(
BehaviourRotate(..) ,
IsBehaviourRotate ,
toBehaviourRotate ,
#if defined(ENABLE_OVERLOADING)
ResolveBehaviourRotateMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
BehaviourRotateGetAxisMethodInfo ,
#endif
behaviourRotateGetAxis ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateGetBoundsMethodInfo ,
#endif
behaviourRotateGetBounds ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateGetCenterMethodInfo ,
#endif
behaviourRotateGetCenter ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateGetDirectionMethodInfo ,
#endif
behaviourRotateGetDirection ,
behaviourRotateNew ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateSetAxisMethodInfo ,
#endif
behaviourRotateSetAxis ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateSetBoundsMethodInfo ,
#endif
behaviourRotateSetBounds ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateSetCenterMethodInfo ,
#endif
behaviourRotateSetCenter ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateSetDirectionMethodInfo ,
#endif
behaviourRotateSetDirection ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateAngleEndPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateAngleEnd ,
#endif
constructBehaviourRotateAngleEnd ,
getBehaviourRotateAngleEnd ,
setBehaviourRotateAngleEnd ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateAngleStartPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateAngleStart ,
#endif
constructBehaviourRotateAngleStart ,
getBehaviourRotateAngleStart ,
setBehaviourRotateAngleStart ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateAxisPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateAxis ,
#endif
constructBehaviourRotateAxis ,
getBehaviourRotateAxis ,
setBehaviourRotateAxis ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateCenterXPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateCenterX ,
#endif
constructBehaviourRotateCenterX ,
getBehaviourRotateCenterX ,
setBehaviourRotateCenterX ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateCenterYPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateCenterY ,
#endif
constructBehaviourRotateCenterY ,
getBehaviourRotateCenterY ,
setBehaviourRotateCenterY ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateCenterZPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateCenterZ ,
#endif
constructBehaviourRotateCenterZ ,
getBehaviourRotateCenterZ ,
setBehaviourRotateCenterZ ,
#if defined(ENABLE_OVERLOADING)
BehaviourRotateDirectionPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateDirection ,
#endif
constructBehaviourRotateDirection ,
getBehaviourRotateDirection ,
setBehaviourRotateDirection ,
) 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.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.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.Enums as Clutter.Enums
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 qualified GI.GObject.Objects.Object as GObject.Object
#endif
newtype BehaviourRotate = BehaviourRotate (SP.ManagedPtr BehaviourRotate)
deriving (BehaviourRotate -> BehaviourRotate -> Bool
(BehaviourRotate -> BehaviourRotate -> Bool)
-> (BehaviourRotate -> BehaviourRotate -> Bool)
-> Eq BehaviourRotate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BehaviourRotate -> BehaviourRotate -> Bool
== :: BehaviourRotate -> BehaviourRotate -> Bool
$c/= :: BehaviourRotate -> BehaviourRotate -> Bool
/= :: BehaviourRotate -> BehaviourRotate -> Bool
Eq)
instance SP.ManagedPtrNewtype BehaviourRotate where
toManagedPtr :: BehaviourRotate -> ManagedPtr BehaviourRotate
toManagedPtr (BehaviourRotate ManagedPtr BehaviourRotate
p) = ManagedPtr BehaviourRotate
p
foreign import ccall "clutter_behaviour_rotate_get_type"
c_clutter_behaviour_rotate_get_type :: IO B.Types.GType
instance B.Types.TypedObject BehaviourRotate where
glibType :: IO GType
glibType = IO GType
c_clutter_behaviour_rotate_get_type
instance B.Types.GObject BehaviourRotate
class (SP.GObject o, O.IsDescendantOf BehaviourRotate o) => IsBehaviourRotate o
instance (SP.GObject o, O.IsDescendantOf BehaviourRotate o) => IsBehaviourRotate o
instance O.HasParentTypes BehaviourRotate
type instance O.ParentTypes BehaviourRotate = '[Clutter.Behaviour.Behaviour, GObject.Object.Object, Clutter.Scriptable.Scriptable]
toBehaviourRotate :: (MIO.MonadIO m, IsBehaviourRotate o) => o -> m BehaviourRotate
toBehaviourRotate :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m BehaviourRotate
toBehaviourRotate = IO BehaviourRotate -> m BehaviourRotate
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO BehaviourRotate -> m BehaviourRotate)
-> (o -> IO BehaviourRotate) -> o -> m BehaviourRotate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr BehaviourRotate -> BehaviourRotate)
-> o -> IO BehaviourRotate
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr BehaviourRotate -> BehaviourRotate
BehaviourRotate
instance B.GValue.IsGValue (Maybe BehaviourRotate) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_behaviour_rotate_get_type
gvalueSet_ :: Ptr GValue -> Maybe BehaviourRotate -> IO ()
gvalueSet_ Ptr GValue
gv Maybe BehaviourRotate
P.Nothing = Ptr GValue -> Ptr BehaviourRotate -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr BehaviourRotate
forall a. Ptr a
FP.nullPtr :: FP.Ptr BehaviourRotate)
gvalueSet_ Ptr GValue
gv (P.Just BehaviourRotate
obj) = BehaviourRotate -> (Ptr BehaviourRotate -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BehaviourRotate
obj (Ptr GValue -> Ptr BehaviourRotate -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe BehaviourRotate)
gvalueGet_ Ptr GValue
gv = do
Ptr BehaviourRotate
ptr <- Ptr GValue -> IO (Ptr BehaviourRotate)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr BehaviourRotate)
if Ptr BehaviourRotate
ptr Ptr BehaviourRotate -> Ptr BehaviourRotate -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr BehaviourRotate
forall a. Ptr a
FP.nullPtr
then BehaviourRotate -> Maybe BehaviourRotate
forall a. a -> Maybe a
P.Just (BehaviourRotate -> Maybe BehaviourRotate)
-> IO BehaviourRotate -> IO (Maybe BehaviourRotate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr BehaviourRotate -> BehaviourRotate)
-> Ptr BehaviourRotate -> IO BehaviourRotate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr BehaviourRotate -> BehaviourRotate
BehaviourRotate Ptr BehaviourRotate
ptr
else Maybe BehaviourRotate -> IO (Maybe BehaviourRotate)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BehaviourRotate
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveBehaviourRotateMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveBehaviourRotateMethod "actorsForeach" o = Clutter.Behaviour.BehaviourActorsForeachMethodInfo
ResolveBehaviourRotateMethod "apply" o = Clutter.Behaviour.BehaviourApplyMethodInfo
ResolveBehaviourRotateMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveBehaviourRotateMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveBehaviourRotateMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveBehaviourRotateMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveBehaviourRotateMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveBehaviourRotateMethod "isApplied" o = Clutter.Behaviour.BehaviourIsAppliedMethodInfo
ResolveBehaviourRotateMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveBehaviourRotateMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveBehaviourRotateMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveBehaviourRotateMethod "parseCustomNode" o = Clutter.Scriptable.ScriptableParseCustomNodeMethodInfo
ResolveBehaviourRotateMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveBehaviourRotateMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveBehaviourRotateMethod "remove" o = Clutter.Behaviour.BehaviourRemoveMethodInfo
ResolveBehaviourRotateMethod "removeAll" o = Clutter.Behaviour.BehaviourRemoveAllMethodInfo
ResolveBehaviourRotateMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveBehaviourRotateMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveBehaviourRotateMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveBehaviourRotateMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveBehaviourRotateMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveBehaviourRotateMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveBehaviourRotateMethod "getActors" o = Clutter.Behaviour.BehaviourGetActorsMethodInfo
ResolveBehaviourRotateMethod "getAlpha" o = Clutter.Behaviour.BehaviourGetAlphaMethodInfo
ResolveBehaviourRotateMethod "getAxis" o = BehaviourRotateGetAxisMethodInfo
ResolveBehaviourRotateMethod "getBounds" o = BehaviourRotateGetBoundsMethodInfo
ResolveBehaviourRotateMethod "getCenter" o = BehaviourRotateGetCenterMethodInfo
ResolveBehaviourRotateMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveBehaviourRotateMethod "getDirection" o = BehaviourRotateGetDirectionMethodInfo
ResolveBehaviourRotateMethod "getId" o = Clutter.Scriptable.ScriptableGetIdMethodInfo
ResolveBehaviourRotateMethod "getNActors" o = Clutter.Behaviour.BehaviourGetNActorsMethodInfo
ResolveBehaviourRotateMethod "getNthActor" o = Clutter.Behaviour.BehaviourGetNthActorMethodInfo
ResolveBehaviourRotateMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveBehaviourRotateMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveBehaviourRotateMethod "setAlpha" o = Clutter.Behaviour.BehaviourSetAlphaMethodInfo
ResolveBehaviourRotateMethod "setAxis" o = BehaviourRotateSetAxisMethodInfo
ResolveBehaviourRotateMethod "setBounds" o = BehaviourRotateSetBoundsMethodInfo
ResolveBehaviourRotateMethod "setCenter" o = BehaviourRotateSetCenterMethodInfo
ResolveBehaviourRotateMethod "setCustomProperty" o = Clutter.Scriptable.ScriptableSetCustomPropertyMethodInfo
ResolveBehaviourRotateMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveBehaviourRotateMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveBehaviourRotateMethod "setDirection" o = BehaviourRotateSetDirectionMethodInfo
ResolveBehaviourRotateMethod "setId" o = Clutter.Scriptable.ScriptableSetIdMethodInfo
ResolveBehaviourRotateMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveBehaviourRotateMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveBehaviourRotateMethod t BehaviourRotate, O.OverloadedMethod info BehaviourRotate p) => OL.IsLabel t (BehaviourRotate -> 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 ~ ResolveBehaviourRotateMethod t BehaviourRotate, O.OverloadedMethod info BehaviourRotate p, R.HasField t BehaviourRotate p) => R.HasField t BehaviourRotate p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveBehaviourRotateMethod t BehaviourRotate, O.OverloadedMethodInfo info BehaviourRotate) => OL.IsLabel t (O.MethodProxy info BehaviourRotate) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getBehaviourRotateAngleEnd :: (MonadIO m, IsBehaviourRotate o) => o -> m Double
getBehaviourRotateAngleEnd :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m Double
getBehaviourRotateAngleEnd o
obj = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Double
forall a. GObject a => a -> String -> IO Double
B.Properties.getObjectPropertyDouble o
obj String
"angle-end"
setBehaviourRotateAngleEnd :: (MonadIO m, IsBehaviourRotate o) => o -> Double -> m ()
setBehaviourRotateAngleEnd :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> Double -> m ()
setBehaviourRotateAngleEnd o
obj Double
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 -> Double -> IO ()
forall a. GObject a => a -> String -> Double -> IO ()
B.Properties.setObjectPropertyDouble o
obj String
"angle-end" Double
val
constructBehaviourRotateAngleEnd :: (IsBehaviourRotate o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructBehaviourRotateAngleEnd :: forall o (m :: * -> *).
(IsBehaviourRotate o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructBehaviourRotateAngleEnd Double
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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"angle-end" Double
val
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateAngleEndPropertyInfo
instance AttrInfo BehaviourRotateAngleEndPropertyInfo where
type AttrAllowedOps BehaviourRotateAngleEndPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourRotateAngleEndPropertyInfo = IsBehaviourRotate
type AttrSetTypeConstraint BehaviourRotateAngleEndPropertyInfo = (~) Double
type AttrTransferTypeConstraint BehaviourRotateAngleEndPropertyInfo = (~) Double
type AttrTransferType BehaviourRotateAngleEndPropertyInfo = Double
type AttrGetType BehaviourRotateAngleEndPropertyInfo = Double
type AttrLabel BehaviourRotateAngleEndPropertyInfo = "angle-end"
type AttrOrigin BehaviourRotateAngleEndPropertyInfo = BehaviourRotate
attrGet = getBehaviourRotateAngleEnd
attrSet = setBehaviourRotateAngleEnd
attrTransfer _ v = do
return v
attrConstruct = constructBehaviourRotateAngleEnd
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.angleEnd"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#g:attr:angleEnd"
})
#endif
getBehaviourRotateAngleStart :: (MonadIO m, IsBehaviourRotate o) => o -> m Double
getBehaviourRotateAngleStart :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m Double
getBehaviourRotateAngleStart o
obj = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Double
forall a. GObject a => a -> String -> IO Double
B.Properties.getObjectPropertyDouble o
obj String
"angle-start"
setBehaviourRotateAngleStart :: (MonadIO m, IsBehaviourRotate o) => o -> Double -> m ()
setBehaviourRotateAngleStart :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> Double -> m ()
setBehaviourRotateAngleStart o
obj Double
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 -> Double -> IO ()
forall a. GObject a => a -> String -> Double -> IO ()
B.Properties.setObjectPropertyDouble o
obj String
"angle-start" Double
val
constructBehaviourRotateAngleStart :: (IsBehaviourRotate o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructBehaviourRotateAngleStart :: forall o (m :: * -> *).
(IsBehaviourRotate o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructBehaviourRotateAngleStart Double
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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"angle-start" Double
val
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateAngleStartPropertyInfo
instance AttrInfo BehaviourRotateAngleStartPropertyInfo where
type AttrAllowedOps BehaviourRotateAngleStartPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourRotateAngleStartPropertyInfo = IsBehaviourRotate
type AttrSetTypeConstraint BehaviourRotateAngleStartPropertyInfo = (~) Double
type AttrTransferTypeConstraint BehaviourRotateAngleStartPropertyInfo = (~) Double
type AttrTransferType BehaviourRotateAngleStartPropertyInfo = Double
type AttrGetType BehaviourRotateAngleStartPropertyInfo = Double
type AttrLabel BehaviourRotateAngleStartPropertyInfo = "angle-start"
type AttrOrigin BehaviourRotateAngleStartPropertyInfo = BehaviourRotate
attrGet = getBehaviourRotateAngleStart
attrSet = setBehaviourRotateAngleStart
attrTransfer _ v = do
return v
attrConstruct = constructBehaviourRotateAngleStart
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.angleStart"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#g:attr:angleStart"
})
#endif
getBehaviourRotateAxis :: (MonadIO m, IsBehaviourRotate o) => o -> m Clutter.Enums.RotateAxis
getBehaviourRotateAxis :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m RotateAxis
getBehaviourRotateAxis o
obj = IO RotateAxis -> m RotateAxis
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO RotateAxis -> m RotateAxis) -> IO RotateAxis -> m RotateAxis
forall a b. (a -> b) -> a -> b
$ o -> String -> IO RotateAxis
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"axis"
setBehaviourRotateAxis :: (MonadIO m, IsBehaviourRotate o) => o -> Clutter.Enums.RotateAxis -> m ()
setBehaviourRotateAxis :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> RotateAxis -> m ()
setBehaviourRotateAxis o
obj RotateAxis
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 -> RotateAxis -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"axis" RotateAxis
val
constructBehaviourRotateAxis :: (IsBehaviourRotate o, MIO.MonadIO m) => Clutter.Enums.RotateAxis -> m (GValueConstruct o)
constructBehaviourRotateAxis :: forall o (m :: * -> *).
(IsBehaviourRotate o, MonadIO m) =>
RotateAxis -> m (GValueConstruct o)
constructBehaviourRotateAxis RotateAxis
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 -> RotateAxis -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"axis" RotateAxis
val
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateAxisPropertyInfo
instance AttrInfo BehaviourRotateAxisPropertyInfo where
type AttrAllowedOps BehaviourRotateAxisPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourRotateAxisPropertyInfo = IsBehaviourRotate
type AttrSetTypeConstraint BehaviourRotateAxisPropertyInfo = (~) Clutter.Enums.RotateAxis
type AttrTransferTypeConstraint BehaviourRotateAxisPropertyInfo = (~) Clutter.Enums.RotateAxis
type AttrTransferType BehaviourRotateAxisPropertyInfo = Clutter.Enums.RotateAxis
type AttrGetType BehaviourRotateAxisPropertyInfo = Clutter.Enums.RotateAxis
type AttrLabel BehaviourRotateAxisPropertyInfo = "axis"
type AttrOrigin BehaviourRotateAxisPropertyInfo = BehaviourRotate
attrGet = getBehaviourRotateAxis
attrSet = setBehaviourRotateAxis
attrTransfer _ v = do
return v
attrConstruct = constructBehaviourRotateAxis
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.axis"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#g:attr:axis"
})
#endif
getBehaviourRotateCenterX :: (MonadIO m, IsBehaviourRotate o) => o -> m Int32
getBehaviourRotateCenterX :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m Int32
getBehaviourRotateCenterX o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"center-x"
setBehaviourRotateCenterX :: (MonadIO m, IsBehaviourRotate o) => o -> Int32 -> m ()
setBehaviourRotateCenterX :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> Int32 -> m ()
setBehaviourRotateCenterX o
obj Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"center-x" Int32
val
constructBehaviourRotateCenterX :: (IsBehaviourRotate o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructBehaviourRotateCenterX :: forall o (m :: * -> *).
(IsBehaviourRotate o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructBehaviourRotateCenterX Int32
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"center-x" Int32
val
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateCenterXPropertyInfo
instance AttrInfo BehaviourRotateCenterXPropertyInfo where
type AttrAllowedOps BehaviourRotateCenterXPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourRotateCenterXPropertyInfo = IsBehaviourRotate
type AttrSetTypeConstraint BehaviourRotateCenterXPropertyInfo = (~) Int32
type AttrTransferTypeConstraint BehaviourRotateCenterXPropertyInfo = (~) Int32
type AttrTransferType BehaviourRotateCenterXPropertyInfo = Int32
type AttrGetType BehaviourRotateCenterXPropertyInfo = Int32
type AttrLabel BehaviourRotateCenterXPropertyInfo = "center-x"
type AttrOrigin BehaviourRotateCenterXPropertyInfo = BehaviourRotate
attrGet = getBehaviourRotateCenterX
attrSet = setBehaviourRotateCenterX
attrTransfer _ v = do
return v
attrConstruct = constructBehaviourRotateCenterX
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.centerX"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#g:attr:centerX"
})
#endif
getBehaviourRotateCenterY :: (MonadIO m, IsBehaviourRotate o) => o -> m Int32
getBehaviourRotateCenterY :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m Int32
getBehaviourRotateCenterY o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"center-y"
setBehaviourRotateCenterY :: (MonadIO m, IsBehaviourRotate o) => o -> Int32 -> m ()
setBehaviourRotateCenterY :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> Int32 -> m ()
setBehaviourRotateCenterY o
obj Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"center-y" Int32
val
constructBehaviourRotateCenterY :: (IsBehaviourRotate o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructBehaviourRotateCenterY :: forall o (m :: * -> *).
(IsBehaviourRotate o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructBehaviourRotateCenterY Int32
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"center-y" Int32
val
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateCenterYPropertyInfo
instance AttrInfo BehaviourRotateCenterYPropertyInfo where
type AttrAllowedOps BehaviourRotateCenterYPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourRotateCenterYPropertyInfo = IsBehaviourRotate
type AttrSetTypeConstraint BehaviourRotateCenterYPropertyInfo = (~) Int32
type AttrTransferTypeConstraint BehaviourRotateCenterYPropertyInfo = (~) Int32
type AttrTransferType BehaviourRotateCenterYPropertyInfo = Int32
type AttrGetType BehaviourRotateCenterYPropertyInfo = Int32
type AttrLabel BehaviourRotateCenterYPropertyInfo = "center-y"
type AttrOrigin BehaviourRotateCenterYPropertyInfo = BehaviourRotate
attrGet = getBehaviourRotateCenterY
attrSet = setBehaviourRotateCenterY
attrTransfer _ v = do
return v
attrConstruct = constructBehaviourRotateCenterY
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.centerY"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#g:attr:centerY"
})
#endif
getBehaviourRotateCenterZ :: (MonadIO m, IsBehaviourRotate o) => o -> m Int32
getBehaviourRotateCenterZ :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m Int32
getBehaviourRotateCenterZ o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"center-z"
setBehaviourRotateCenterZ :: (MonadIO m, IsBehaviourRotate o) => o -> Int32 -> m ()
setBehaviourRotateCenterZ :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> Int32 -> m ()
setBehaviourRotateCenterZ o
obj Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"center-z" Int32
val
constructBehaviourRotateCenterZ :: (IsBehaviourRotate o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructBehaviourRotateCenterZ :: forall o (m :: * -> *).
(IsBehaviourRotate o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructBehaviourRotateCenterZ Int32
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"center-z" Int32
val
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateCenterZPropertyInfo
instance AttrInfo BehaviourRotateCenterZPropertyInfo where
type AttrAllowedOps BehaviourRotateCenterZPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourRotateCenterZPropertyInfo = IsBehaviourRotate
type AttrSetTypeConstraint BehaviourRotateCenterZPropertyInfo = (~) Int32
type AttrTransferTypeConstraint BehaviourRotateCenterZPropertyInfo = (~) Int32
type AttrTransferType BehaviourRotateCenterZPropertyInfo = Int32
type AttrGetType BehaviourRotateCenterZPropertyInfo = Int32
type AttrLabel BehaviourRotateCenterZPropertyInfo = "center-z"
type AttrOrigin BehaviourRotateCenterZPropertyInfo = BehaviourRotate
attrGet = getBehaviourRotateCenterZ
attrSet = setBehaviourRotateCenterZ
attrTransfer _ v = do
return v
attrConstruct = constructBehaviourRotateCenterZ
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.centerZ"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#g:attr:centerZ"
})
#endif
getBehaviourRotateDirection :: (MonadIO m, IsBehaviourRotate o) => o -> m Clutter.Enums.RotateDirection
getBehaviourRotateDirection :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> m RotateDirection
getBehaviourRotateDirection o
obj = IO RotateDirection -> m RotateDirection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO RotateDirection -> m RotateDirection)
-> IO RotateDirection -> m RotateDirection
forall a b. (a -> b) -> a -> b
$ o -> String -> IO RotateDirection
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"direction"
setBehaviourRotateDirection :: (MonadIO m, IsBehaviourRotate o) => o -> Clutter.Enums.RotateDirection -> m ()
setBehaviourRotateDirection :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourRotate o) =>
o -> RotateDirection -> m ()
setBehaviourRotateDirection o
obj RotateDirection
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 -> RotateDirection -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"direction" RotateDirection
val
constructBehaviourRotateDirection :: (IsBehaviourRotate o, MIO.MonadIO m) => Clutter.Enums.RotateDirection -> m (GValueConstruct o)
constructBehaviourRotateDirection :: forall o (m :: * -> *).
(IsBehaviourRotate o, MonadIO m) =>
RotateDirection -> m (GValueConstruct o)
constructBehaviourRotateDirection RotateDirection
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 -> RotateDirection -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"direction" RotateDirection
val
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateDirectionPropertyInfo
instance AttrInfo BehaviourRotateDirectionPropertyInfo where
type AttrAllowedOps BehaviourRotateDirectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint BehaviourRotateDirectionPropertyInfo = IsBehaviourRotate
type AttrSetTypeConstraint BehaviourRotateDirectionPropertyInfo = (~) Clutter.Enums.RotateDirection
type AttrTransferTypeConstraint BehaviourRotateDirectionPropertyInfo = (~) Clutter.Enums.RotateDirection
type AttrTransferType BehaviourRotateDirectionPropertyInfo = Clutter.Enums.RotateDirection
type AttrGetType BehaviourRotateDirectionPropertyInfo = Clutter.Enums.RotateDirection
type AttrLabel BehaviourRotateDirectionPropertyInfo = "direction"
type AttrOrigin BehaviourRotateDirectionPropertyInfo = BehaviourRotate
attrGet = getBehaviourRotateDirection
attrSet = setBehaviourRotateDirection
attrTransfer _ v = do
return v
attrConstruct = constructBehaviourRotateDirection
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.direction"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#g:attr:direction"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BehaviourRotate
type instance O.AttributeList BehaviourRotate = BehaviourRotateAttributeList
type BehaviourRotateAttributeList = ('[ '("alpha", Clutter.Behaviour.BehaviourAlphaPropertyInfo), '("angleEnd", BehaviourRotateAngleEndPropertyInfo), '("angleStart", BehaviourRotateAngleStartPropertyInfo), '("axis", BehaviourRotateAxisPropertyInfo), '("centerX", BehaviourRotateCenterXPropertyInfo), '("centerY", BehaviourRotateCenterYPropertyInfo), '("centerZ", BehaviourRotateCenterZPropertyInfo), '("direction", BehaviourRotateDirectionPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
behaviourRotateAngleEnd :: AttrLabelProxy "angleEnd"
behaviourRotateAngleEnd = AttrLabelProxy
behaviourRotateAngleStart :: AttrLabelProxy "angleStart"
behaviourRotateAngleStart = AttrLabelProxy
behaviourRotateAxis :: AttrLabelProxy "axis"
behaviourRotateAxis = AttrLabelProxy
behaviourRotateCenterX :: AttrLabelProxy "centerX"
behaviourRotateCenterX = AttrLabelProxy
behaviourRotateCenterY :: AttrLabelProxy "centerY"
behaviourRotateCenterY = AttrLabelProxy
behaviourRotateCenterZ :: AttrLabelProxy "centerZ"
behaviourRotateCenterZ = AttrLabelProxy
behaviourRotateDirection :: AttrLabelProxy "direction"
behaviourRotateDirection = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList BehaviourRotate = BehaviourRotateSignalList
type BehaviourRotateSignalList = ('[ '("applied", Clutter.Behaviour.BehaviourAppliedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("removed", Clutter.Behaviour.BehaviourRemovedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "clutter_behaviour_rotate_new" clutter_behaviour_rotate_new ::
Ptr Clutter.Alpha.Alpha ->
CUInt ->
CUInt ->
CDouble ->
CDouble ->
IO (Ptr BehaviourRotate)
behaviourRotateNew ::
(B.CallStack.HasCallStack, MonadIO m, Clutter.Alpha.IsAlpha a) =>
Maybe (a)
-> Clutter.Enums.RotateAxis
-> Clutter.Enums.RotateDirection
-> Double
-> Double
-> m BehaviourRotate
behaviourRotateNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAlpha a) =>
Maybe a
-> RotateAxis
-> RotateDirection
-> Double
-> Double
-> m BehaviourRotate
behaviourRotateNew Maybe a
alpha RotateAxis
axis RotateDirection
direction Double
angleStart Double
angleEnd = IO BehaviourRotate -> m BehaviourRotate
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BehaviourRotate -> m BehaviourRotate)
-> IO BehaviourRotate -> m BehaviourRotate
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'
let axis' :: CUInt
axis' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RotateAxis -> Int) -> RotateAxis -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RotateAxis -> Int
forall a. Enum a => a -> Int
fromEnum) RotateAxis
axis
let direction' :: CUInt
direction' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (RotateDirection -> Int) -> RotateDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RotateDirection -> Int
forall a. Enum a => a -> Int
fromEnum) RotateDirection
direction
let angleStart' :: CDouble
angleStart' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleStart
let angleEnd' :: CDouble
angleEnd' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleEnd
Ptr BehaviourRotate
result <- Ptr Alpha
-> CUInt -> CUInt -> CDouble -> CDouble -> IO (Ptr BehaviourRotate)
clutter_behaviour_rotate_new Ptr Alpha
maybeAlpha CUInt
axis' CUInt
direction' CDouble
angleStart' CDouble
angleEnd'
Text -> Ptr BehaviourRotate -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"behaviourRotateNew" Ptr BehaviourRotate
result
BehaviourRotate
result' <- ((ManagedPtr BehaviourRotate -> BehaviourRotate)
-> Ptr BehaviourRotate -> IO BehaviourRotate
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BehaviourRotate -> BehaviourRotate
BehaviourRotate) Ptr BehaviourRotate
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
BehaviourRotate -> IO BehaviourRotate
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BehaviourRotate
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "clutter_behaviour_rotate_get_axis" clutter_behaviour_rotate_get_axis ::
Ptr BehaviourRotate ->
IO CUInt
behaviourRotateGetAxis ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> m Clutter.Enums.RotateAxis
behaviourRotateGetAxis :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> m RotateAxis
behaviourRotateGetAxis a
rotate = IO RotateAxis -> m RotateAxis
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RotateAxis -> m RotateAxis) -> IO RotateAxis -> m RotateAxis
forall a b. (a -> b) -> a -> b
$ do
Ptr BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
CUInt
result <- Ptr BehaviourRotate -> IO CUInt
clutter_behaviour_rotate_get_axis Ptr BehaviourRotate
rotate'
let result' :: RotateAxis
result' = (Int -> RotateAxis
forall a. Enum a => Int -> a
toEnum (Int -> RotateAxis) -> (CUInt -> Int) -> CUInt -> RotateAxis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
RotateAxis -> IO RotateAxis
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RotateAxis
result'
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateGetAxisMethodInfo
instance (signature ~ (m Clutter.Enums.RotateAxis), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateGetAxisMethodInfo a signature where
overloadedMethod = behaviourRotateGetAxis
instance O.OverloadedMethodInfo BehaviourRotateGetAxisMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateGetAxis",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateGetAxis"
})
#endif
foreign import ccall "clutter_behaviour_rotate_get_bounds" clutter_behaviour_rotate_get_bounds ::
Ptr BehaviourRotate ->
Ptr CDouble ->
Ptr CDouble ->
IO ()
behaviourRotateGetBounds ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> m ((Double, Double))
behaviourRotateGetBounds :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> m (Double, Double)
behaviourRotateGetBounds a
rotate = IO (Double, Double) -> m (Double, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Double) -> m (Double, Double))
-> IO (Double, Double) -> m (Double, Double)
forall a b. (a -> b) -> a -> b
$ do
Ptr BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
Ptr CDouble
angleStart <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
Ptr CDouble
angleEnd <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
Ptr BehaviourRotate -> Ptr CDouble -> Ptr CDouble -> IO ()
clutter_behaviour_rotate_get_bounds Ptr BehaviourRotate
rotate' Ptr CDouble
angleStart Ptr CDouble
angleEnd
CDouble
angleStart' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
angleStart
let angleStart'' :: Double
angleStart'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
angleStart'
CDouble
angleEnd' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
angleEnd
let angleEnd'' :: Double
angleEnd'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
angleEnd'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
angleStart
Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
angleEnd
(Double, Double) -> IO (Double, Double)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
angleStart'', Double
angleEnd'')
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateGetBoundsMethodInfo
instance (signature ~ (m ((Double, Double))), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateGetBoundsMethodInfo a signature where
overloadedMethod = behaviourRotateGetBounds
instance O.OverloadedMethodInfo BehaviourRotateGetBoundsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateGetBounds",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateGetBounds"
})
#endif
foreign import ccall "clutter_behaviour_rotate_get_center" clutter_behaviour_rotate_get_center ::
Ptr BehaviourRotate ->
Ptr Int32 ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
behaviourRotateGetCenter ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> m ((Int32, Int32, Int32))
behaviourRotateGetCenter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> m (Int32, Int32, Int32)
behaviourRotateGetCenter a
rotate = IO (Int32, Int32, Int32) -> m (Int32, Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32, Int32) -> m (Int32, Int32, Int32))
-> IO (Int32, Int32, Int32) -> m (Int32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
Ptr BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
Ptr Int32
x <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32
z <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr BehaviourRotate -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> IO ()
clutter_behaviour_rotate_get_center Ptr BehaviourRotate
rotate' Ptr Int32
x Ptr Int32
y Ptr Int32
z
Int32
x' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
x
Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
Int32
z' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
z
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
x
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
z
(Int32, Int32, Int32) -> IO (Int32, Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
x', Int32
y', Int32
z')
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateGetCenterMethodInfo
instance (signature ~ (m ((Int32, Int32, Int32))), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateGetCenterMethodInfo a signature where
overloadedMethod = behaviourRotateGetCenter
instance O.OverloadedMethodInfo BehaviourRotateGetCenterMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateGetCenter",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateGetCenter"
})
#endif
foreign import ccall "clutter_behaviour_rotate_get_direction" clutter_behaviour_rotate_get_direction ::
Ptr BehaviourRotate ->
IO CUInt
behaviourRotateGetDirection ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> m Clutter.Enums.RotateDirection
behaviourRotateGetDirection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> m RotateDirection
behaviourRotateGetDirection a
rotate = IO RotateDirection -> m RotateDirection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RotateDirection -> m RotateDirection)
-> IO RotateDirection -> m RotateDirection
forall a b. (a -> b) -> a -> b
$ do
Ptr BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
CUInt
result <- Ptr BehaviourRotate -> IO CUInt
clutter_behaviour_rotate_get_direction Ptr BehaviourRotate
rotate'
let result' :: RotateDirection
result' = (Int -> RotateDirection
forall a. Enum a => Int -> a
toEnum (Int -> RotateDirection)
-> (CUInt -> Int) -> CUInt -> RotateDirection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
RotateDirection -> IO RotateDirection
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RotateDirection
result'
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateGetDirectionMethodInfo
instance (signature ~ (m Clutter.Enums.RotateDirection), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateGetDirectionMethodInfo a signature where
overloadedMethod = behaviourRotateGetDirection
instance O.OverloadedMethodInfo BehaviourRotateGetDirectionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateGetDirection",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateGetDirection"
})
#endif
foreign import ccall "clutter_behaviour_rotate_set_axis" clutter_behaviour_rotate_set_axis ::
Ptr BehaviourRotate ->
CUInt ->
IO ()
behaviourRotateSetAxis ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> Clutter.Enums.RotateAxis
-> m ()
behaviourRotateSetAxis :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> RotateAxis -> m ()
behaviourRotateSetAxis a
rotate RotateAxis
axis = 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 BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
let axis' :: CUInt
axis' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RotateAxis -> Int) -> RotateAxis -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RotateAxis -> Int
forall a. Enum a => a -> Int
fromEnum) RotateAxis
axis
Ptr BehaviourRotate -> CUInt -> IO ()
clutter_behaviour_rotate_set_axis Ptr BehaviourRotate
rotate' CUInt
axis'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateSetAxisMethodInfo
instance (signature ~ (Clutter.Enums.RotateAxis -> m ()), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateSetAxisMethodInfo a signature where
overloadedMethod = behaviourRotateSetAxis
instance O.OverloadedMethodInfo BehaviourRotateSetAxisMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateSetAxis",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateSetAxis"
})
#endif
foreign import ccall "clutter_behaviour_rotate_set_bounds" clutter_behaviour_rotate_set_bounds ::
Ptr BehaviourRotate ->
CDouble ->
CDouble ->
IO ()
behaviourRotateSetBounds ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> Double
-> Double
-> m ()
behaviourRotateSetBounds :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> Double -> Double -> m ()
behaviourRotateSetBounds a
rotate Double
angleStart Double
angleEnd = 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 BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
let angleStart' :: CDouble
angleStart' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleStart
let angleEnd' :: CDouble
angleEnd' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleEnd
Ptr BehaviourRotate -> CDouble -> CDouble -> IO ()
clutter_behaviour_rotate_set_bounds Ptr BehaviourRotate
rotate' CDouble
angleStart' CDouble
angleEnd'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateSetBoundsMethodInfo
instance (signature ~ (Double -> Double -> m ()), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateSetBoundsMethodInfo a signature where
overloadedMethod = behaviourRotateSetBounds
instance O.OverloadedMethodInfo BehaviourRotateSetBoundsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateSetBounds",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateSetBounds"
})
#endif
foreign import ccall "clutter_behaviour_rotate_set_center" clutter_behaviour_rotate_set_center ::
Ptr BehaviourRotate ->
Int32 ->
Int32 ->
Int32 ->
IO ()
behaviourRotateSetCenter ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> Int32
-> Int32
-> Int32
-> m ()
behaviourRotateSetCenter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> Int32 -> Int32 -> Int32 -> m ()
behaviourRotateSetCenter a
rotate Int32
x Int32
y Int32
z = 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 BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
Ptr BehaviourRotate -> Int32 -> Int32 -> Int32 -> IO ()
clutter_behaviour_rotate_set_center Ptr BehaviourRotate
rotate' Int32
x Int32
y Int32
z
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateSetCenterMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateSetCenterMethodInfo a signature where
overloadedMethod = behaviourRotateSetCenter
instance O.OverloadedMethodInfo BehaviourRotateSetCenterMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateSetCenter",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateSetCenter"
})
#endif
foreign import ccall "clutter_behaviour_rotate_set_direction" clutter_behaviour_rotate_set_direction ::
Ptr BehaviourRotate ->
CUInt ->
IO ()
behaviourRotateSetDirection ::
(B.CallStack.HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a
-> Clutter.Enums.RotateDirection
-> m ()
behaviourRotateSetDirection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourRotate a) =>
a -> RotateDirection -> m ()
behaviourRotateSetDirection a
rotate RotateDirection
direction = 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 BehaviourRotate
rotate' <- a -> IO (Ptr BehaviourRotate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
rotate
let direction' :: CUInt
direction' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (RotateDirection -> Int) -> RotateDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RotateDirection -> Int
forall a. Enum a => a -> Int
fromEnum) RotateDirection
direction
Ptr BehaviourRotate -> CUInt -> IO ()
clutter_behaviour_rotate_set_direction Ptr BehaviourRotate
rotate' CUInt
direction'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
rotate
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BehaviourRotateSetDirectionMethodInfo
instance (signature ~ (Clutter.Enums.RotateDirection -> m ()), MonadIO m, IsBehaviourRotate a) => O.OverloadedMethod BehaviourRotateSetDirectionMethodInfo a signature where
overloadedMethod = behaviourRotateSetDirection
instance O.OverloadedMethodInfo BehaviourRotateSetDirectionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourRotate.behaviourRotateSetDirection",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-BehaviourRotate.html#v:behaviourRotateSetDirection"
})
#endif