{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse' struct contains only private data
-- and should be accessed using the provided API
-- 
-- /Since: 0.4/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Clutter.Objects.BehaviourEllipse
    ( 

-- * Exported types
    BehaviourEllipse(..)                    ,
    IsBehaviourEllipse                      ,
    toBehaviourEllipse                      ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actorsForeach]("GI.Clutter.Objects.Behaviour#g:method:actorsForeach"), [apply]("GI.Clutter.Objects.Behaviour#g:method:apply"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isApplied]("GI.Clutter.Objects.Behaviour#g:method:isApplied"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [parseCustomNode]("GI.Clutter.Interfaces.Scriptable#g:method:parseCustomNode"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [remove]("GI.Clutter.Objects.Behaviour#g:method:remove"), [removeAll]("GI.Clutter.Objects.Behaviour#g:method:removeAll"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getActors]("GI.Clutter.Objects.Behaviour#g:method:getActors"), [getAlpha]("GI.Clutter.Objects.Behaviour#g:method:getAlpha"), [getAngleEnd]("GI.Clutter.Objects.BehaviourEllipse#g:method:getAngleEnd"), [getAngleStart]("GI.Clutter.Objects.BehaviourEllipse#g:method:getAngleStart"), [getAngleTilt]("GI.Clutter.Objects.BehaviourEllipse#g:method:getAngleTilt"), [getCenter]("GI.Clutter.Objects.BehaviourEllipse#g:method:getCenter"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Clutter.Objects.BehaviourEllipse#g:method:getDirection"), [getHeight]("GI.Clutter.Objects.BehaviourEllipse#g:method:getHeight"), [getId]("GI.Clutter.Interfaces.Scriptable#g:method:getId"), [getNActors]("GI.Clutter.Objects.Behaviour#g:method:getNActors"), [getNthActor]("GI.Clutter.Objects.Behaviour#g:method:getNthActor"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTilt]("GI.Clutter.Objects.BehaviourEllipse#g:method:getTilt"), [getWidth]("GI.Clutter.Objects.BehaviourEllipse#g:method:getWidth").
-- 
-- ==== Setters
-- [setAlpha]("GI.Clutter.Objects.Behaviour#g:method:setAlpha"), [setAngleEnd]("GI.Clutter.Objects.BehaviourEllipse#g:method:setAngleEnd"), [setAngleStart]("GI.Clutter.Objects.BehaviourEllipse#g:method:setAngleStart"), [setAngleTilt]("GI.Clutter.Objects.BehaviourEllipse#g:method:setAngleTilt"), [setCenter]("GI.Clutter.Objects.BehaviourEllipse#g:method:setCenter"), [setCustomProperty]("GI.Clutter.Interfaces.Scriptable#g:method:setCustomProperty"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Clutter.Objects.BehaviourEllipse#g:method:setDirection"), [setHeight]("GI.Clutter.Objects.BehaviourEllipse#g:method:setHeight"), [setId]("GI.Clutter.Interfaces.Scriptable#g:method:setId"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTilt]("GI.Clutter.Objects.BehaviourEllipse#g:method:setTilt"), [setWidth]("GI.Clutter.Objects.BehaviourEllipse#g:method:setWidth").

#if defined(ENABLE_OVERLOADING)
    ResolveBehaviourEllipseMethod           ,
#endif

-- ** getAngleEnd #method:getAngleEnd#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetAngleEndMethodInfo   ,
#endif
    behaviourEllipseGetAngleEnd             ,


-- ** getAngleStart #method:getAngleStart#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetAngleStartMethodInfo ,
#endif
    behaviourEllipseGetAngleStart           ,


-- ** getAngleTilt #method:getAngleTilt#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetAngleTiltMethodInfo  ,
#endif
    behaviourEllipseGetAngleTilt            ,


-- ** getCenter #method:getCenter#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetCenterMethodInfo     ,
#endif
    behaviourEllipseGetCenter               ,


-- ** getDirection #method:getDirection#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetDirectionMethodInfo  ,
#endif
    behaviourEllipseGetDirection            ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetHeightMethodInfo     ,
#endif
    behaviourEllipseGetHeight               ,


-- ** getTilt #method:getTilt#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetTiltMethodInfo       ,
#endif
    behaviourEllipseGetTilt                 ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseGetWidthMethodInfo      ,
#endif
    behaviourEllipseGetWidth                ,


-- ** new #method:new#

    behaviourEllipseNew                     ,


-- ** setAngleEnd #method:setAngleEnd#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetAngleEndMethodInfo   ,
#endif
    behaviourEllipseSetAngleEnd             ,


-- ** setAngleStart #method:setAngleStart#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetAngleStartMethodInfo ,
#endif
    behaviourEllipseSetAngleStart           ,


-- ** setAngleTilt #method:setAngleTilt#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetAngleTiltMethodInfo  ,
#endif
    behaviourEllipseSetAngleTilt            ,


-- ** setCenter #method:setCenter#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetCenterMethodInfo     ,
#endif
    behaviourEllipseSetCenter               ,


-- ** setDirection #method:setDirection#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetDirectionMethodInfo  ,
#endif
    behaviourEllipseSetDirection            ,


-- ** setHeight #method:setHeight#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetHeightMethodInfo     ,
#endif
    behaviourEllipseSetHeight               ,


-- ** setTilt #method:setTilt#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetTiltMethodInfo       ,
#endif
    behaviourEllipseSetTilt                 ,


-- ** setWidth #method:setWidth#

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseSetWidthMethodInfo      ,
#endif
    behaviourEllipseSetWidth                ,




 -- * Properties


-- ** angleEnd #attr:angleEnd#
-- | The final angle to where the rotation should end.
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseAngleEndPropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseAngleEnd                ,
#endif
    constructBehaviourEllipseAngleEnd       ,
    getBehaviourEllipseAngleEnd             ,
    setBehaviourEllipseAngleEnd             ,


-- ** angleStart #attr:angleStart#
-- | The initial angle from where the rotation should start.
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseAngleStartPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseAngleStart              ,
#endif
    constructBehaviourEllipseAngleStart     ,
    getBehaviourEllipseAngleStart           ,
    setBehaviourEllipseAngleStart           ,


-- ** angleTiltX #attr:angleTiltX#
-- | The tilt angle for the rotation around center in X axis
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseAngleTiltXPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseAngleTiltX              ,
#endif
    constructBehaviourEllipseAngleTiltX     ,
    getBehaviourEllipseAngleTiltX           ,
    setBehaviourEllipseAngleTiltX           ,


-- ** angleTiltY #attr:angleTiltY#
-- | The tilt angle for the rotation around center in Y axis
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseAngleTiltYPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseAngleTiltY              ,
#endif
    constructBehaviourEllipseAngleTiltY     ,
    getBehaviourEllipseAngleTiltY           ,
    setBehaviourEllipseAngleTiltY           ,


-- ** angleTiltZ #attr:angleTiltZ#
-- | The tilt angle for the rotation on the Z axis
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseAngleTiltZPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseAngleTiltZ              ,
#endif
    constructBehaviourEllipseAngleTiltZ     ,
    getBehaviourEllipseAngleTiltZ           ,
    setBehaviourEllipseAngleTiltZ           ,


-- ** center #attr:center#
-- | The center of the ellipse.
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseCenterPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseCenter                  ,
#endif
    clearBehaviourEllipseCenter             ,
    constructBehaviourEllipseCenter         ,
    getBehaviourEllipseCenter               ,
    setBehaviourEllipseCenter               ,


-- ** direction #attr:direction#
-- | The direction of the rotation.
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseDirectionPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseDirection               ,
#endif
    constructBehaviourEllipseDirection      ,
    getBehaviourEllipseDirection            ,
    setBehaviourEllipseDirection            ,


-- ** height #attr:height#
-- | Height of the ellipse, in pixels
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseHeightPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseHeight                  ,
#endif
    constructBehaviourEllipseHeight         ,
    getBehaviourEllipseHeight               ,
    setBehaviourEllipseHeight               ,


-- ** width #attr:width#
-- | Width of the ellipse, in pixels
-- 
-- /Since: 0.4/

#if defined(ENABLE_OVERLOADING)
    BehaviourEllipseWidthPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    behaviourEllipseWidth                   ,
#endif
    constructBehaviourEllipseWidth          ,
    getBehaviourEllipseWidth                ,
    setBehaviourEllipseWidth                ,




    ) 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.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Clutter.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 {-# SOURCE #-} qualified GI.Clutter.Structs.Knot as Clutter.Knot
import qualified GI.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype BehaviourEllipse = BehaviourEllipse (SP.ManagedPtr BehaviourEllipse)
    deriving (BehaviourEllipse -> BehaviourEllipse -> Bool
(BehaviourEllipse -> BehaviourEllipse -> Bool)
-> (BehaviourEllipse -> BehaviourEllipse -> Bool)
-> Eq BehaviourEllipse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BehaviourEllipse -> BehaviourEllipse -> Bool
$c/= :: BehaviourEllipse -> BehaviourEllipse -> Bool
== :: BehaviourEllipse -> BehaviourEllipse -> Bool
$c== :: BehaviourEllipse -> BehaviourEllipse -> Bool
Eq)

instance SP.ManagedPtrNewtype BehaviourEllipse where
    toManagedPtr :: BehaviourEllipse -> ManagedPtr BehaviourEllipse
toManagedPtr (BehaviourEllipse ManagedPtr BehaviourEllipse
p) = ManagedPtr BehaviourEllipse
p

foreign import ccall "clutter_behaviour_ellipse_get_type"
    c_clutter_behaviour_ellipse_get_type :: IO B.Types.GType

instance B.Types.TypedObject BehaviourEllipse where
    glibType :: IO GType
glibType = IO GType
c_clutter_behaviour_ellipse_get_type

instance B.Types.GObject BehaviourEllipse

-- | Type class for types which can be safely cast to `BehaviourEllipse`, for instance with `toBehaviourEllipse`.
class (SP.GObject o, O.IsDescendantOf BehaviourEllipse o) => IsBehaviourEllipse o
instance (SP.GObject o, O.IsDescendantOf BehaviourEllipse o) => IsBehaviourEllipse o

instance O.HasParentTypes BehaviourEllipse
type instance O.ParentTypes BehaviourEllipse = '[Clutter.Behaviour.Behaviour, GObject.Object.Object, Clutter.Scriptable.Scriptable]

-- | Cast to `BehaviourEllipse`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toBehaviourEllipse :: (MIO.MonadIO m, IsBehaviourEllipse o) => o -> m BehaviourEllipse
toBehaviourEllipse :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m BehaviourEllipse
toBehaviourEllipse = IO BehaviourEllipse -> m BehaviourEllipse
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO BehaviourEllipse -> m BehaviourEllipse)
-> (o -> IO BehaviourEllipse) -> o -> m BehaviourEllipse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr BehaviourEllipse -> BehaviourEllipse)
-> o -> IO BehaviourEllipse
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr BehaviourEllipse -> BehaviourEllipse
BehaviourEllipse

-- | Convert 'BehaviourEllipse' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe BehaviourEllipse) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_behaviour_ellipse_get_type
    gvalueSet_ :: Ptr GValue -> Maybe BehaviourEllipse -> IO ()
gvalueSet_ Ptr GValue
gv Maybe BehaviourEllipse
P.Nothing = Ptr GValue -> Ptr BehaviourEllipse -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr BehaviourEllipse
forall a. Ptr a
FP.nullPtr :: FP.Ptr BehaviourEllipse)
    gvalueSet_ Ptr GValue
gv (P.Just BehaviourEllipse
obj) = BehaviourEllipse -> (Ptr BehaviourEllipse -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BehaviourEllipse
obj (Ptr GValue -> Ptr BehaviourEllipse -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe BehaviourEllipse)
gvalueGet_ Ptr GValue
gv = do
        Ptr BehaviourEllipse
ptr <- Ptr GValue -> IO (Ptr BehaviourEllipse)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr BehaviourEllipse)
        if Ptr BehaviourEllipse
ptr Ptr BehaviourEllipse -> Ptr BehaviourEllipse -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr BehaviourEllipse
forall a. Ptr a
FP.nullPtr
        then BehaviourEllipse -> Maybe BehaviourEllipse
forall a. a -> Maybe a
P.Just (BehaviourEllipse -> Maybe BehaviourEllipse)
-> IO BehaviourEllipse -> IO (Maybe BehaviourEllipse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr BehaviourEllipse -> BehaviourEllipse)
-> Ptr BehaviourEllipse -> IO BehaviourEllipse
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr BehaviourEllipse -> BehaviourEllipse
BehaviourEllipse Ptr BehaviourEllipse
ptr
        else Maybe BehaviourEllipse -> IO (Maybe BehaviourEllipse)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BehaviourEllipse
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveBehaviourEllipseMethod (t :: Symbol) (o :: *) :: * where
    ResolveBehaviourEllipseMethod "actorsForeach" o = Clutter.Behaviour.BehaviourActorsForeachMethodInfo
    ResolveBehaviourEllipseMethod "apply" o = Clutter.Behaviour.BehaviourApplyMethodInfo
    ResolveBehaviourEllipseMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBehaviourEllipseMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBehaviourEllipseMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBehaviourEllipseMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBehaviourEllipseMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBehaviourEllipseMethod "isApplied" o = Clutter.Behaviour.BehaviourIsAppliedMethodInfo
    ResolveBehaviourEllipseMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBehaviourEllipseMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBehaviourEllipseMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBehaviourEllipseMethod "parseCustomNode" o = Clutter.Scriptable.ScriptableParseCustomNodeMethodInfo
    ResolveBehaviourEllipseMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBehaviourEllipseMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBehaviourEllipseMethod "remove" o = Clutter.Behaviour.BehaviourRemoveMethodInfo
    ResolveBehaviourEllipseMethod "removeAll" o = Clutter.Behaviour.BehaviourRemoveAllMethodInfo
    ResolveBehaviourEllipseMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBehaviourEllipseMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBehaviourEllipseMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBehaviourEllipseMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBehaviourEllipseMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBehaviourEllipseMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBehaviourEllipseMethod "getActors" o = Clutter.Behaviour.BehaviourGetActorsMethodInfo
    ResolveBehaviourEllipseMethod "getAlpha" o = Clutter.Behaviour.BehaviourGetAlphaMethodInfo
    ResolveBehaviourEllipseMethod "getAngleEnd" o = BehaviourEllipseGetAngleEndMethodInfo
    ResolveBehaviourEllipseMethod "getAngleStart" o = BehaviourEllipseGetAngleStartMethodInfo
    ResolveBehaviourEllipseMethod "getAngleTilt" o = BehaviourEllipseGetAngleTiltMethodInfo
    ResolveBehaviourEllipseMethod "getCenter" o = BehaviourEllipseGetCenterMethodInfo
    ResolveBehaviourEllipseMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBehaviourEllipseMethod "getDirection" o = BehaviourEllipseGetDirectionMethodInfo
    ResolveBehaviourEllipseMethod "getHeight" o = BehaviourEllipseGetHeightMethodInfo
    ResolveBehaviourEllipseMethod "getId" o = Clutter.Scriptable.ScriptableGetIdMethodInfo
    ResolveBehaviourEllipseMethod "getNActors" o = Clutter.Behaviour.BehaviourGetNActorsMethodInfo
    ResolveBehaviourEllipseMethod "getNthActor" o = Clutter.Behaviour.BehaviourGetNthActorMethodInfo
    ResolveBehaviourEllipseMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBehaviourEllipseMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBehaviourEllipseMethod "getTilt" o = BehaviourEllipseGetTiltMethodInfo
    ResolveBehaviourEllipseMethod "getWidth" o = BehaviourEllipseGetWidthMethodInfo
    ResolveBehaviourEllipseMethod "setAlpha" o = Clutter.Behaviour.BehaviourSetAlphaMethodInfo
    ResolveBehaviourEllipseMethod "setAngleEnd" o = BehaviourEllipseSetAngleEndMethodInfo
    ResolveBehaviourEllipseMethod "setAngleStart" o = BehaviourEllipseSetAngleStartMethodInfo
    ResolveBehaviourEllipseMethod "setAngleTilt" o = BehaviourEllipseSetAngleTiltMethodInfo
    ResolveBehaviourEllipseMethod "setCenter" o = BehaviourEllipseSetCenterMethodInfo
    ResolveBehaviourEllipseMethod "setCustomProperty" o = Clutter.Scriptable.ScriptableSetCustomPropertyMethodInfo
    ResolveBehaviourEllipseMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBehaviourEllipseMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBehaviourEllipseMethod "setDirection" o = BehaviourEllipseSetDirectionMethodInfo
    ResolveBehaviourEllipseMethod "setHeight" o = BehaviourEllipseSetHeightMethodInfo
    ResolveBehaviourEllipseMethod "setId" o = Clutter.Scriptable.ScriptableSetIdMethodInfo
    ResolveBehaviourEllipseMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBehaviourEllipseMethod "setTilt" o = BehaviourEllipseSetTiltMethodInfo
    ResolveBehaviourEllipseMethod "setWidth" o = BehaviourEllipseSetWidthMethodInfo
    ResolveBehaviourEllipseMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveBehaviourEllipseMethod t BehaviourEllipse, O.OverloadedMethod info BehaviourEllipse p) => OL.IsLabel t (BehaviourEllipse -> 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 ~ ResolveBehaviourEllipseMethod t BehaviourEllipse, O.OverloadedMethod info BehaviourEllipse p, R.HasField t BehaviourEllipse p) => R.HasField t BehaviourEllipse p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveBehaviourEllipseMethod t BehaviourEllipse, O.OverloadedMethodInfo info BehaviourEllipse) => OL.IsLabel t (O.MethodProxy info BehaviourEllipse) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "angle-end"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@angle-end@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #angleEnd
-- @
getBehaviourEllipseAngleEnd :: (MonadIO m, IsBehaviourEllipse o) => o -> m Double
getBehaviourEllipseAngleEnd :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m Double
getBehaviourEllipseAngleEnd o
obj = IO Double -> m Double
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"

-- | Set the value of the “@angle-end@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #angleEnd 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseAngleEnd :: (MonadIO m, IsBehaviourEllipse o) => o -> Double -> m ()
setBehaviourEllipseAngleEnd :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Double -> m ()
setBehaviourEllipseAngleEnd o
obj Double
val = IO () -> m ()
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

-- | Construct a `GValueConstruct` with valid value for the “@angle-end@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseAngleEnd :: (IsBehaviourEllipse o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleEnd :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleEnd Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 BehaviourEllipseAngleEndPropertyInfo
instance AttrInfo BehaviourEllipseAngleEndPropertyInfo where
    type AttrAllowedOps BehaviourEllipseAngleEndPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseAngleEndPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseAngleEndPropertyInfo = (~) Double
    type AttrTransferTypeConstraint BehaviourEllipseAngleEndPropertyInfo = (~) Double
    type AttrTransferType BehaviourEllipseAngleEndPropertyInfo = Double
    type AttrGetType BehaviourEllipseAngleEndPropertyInfo = Double
    type AttrLabel BehaviourEllipseAngleEndPropertyInfo = "angle-end"
    type AttrOrigin BehaviourEllipseAngleEndPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseAngleEnd
    attrSet = setBehaviourEllipseAngleEnd
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseAngleEnd
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.angleEnd"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:angleEnd"
        })
#endif

-- VVV Prop "angle-start"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@angle-start@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #angleStart
-- @
getBehaviourEllipseAngleStart :: (MonadIO m, IsBehaviourEllipse o) => o -> m Double
getBehaviourEllipseAngleStart :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m Double
getBehaviourEllipseAngleStart o
obj = IO Double -> m Double
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"

-- | Set the value of the “@angle-start@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #angleStart 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseAngleStart :: (MonadIO m, IsBehaviourEllipse o) => o -> Double -> m ()
setBehaviourEllipseAngleStart :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Double -> m ()
setBehaviourEllipseAngleStart o
obj Double
val = IO () -> m ()
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

-- | Construct a `GValueConstruct` with valid value for the “@angle-start@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseAngleStart :: (IsBehaviourEllipse o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleStart :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleStart Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 BehaviourEllipseAngleStartPropertyInfo
instance AttrInfo BehaviourEllipseAngleStartPropertyInfo where
    type AttrAllowedOps BehaviourEllipseAngleStartPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseAngleStartPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseAngleStartPropertyInfo = (~) Double
    type AttrTransferTypeConstraint BehaviourEllipseAngleStartPropertyInfo = (~) Double
    type AttrTransferType BehaviourEllipseAngleStartPropertyInfo = Double
    type AttrGetType BehaviourEllipseAngleStartPropertyInfo = Double
    type AttrLabel BehaviourEllipseAngleStartPropertyInfo = "angle-start"
    type AttrOrigin BehaviourEllipseAngleStartPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseAngleStart
    attrSet = setBehaviourEllipseAngleStart
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseAngleStart
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.angleStart"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:angleStart"
        })
#endif

-- VVV Prop "angle-tilt-x"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@angle-tilt-x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #angleTiltX
-- @
getBehaviourEllipseAngleTiltX :: (MonadIO m, IsBehaviourEllipse o) => o -> m Double
getBehaviourEllipseAngleTiltX :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m Double
getBehaviourEllipseAngleTiltX o
obj = IO Double -> m Double
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-tilt-x"

-- | Set the value of the “@angle-tilt-x@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #angleTiltX 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseAngleTiltX :: (MonadIO m, IsBehaviourEllipse o) => o -> Double -> m ()
setBehaviourEllipseAngleTiltX :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Double -> m ()
setBehaviourEllipseAngleTiltX o
obj Double
val = IO () -> m ()
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-tilt-x" Double
val

-- | Construct a `GValueConstruct` with valid value for the “@angle-tilt-x@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseAngleTiltX :: (IsBehaviourEllipse o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleTiltX :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleTiltX Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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-tilt-x" Double
val

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseAngleTiltXPropertyInfo
instance AttrInfo BehaviourEllipseAngleTiltXPropertyInfo where
    type AttrAllowedOps BehaviourEllipseAngleTiltXPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseAngleTiltXPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseAngleTiltXPropertyInfo = (~) Double
    type AttrTransferTypeConstraint BehaviourEllipseAngleTiltXPropertyInfo = (~) Double
    type AttrTransferType BehaviourEllipseAngleTiltXPropertyInfo = Double
    type AttrGetType BehaviourEllipseAngleTiltXPropertyInfo = Double
    type AttrLabel BehaviourEllipseAngleTiltXPropertyInfo = "angle-tilt-x"
    type AttrOrigin BehaviourEllipseAngleTiltXPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseAngleTiltX
    attrSet = setBehaviourEllipseAngleTiltX
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseAngleTiltX
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.angleTiltX"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:angleTiltX"
        })
#endif

-- VVV Prop "angle-tilt-y"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@angle-tilt-y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #angleTiltY
-- @
getBehaviourEllipseAngleTiltY :: (MonadIO m, IsBehaviourEllipse o) => o -> m Double
getBehaviourEllipseAngleTiltY :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m Double
getBehaviourEllipseAngleTiltY o
obj = IO Double -> m Double
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-tilt-y"

-- | Set the value of the “@angle-tilt-y@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #angleTiltY 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseAngleTiltY :: (MonadIO m, IsBehaviourEllipse o) => o -> Double -> m ()
setBehaviourEllipseAngleTiltY :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Double -> m ()
setBehaviourEllipseAngleTiltY o
obj Double
val = IO () -> m ()
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-tilt-y" Double
val

-- | Construct a `GValueConstruct` with valid value for the “@angle-tilt-y@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseAngleTiltY :: (IsBehaviourEllipse o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleTiltY :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleTiltY Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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-tilt-y" Double
val

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseAngleTiltYPropertyInfo
instance AttrInfo BehaviourEllipseAngleTiltYPropertyInfo where
    type AttrAllowedOps BehaviourEllipseAngleTiltYPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseAngleTiltYPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseAngleTiltYPropertyInfo = (~) Double
    type AttrTransferTypeConstraint BehaviourEllipseAngleTiltYPropertyInfo = (~) Double
    type AttrTransferType BehaviourEllipseAngleTiltYPropertyInfo = Double
    type AttrGetType BehaviourEllipseAngleTiltYPropertyInfo = Double
    type AttrLabel BehaviourEllipseAngleTiltYPropertyInfo = "angle-tilt-y"
    type AttrOrigin BehaviourEllipseAngleTiltYPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseAngleTiltY
    attrSet = setBehaviourEllipseAngleTiltY
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseAngleTiltY
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.angleTiltY"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:angleTiltY"
        })
#endif

-- VVV Prop "angle-tilt-z"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@angle-tilt-z@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #angleTiltZ
-- @
getBehaviourEllipseAngleTiltZ :: (MonadIO m, IsBehaviourEllipse o) => o -> m Double
getBehaviourEllipseAngleTiltZ :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m Double
getBehaviourEllipseAngleTiltZ o
obj = IO Double -> m Double
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-tilt-z"

-- | Set the value of the “@angle-tilt-z@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #angleTiltZ 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseAngleTiltZ :: (MonadIO m, IsBehaviourEllipse o) => o -> Double -> m ()
setBehaviourEllipseAngleTiltZ :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Double -> m ()
setBehaviourEllipseAngleTiltZ o
obj Double
val = IO () -> m ()
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-tilt-z" Double
val

-- | Construct a `GValueConstruct` with valid value for the “@angle-tilt-z@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseAngleTiltZ :: (IsBehaviourEllipse o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleTiltZ :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructBehaviourEllipseAngleTiltZ Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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-tilt-z" Double
val

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseAngleTiltZPropertyInfo
instance AttrInfo BehaviourEllipseAngleTiltZPropertyInfo where
    type AttrAllowedOps BehaviourEllipseAngleTiltZPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseAngleTiltZPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseAngleTiltZPropertyInfo = (~) Double
    type AttrTransferTypeConstraint BehaviourEllipseAngleTiltZPropertyInfo = (~) Double
    type AttrTransferType BehaviourEllipseAngleTiltZPropertyInfo = Double
    type AttrGetType BehaviourEllipseAngleTiltZPropertyInfo = Double
    type AttrLabel BehaviourEllipseAngleTiltZPropertyInfo = "angle-tilt-z"
    type AttrOrigin BehaviourEllipseAngleTiltZPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseAngleTiltZ
    attrSet = setBehaviourEllipseAngleTiltZ
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseAngleTiltZ
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.angleTiltZ"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:angleTiltZ"
        })
#endif

-- VVV Prop "center"
   -- Type: TInterface (Name {namespace = "Clutter", name = "Knot"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@center@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #center
-- @
getBehaviourEllipseCenter :: (MonadIO m, IsBehaviourEllipse o) => o -> m (Maybe Clutter.Knot.Knot)
getBehaviourEllipseCenter :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m (Maybe Knot)
getBehaviourEllipseCenter o
obj = IO (Maybe Knot) -> m (Maybe Knot)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Knot) -> m (Maybe Knot))
-> IO (Maybe Knot) -> m (Maybe Knot)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Knot -> Knot) -> IO (Maybe Knot)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"center" ManagedPtr Knot -> Knot
Clutter.Knot.Knot

-- | Set the value of the “@center@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #center 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseCenter :: (MonadIO m, IsBehaviourEllipse o) => o -> Clutter.Knot.Knot -> m ()
setBehaviourEllipseCenter :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Knot -> m ()
setBehaviourEllipseCenter o
obj Knot
val = IO () -> m ()
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 Knot -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"center" (Knot -> Maybe Knot
forall a. a -> Maybe a
Just Knot
val)

-- | Construct a `GValueConstruct` with valid value for the “@center@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseCenter :: (IsBehaviourEllipse o, MIO.MonadIO m) => Clutter.Knot.Knot -> m (GValueConstruct o)
constructBehaviourEllipseCenter :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Knot -> m (GValueConstruct o)
constructBehaviourEllipseCenter Knot
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Knot -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"center" (Knot -> Maybe Knot
forall a. a -> Maybe a
P.Just Knot
val)

-- | Set the value of the “@center@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #center
-- @
clearBehaviourEllipseCenter :: (MonadIO m, IsBehaviourEllipse o) => o -> m ()
clearBehaviourEllipseCenter :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m ()
clearBehaviourEllipseCenter o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Knot -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"center" (Maybe Knot
forall a. Maybe a
Nothing :: Maybe Clutter.Knot.Knot)

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseCenterPropertyInfo
instance AttrInfo BehaviourEllipseCenterPropertyInfo where
    type AttrAllowedOps BehaviourEllipseCenterPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BehaviourEllipseCenterPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseCenterPropertyInfo = (~) Clutter.Knot.Knot
    type AttrTransferTypeConstraint BehaviourEllipseCenterPropertyInfo = (~) Clutter.Knot.Knot
    type AttrTransferType BehaviourEllipseCenterPropertyInfo = Clutter.Knot.Knot
    type AttrGetType BehaviourEllipseCenterPropertyInfo = (Maybe Clutter.Knot.Knot)
    type AttrLabel BehaviourEllipseCenterPropertyInfo = "center"
    type AttrOrigin BehaviourEllipseCenterPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseCenter
    attrSet = setBehaviourEllipseCenter
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseCenter
    attrClear = clearBehaviourEllipseCenter
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.center"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:center"
        })
#endif

-- VVV Prop "direction"
   -- Type: TInterface (Name {namespace = "Clutter", name = "RotateDirection"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@direction@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #direction
-- @
getBehaviourEllipseDirection :: (MonadIO m, IsBehaviourEllipse o) => o -> m Clutter.Enums.RotateDirection
getBehaviourEllipseDirection :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m RotateDirection
getBehaviourEllipseDirection o
obj = IO RotateDirection -> m RotateDirection
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"

-- | Set the value of the “@direction@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #direction 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseDirection :: (MonadIO m, IsBehaviourEllipse o) => o -> Clutter.Enums.RotateDirection -> m ()
setBehaviourEllipseDirection :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> RotateDirection -> m ()
setBehaviourEllipseDirection o
obj RotateDirection
val = IO () -> m ()
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

-- | Construct a `GValueConstruct` with valid value for the “@direction@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseDirection :: (IsBehaviourEllipse o, MIO.MonadIO m) => Clutter.Enums.RotateDirection -> m (GValueConstruct o)
constructBehaviourEllipseDirection :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
RotateDirection -> m (GValueConstruct o)
constructBehaviourEllipseDirection RotateDirection
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 BehaviourEllipseDirectionPropertyInfo
instance AttrInfo BehaviourEllipseDirectionPropertyInfo where
    type AttrAllowedOps BehaviourEllipseDirectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseDirectionPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseDirectionPropertyInfo = (~) Clutter.Enums.RotateDirection
    type AttrTransferTypeConstraint BehaviourEllipseDirectionPropertyInfo = (~) Clutter.Enums.RotateDirection
    type AttrTransferType BehaviourEllipseDirectionPropertyInfo = Clutter.Enums.RotateDirection
    type AttrGetType BehaviourEllipseDirectionPropertyInfo = Clutter.Enums.RotateDirection
    type AttrLabel BehaviourEllipseDirectionPropertyInfo = "direction"
    type AttrOrigin BehaviourEllipseDirectionPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseDirection
    attrSet = setBehaviourEllipseDirection
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseDirection
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.direction"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:direction"
        })
#endif

-- VVV Prop "height"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #height
-- @
getBehaviourEllipseHeight :: (MonadIO m, IsBehaviourEllipse o) => o -> m Int32
getBehaviourEllipseHeight :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m Int32
getBehaviourEllipseHeight o
obj = IO Int32 -> m Int32
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
"height"

-- | Set the value of the “@height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #height 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseHeight :: (MonadIO m, IsBehaviourEllipse o) => o -> Int32 -> m ()
setBehaviourEllipseHeight :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Int32 -> m ()
setBehaviourEllipseHeight o
obj Int32
val = IO () -> m ()
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
"height" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseHeight :: (IsBehaviourEllipse o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructBehaviourEllipseHeight :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructBehaviourEllipseHeight Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"height" Int32
val

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseHeightPropertyInfo
instance AttrInfo BehaviourEllipseHeightPropertyInfo where
    type AttrAllowedOps BehaviourEllipseHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseHeightPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseHeightPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint BehaviourEllipseHeightPropertyInfo = (~) Int32
    type AttrTransferType BehaviourEllipseHeightPropertyInfo = Int32
    type AttrGetType BehaviourEllipseHeightPropertyInfo = Int32
    type AttrLabel BehaviourEllipseHeightPropertyInfo = "height"
    type AttrOrigin BehaviourEllipseHeightPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseHeight
    attrSet = setBehaviourEllipseHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.height"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:height"
        })
#endif

-- VVV Prop "width"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' behaviourEllipse #width
-- @
getBehaviourEllipseWidth :: (MonadIO m, IsBehaviourEllipse o) => o -> m Int32
getBehaviourEllipseWidth :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> m Int32
getBehaviourEllipseWidth o
obj = IO Int32 -> m Int32
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
"width"

-- | Set the value of the “@width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' behaviourEllipse [ #width 'Data.GI.Base.Attributes.:=' value ]
-- @
setBehaviourEllipseWidth :: (MonadIO m, IsBehaviourEllipse o) => o -> Int32 -> m ()
setBehaviourEllipseWidth :: forall (m :: * -> *) o.
(MonadIO m, IsBehaviourEllipse o) =>
o -> Int32 -> m ()
setBehaviourEllipseWidth o
obj Int32
val = IO () -> m ()
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
"width" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBehaviourEllipseWidth :: (IsBehaviourEllipse o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructBehaviourEllipseWidth :: forall o (m :: * -> *).
(IsBehaviourEllipse o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructBehaviourEllipseWidth Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"width" Int32
val

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseWidthPropertyInfo
instance AttrInfo BehaviourEllipseWidthPropertyInfo where
    type AttrAllowedOps BehaviourEllipseWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BehaviourEllipseWidthPropertyInfo = IsBehaviourEllipse
    type AttrSetTypeConstraint BehaviourEllipseWidthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint BehaviourEllipseWidthPropertyInfo = (~) Int32
    type AttrTransferType BehaviourEllipseWidthPropertyInfo = Int32
    type AttrGetType BehaviourEllipseWidthPropertyInfo = Int32
    type AttrLabel BehaviourEllipseWidthPropertyInfo = "width"
    type AttrOrigin BehaviourEllipseWidthPropertyInfo = BehaviourEllipse
    attrGet = getBehaviourEllipseWidth
    attrSet = setBehaviourEllipseWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructBehaviourEllipseWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.width"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#g:attr:width"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BehaviourEllipse
type instance O.AttributeList BehaviourEllipse = BehaviourEllipseAttributeList
type BehaviourEllipseAttributeList = ('[ '("alpha", Clutter.Behaviour.BehaviourAlphaPropertyInfo), '("angleEnd", BehaviourEllipseAngleEndPropertyInfo), '("angleStart", BehaviourEllipseAngleStartPropertyInfo), '("angleTiltX", BehaviourEllipseAngleTiltXPropertyInfo), '("angleTiltY", BehaviourEllipseAngleTiltYPropertyInfo), '("angleTiltZ", BehaviourEllipseAngleTiltZPropertyInfo), '("center", BehaviourEllipseCenterPropertyInfo), '("direction", BehaviourEllipseDirectionPropertyInfo), '("height", BehaviourEllipseHeightPropertyInfo), '("width", BehaviourEllipseWidthPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
behaviourEllipseAngleEnd :: AttrLabelProxy "angleEnd"
behaviourEllipseAngleEnd = AttrLabelProxy

behaviourEllipseAngleStart :: AttrLabelProxy "angleStart"
behaviourEllipseAngleStart = AttrLabelProxy

behaviourEllipseAngleTiltX :: AttrLabelProxy "angleTiltX"
behaviourEllipseAngleTiltX = AttrLabelProxy

behaviourEllipseAngleTiltY :: AttrLabelProxy "angleTiltY"
behaviourEllipseAngleTiltY = AttrLabelProxy

behaviourEllipseAngleTiltZ :: AttrLabelProxy "angleTiltZ"
behaviourEllipseAngleTiltZ = AttrLabelProxy

behaviourEllipseCenter :: AttrLabelProxy "center"
behaviourEllipseCenter = AttrLabelProxy

behaviourEllipseDirection :: AttrLabelProxy "direction"
behaviourEllipseDirection = AttrLabelProxy

behaviourEllipseHeight :: AttrLabelProxy "height"
behaviourEllipseHeight = AttrLabelProxy

behaviourEllipseWidth :: AttrLabelProxy "width"
behaviourEllipseWidth = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList BehaviourEllipse = BehaviourEllipseSignalList
type BehaviourEllipseSignalList = ('[ '("applied", Clutter.Behaviour.BehaviourAppliedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("removed", Clutter.Behaviour.BehaviourRemovedSignalInfo)] :: [(Symbol, *)])

#endif

-- method BehaviourEllipse::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "alpha"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Alpha" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterAlpha instance, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x coordinace of the center"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y coordiance of the center"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width of the ellipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height of the ellipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "direction"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "RotateDirection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#ClutterRotateDirection of rotation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "angle in degrees at which movement starts, between 0 and 360"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "angle in degrees at which movement ends, between 0 and 360"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Clutter" , name = "BehaviourEllipse" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_new" clutter_behaviour_ellipse_new :: 
    Ptr Clutter.Alpha.Alpha ->              -- alpha : TInterface (Name {namespace = "Clutter", name = "Alpha"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    CUInt ->                                -- direction : TInterface (Name {namespace = "Clutter", name = "RotateDirection"})
    CDouble ->                              -- start : TBasicType TDouble
    CDouble ->                              -- end : TBasicType TDouble
    IO (Ptr BehaviourEllipse)

-- | Creates a behaviour that drives actors along an elliptical path with
-- given center, width and height; the movement starts at /@start@/
-- degrees (with 0 corresponding to 12 o\'clock) and ends at /@end@/
-- degrees. Angles greated than 360 degrees get clamped to the canonical
-- interval \<0, 360); if /@start@/ is equal to /@end@/, the behaviour will
-- rotate by exacly 360 degrees.
-- 
-- If /@alpha@/ is not 'P.Nothing', the t'GI.Clutter.Objects.Behaviour.Behaviour' will take ownership
-- of the t'GI.Clutter.Objects.Alpha.Alpha' instance. In the case when /@alpha@/ is 'P.Nothing',
-- it can be set later with 'GI.Clutter.Objects.Behaviour.behaviourSetAlpha'.
-- 
-- /Since: 0.4/
behaviourEllipseNew ::
    (B.CallStack.HasCallStack, MonadIO m, Clutter.Alpha.IsAlpha a) =>
    Maybe (a)
    -- ^ /@alpha@/: a t'GI.Clutter.Objects.Alpha.Alpha' instance, or 'P.Nothing'
    -> Int32
    -- ^ /@x@/: x coordinace of the center
    -> Int32
    -- ^ /@y@/: y coordiance of the center
    -> Int32
    -- ^ /@width@/: width of the ellipse
    -> Int32
    -- ^ /@height@/: height of the ellipse
    -> Clutter.Enums.RotateDirection
    -- ^ /@direction@/: t'GI.Clutter.Enums.RotateDirection' of rotation
    -> Double
    -- ^ /@start@/: angle in degrees at which movement starts, between 0 and 360
    -> Double
    -- ^ /@end@/: angle in degrees at which movement ends, between 0 and 360
    -> m BehaviourEllipse
    -- ^ __Returns:__ the newly created t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
behaviourEllipseNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAlpha a) =>
Maybe a
-> Int32
-> Int32
-> Int32
-> Int32
-> RotateDirection
-> Double
-> Double
-> m BehaviourEllipse
behaviourEllipseNew Maybe a
alpha Int32
x Int32
y Int32
width Int32
height RotateDirection
direction Double
start Double
end = IO BehaviourEllipse -> m BehaviourEllipse
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BehaviourEllipse -> m BehaviourEllipse)
-> IO BehaviourEllipse -> m BehaviourEllipse
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 (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 (m :: * -> *) a. Monad m => a -> m a
return Ptr Alpha
jAlpha'
    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 start' :: CDouble
start' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
start
    let end' :: CDouble
end' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
end
    Ptr BehaviourEllipse
result <- Ptr Alpha
-> Int32
-> Int32
-> Int32
-> Int32
-> CUInt
-> CDouble
-> CDouble
-> IO (Ptr BehaviourEllipse)
clutter_behaviour_ellipse_new Ptr Alpha
maybeAlpha Int32
x Int32
y Int32
width Int32
height CUInt
direction' CDouble
start' CDouble
end'
    Text -> Ptr BehaviourEllipse -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"behaviourEllipseNew" Ptr BehaviourEllipse
result
    BehaviourEllipse
result' <- ((ManagedPtr BehaviourEllipse -> BehaviourEllipse)
-> Ptr BehaviourEllipse -> IO BehaviourEllipse
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BehaviourEllipse -> BehaviourEllipse
BehaviourEllipse) Ptr BehaviourEllipse
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
    BehaviourEllipse -> IO BehaviourEllipse
forall (m :: * -> *) a. Monad m => a -> m a
return BehaviourEllipse
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method BehaviourEllipse::get_angle_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_angle_end" clutter_behaviour_ellipse_get_angle_end :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    IO CDouble

-- | Gets the at which movements ends.
-- 
-- /Since: 0.4/
behaviourEllipseGetAngleEnd ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> m Double
    -- ^ __Returns:__ angle in degrees
behaviourEllipseGetAngleEnd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> m Double
behaviourEllipseGetAngleEnd a
self = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CDouble
result <- Ptr BehaviourEllipse -> IO CDouble
clutter_behaviour_ellipse_get_angle_end Ptr BehaviourEllipse
self'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetAngleEndMethodInfo
instance (signature ~ (m Double), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetAngleEndMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetAngleEnd

instance O.OverloadedMethodInfo BehaviourEllipseGetAngleEndMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetAngleEnd",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetAngleEnd"
        })


#endif

-- method BehaviourEllipse::get_angle_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_angle_start" clutter_behaviour_ellipse_get_angle_start :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    IO CDouble

-- | Gets the angle at which movements starts.
-- 
-- /Since: 0.6/
behaviourEllipseGetAngleStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> m Double
    -- ^ __Returns:__ angle in degrees
behaviourEllipseGetAngleStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> m Double
behaviourEllipseGetAngleStart a
self = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CDouble
result <- Ptr BehaviourEllipse -> IO CDouble
clutter_behaviour_ellipse_get_angle_start Ptr BehaviourEllipse
self'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetAngleStartMethodInfo
instance (signature ~ (m Double), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetAngleStartMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetAngleStart

instance O.OverloadedMethodInfo BehaviourEllipseGetAngleStartMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetAngleStart",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetAngleStart"
        })


#endif

-- method BehaviourEllipse::get_angle_tilt
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "axis"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "RotateAxis" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterRotateAxis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_angle_tilt" clutter_behaviour_ellipse_get_angle_tilt :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    CUInt ->                                -- axis : TInterface (Name {namespace = "Clutter", name = "RotateAxis"})
    IO CDouble

-- | Gets the tilt of the ellipse around the center in the given axis.
-- 
-- /Since: 0.4/
behaviourEllipseGetAngleTilt ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Clutter.Enums.RotateAxis
    -- ^ /@axis@/: a t'GI.Clutter.Enums.RotateAxis'
    -> m Double
    -- ^ __Returns:__ angle in degrees.
behaviourEllipseGetAngleTilt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> RotateAxis -> m Double
behaviourEllipseGetAngleTilt a
self RotateAxis
axis = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    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
    CDouble
result <- Ptr BehaviourEllipse -> CUInt -> IO CDouble
clutter_behaviour_ellipse_get_angle_tilt Ptr BehaviourEllipse
self' CUInt
axis'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetAngleTiltMethodInfo
instance (signature ~ (Clutter.Enums.RotateAxis -> m Double), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetAngleTiltMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetAngleTilt

instance O.OverloadedMethodInfo BehaviourEllipseGetAngleTiltMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetAngleTilt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetAngleTilt"
        })


#endif

-- method BehaviourEllipse::get_center
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the X coordinate of the center, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the Y coordinate of the center, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_center" clutter_behaviour_ellipse_get_center :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    Ptr Int32 ->                            -- x : TBasicType TInt
    Ptr Int32 ->                            -- y : TBasicType TInt
    IO ()

-- | Gets the center of the elliptical path path.
-- 
-- /Since: 0.4/
behaviourEllipseGetCenter ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> m ((Int32, Int32))
behaviourEllipseGetCenter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> m (Int32, Int32)
behaviourEllipseGetCenter a
self = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    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 BehaviourEllipse -> Ptr Int32 -> Ptr Int32 -> IO ()
clutter_behaviour_ellipse_get_center Ptr BehaviourEllipse
self' Ptr Int32
x Ptr Int32
y
    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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
x
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
x', Int32
y')

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetCenterMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetCenterMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetCenter

instance O.OverloadedMethodInfo BehaviourEllipseGetCenterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetCenter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetCenter"
        })


#endif

-- method BehaviourEllipse::get_direction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Clutter" , name = "RotateDirection" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_direction" clutter_behaviour_ellipse_get_direction :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    IO CUInt

-- | Retrieves the t'GI.Clutter.Enums.RotateDirection' used by the ellipse behaviour.
-- 
-- /Since: 0.4/
behaviourEllipseGetDirection ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> m Clutter.Enums.RotateDirection
    -- ^ __Returns:__ the rotation direction
behaviourEllipseGetDirection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> m RotateDirection
behaviourEllipseGetDirection a
self = IO RotateDirection -> m RotateDirection
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 BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr BehaviourEllipse -> IO CUInt
clutter_behaviour_ellipse_get_direction Ptr BehaviourEllipse
self'
    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
self
    RotateDirection -> IO RotateDirection
forall (m :: * -> *) a. Monad m => a -> m a
return RotateDirection
result'

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetDirectionMethodInfo
instance (signature ~ (m Clutter.Enums.RotateDirection), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetDirectionMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetDirection

instance O.OverloadedMethodInfo BehaviourEllipseGetDirectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetDirection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetDirection"
        })


#endif

-- method BehaviourEllipse::get_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_height" clutter_behaviour_ellipse_get_height :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    IO Int32

-- | Gets the height of the elliptical path.
-- 
-- /Since: 0.4/
behaviourEllipseGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> m Int32
    -- ^ __Returns:__ the height of the path
behaviourEllipseGetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> m Int32
behaviourEllipseGetHeight a
self = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr BehaviourEllipse -> IO Int32
clutter_behaviour_ellipse_get_height Ptr BehaviourEllipse
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetHeightMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetHeightMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetHeight

instance O.OverloadedMethodInfo BehaviourEllipseGetHeightMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetHeight"
        })


#endif

-- method BehaviourEllipse::get_tilt
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle_tilt_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for tilt angle on the X axis, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "angle_tilt_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for tilt angle on the Y axis, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "angle_tilt_z"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for tilt angle on the Z axis, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_tilt" clutter_behaviour_ellipse_get_tilt :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    Ptr CDouble ->                          -- angle_tilt_x : TBasicType TDouble
    Ptr CDouble ->                          -- angle_tilt_y : TBasicType TDouble
    Ptr CDouble ->                          -- angle_tilt_z : TBasicType TDouble
    IO ()

-- | Gets the tilt of the ellipse around the center in Y axis.
-- 
-- /Since: 0.4/
behaviourEllipseGetTilt ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> m ((Double, Double, Double))
behaviourEllipseGetTilt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> m (Double, Double, Double)
behaviourEllipseGetTilt a
self = IO (Double, Double, Double) -> m (Double, Double, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Double, Double) -> m (Double, Double, Double))
-> IO (Double, Double, Double) -> m (Double, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CDouble
angleTiltX <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
angleTiltY <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
angleTiltZ <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr BehaviourEllipse
-> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
clutter_behaviour_ellipse_get_tilt Ptr BehaviourEllipse
self' Ptr CDouble
angleTiltX Ptr CDouble
angleTiltY Ptr CDouble
angleTiltZ
    CDouble
angleTiltX' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
angleTiltX
    let angleTiltX'' :: Double
angleTiltX'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
angleTiltX'
    CDouble
angleTiltY' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
angleTiltY
    let angleTiltY'' :: Double
angleTiltY'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
angleTiltY'
    CDouble
angleTiltZ' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
angleTiltZ
    let angleTiltZ'' :: Double
angleTiltZ'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
angleTiltZ'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
angleTiltX
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
angleTiltY
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
angleTiltZ
    (Double, Double, Double) -> IO (Double, Double, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
angleTiltX'', Double
angleTiltY'', Double
angleTiltZ'')

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetTiltMethodInfo
instance (signature ~ (m ((Double, Double, Double))), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetTiltMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetTilt

instance O.OverloadedMethodInfo BehaviourEllipseGetTiltMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetTilt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetTilt"
        })


#endif

-- method BehaviourEllipse::get_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_get_width" clutter_behaviour_ellipse_get_width :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    IO Int32

-- | Gets the width of the elliptical path.
-- 
-- /Since: 0.4/
behaviourEllipseGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> m Int32
    -- ^ __Returns:__ the width of the path
behaviourEllipseGetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> m Int32
behaviourEllipseGetWidth a
self = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr BehaviourEllipse -> IO Int32
clutter_behaviour_ellipse_get_width Ptr BehaviourEllipse
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseGetWidthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseGetWidthMethodInfo a signature where
    overloadedMethod = behaviourEllipseGetWidth

instance O.OverloadedMethodInfo BehaviourEllipseGetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseGetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseGetWidth"
        })


#endif

-- method BehaviourEllipse::set_angle_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle_end"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "angle at which movement ends in degrees, between 0 and 360."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_angle_end" clutter_behaviour_ellipse_set_angle_end :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    CDouble ->                              -- angle_end : TBasicType TDouble
    IO ()

-- | Sets the angle at which movement ends; angles >= 360 degress get clamped
-- to the canonical interval \<0, 360).
-- 
-- /Since: 0.4/
behaviourEllipseSetAngleEnd ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Double
    -- ^ /@angleEnd@/: angle at which movement ends in degrees, between 0 and 360.
    -> m ()
behaviourEllipseSetAngleEnd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> Double -> m ()
behaviourEllipseSetAngleEnd a
self Double
angleEnd = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let angleEnd' :: CDouble
angleEnd' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleEnd
    Ptr BehaviourEllipse -> CDouble -> IO ()
clutter_behaviour_ellipse_set_angle_end Ptr BehaviourEllipse
self' CDouble
angleEnd'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetAngleEndMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetAngleEndMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetAngleEnd

instance O.OverloadedMethodInfo BehaviourEllipseSetAngleEndMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetAngleEnd",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetAngleEnd"
        })


#endif

-- method BehaviourEllipse::set_angle_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle_start"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "angle at which movement starts in degrees, between 0 and 360."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_angle_start" clutter_behaviour_ellipse_set_angle_start :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    CDouble ->                              -- angle_start : TBasicType TDouble
    IO ()

-- | Sets the angle at which movement starts; angles >= 360 degress get clamped
-- to the canonical interval \<0, 360).
-- 
-- /Since: 0.6/
behaviourEllipseSetAngleStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Double
    -- ^ /@angleStart@/: angle at which movement starts in degrees, between 0 and 360.
    -> m ()
behaviourEllipseSetAngleStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> Double -> m ()
behaviourEllipseSetAngleStart a
self Double
angleStart = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let angleStart' :: CDouble
angleStart' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleStart
    Ptr BehaviourEllipse -> CDouble -> IO ()
clutter_behaviour_ellipse_set_angle_start Ptr BehaviourEllipse
self' CDouble
angleStart'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetAngleStartMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetAngleStartMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetAngleStart

instance O.OverloadedMethodInfo BehaviourEllipseSetAngleStartMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetAngleStart",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetAngleStart"
        })


#endif

-- method BehaviourEllipse::set_angle_tilt
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "axis"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "RotateAxis" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterRotateAxis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle_tilt"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "tilt of the elipse around the center in the given axis in\ndegrees."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_angle_tilt" clutter_behaviour_ellipse_set_angle_tilt :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    CUInt ->                                -- axis : TInterface (Name {namespace = "Clutter", name = "RotateAxis"})
    CDouble ->                              -- angle_tilt : TBasicType TDouble
    IO ()

-- | Sets the angle at which the ellipse should be tilted around it\'s center.
-- 
-- /Since: 0.4/
behaviourEllipseSetAngleTilt ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Clutter.Enums.RotateAxis
    -- ^ /@axis@/: a t'GI.Clutter.Enums.RotateAxis'
    -> Double
    -- ^ /@angleTilt@/: tilt of the elipse around the center in the given axis in
    -- degrees.
    -> m ()
behaviourEllipseSetAngleTilt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> RotateAxis -> Double -> m ()
behaviourEllipseSetAngleTilt a
self RotateAxis
axis Double
angleTilt = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    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 angleTilt' :: CDouble
angleTilt' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleTilt
    Ptr BehaviourEllipse -> CUInt -> CDouble -> IO ()
clutter_behaviour_ellipse_set_angle_tilt Ptr BehaviourEllipse
self' CUInt
axis' CDouble
angleTilt'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetAngleTiltMethodInfo
instance (signature ~ (Clutter.Enums.RotateAxis -> Double -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetAngleTiltMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetAngleTilt

instance O.OverloadedMethodInfo BehaviourEllipseSetAngleTiltMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetAngleTilt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetAngleTilt"
        })


#endif

-- method BehaviourEllipse::set_center
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x coordinace of centre"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y coordinace of centre"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_center" clutter_behaviour_ellipse_set_center :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO ()

-- | Sets the center of the elliptical path to the point represented by knot.
-- 
-- /Since: 0.4/
behaviourEllipseSetCenter ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Int32
    -- ^ /@x@/: x coordinace of centre
    -> Int32
    -- ^ /@y@/: y coordinace of centre
    -> m ()
behaviourEllipseSetCenter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> Int32 -> Int32 -> m ()
behaviourEllipseSetCenter a
self Int32
x Int32
y = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr BehaviourEllipse -> Int32 -> Int32 -> IO ()
clutter_behaviour_ellipse_set_center Ptr BehaviourEllipse
self' Int32
x Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetCenterMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetCenterMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetCenter

instance O.OverloadedMethodInfo BehaviourEllipseSetCenterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetCenter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetCenter"
        })


#endif

-- method BehaviourEllipse::set_direction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "direction"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "RotateDirection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation direction"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_direction" clutter_behaviour_ellipse_set_direction :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    CUInt ->                                -- direction : TInterface (Name {namespace = "Clutter", name = "RotateDirection"})
    IO ()

-- | Sets the rotation direction used by the ellipse behaviour.
-- 
-- /Since: 0.4/
behaviourEllipseSetDirection ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Clutter.Enums.RotateDirection
    -- ^ /@direction@/: the rotation direction
    -> m ()
behaviourEllipseSetDirection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> RotateDirection -> m ()
behaviourEllipseSetDirection a
self RotateDirection
direction = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    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 BehaviourEllipse -> CUInt -> IO ()
clutter_behaviour_ellipse_set_direction Ptr BehaviourEllipse
self' CUInt
direction'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetDirectionMethodInfo
instance (signature ~ (Clutter.Enums.RotateDirection -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetDirectionMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetDirection

instance O.OverloadedMethodInfo BehaviourEllipseSetDirectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetDirection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetDirection"
        })


#endif

-- method BehaviourEllipse::set_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height of the ellipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_height" clutter_behaviour_ellipse_set_height :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Sets the height of the elliptical path.
-- 
-- /Since: 0.4/
behaviourEllipseSetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Int32
    -- ^ /@height@/: height of the ellipse
    -> m ()
behaviourEllipseSetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> Int32 -> m ()
behaviourEllipseSetHeight a
self Int32
height = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr BehaviourEllipse -> Int32 -> IO ()
clutter_behaviour_ellipse_set_height Ptr BehaviourEllipse
self' Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetHeightMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetHeightMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetHeight

instance O.OverloadedMethodInfo BehaviourEllipseSetHeightMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetHeight"
        })


#endif

-- method BehaviourEllipse::set_tilt
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle_tilt_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "tilt of the elipse around the center in X axis in degrees."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle_tilt_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "tilt of the elipse around the center in Y axis in degrees."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "angle_tilt_z"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "tilt of the elipse around the center in Z axis in degrees."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_tilt" clutter_behaviour_ellipse_set_tilt :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    CDouble ->                              -- angle_tilt_x : TBasicType TDouble
    CDouble ->                              -- angle_tilt_y : TBasicType TDouble
    CDouble ->                              -- angle_tilt_z : TBasicType TDouble
    IO ()

-- | Sets the angles at which the ellipse should be tilted around it\'s center.
-- 
-- /Since: 0.4/
behaviourEllipseSetTilt ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Double
    -- ^ /@angleTiltX@/: tilt of the elipse around the center in X axis in degrees.
    -> Double
    -- ^ /@angleTiltY@/: tilt of the elipse around the center in Y axis in degrees.
    -> Double
    -- ^ /@angleTiltZ@/: tilt of the elipse around the center in Z axis in degrees.
    -> m ()
behaviourEllipseSetTilt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> Double -> Double -> Double -> m ()
behaviourEllipseSetTilt a
self Double
angleTiltX Double
angleTiltY Double
angleTiltZ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let angleTiltX' :: CDouble
angleTiltX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleTiltX
    let angleTiltY' :: CDouble
angleTiltY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleTiltY
    let angleTiltZ' :: CDouble
angleTiltZ' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
angleTiltZ
    Ptr BehaviourEllipse -> CDouble -> CDouble -> CDouble -> IO ()
clutter_behaviour_ellipse_set_tilt Ptr BehaviourEllipse
self' CDouble
angleTiltX' CDouble
angleTiltY' CDouble
angleTiltZ'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetTiltMethodInfo
instance (signature ~ (Double -> Double -> Double -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetTiltMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetTilt

instance O.OverloadedMethodInfo BehaviourEllipseSetTiltMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetTilt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetTilt"
        })


#endif

-- method BehaviourEllipse::set_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "BehaviourEllipse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBehaviourEllipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width of the ellipse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_behaviour_ellipse_set_width" clutter_behaviour_ellipse_set_width :: 
    Ptr BehaviourEllipse ->                 -- self : TInterface (Name {namespace = "Clutter", name = "BehaviourEllipse"})
    Int32 ->                                -- width : TBasicType TInt
    IO ()

-- | Sets the width of the elliptical path.
-- 
-- /Since: 0.4/
behaviourEllipseSetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
    a
    -- ^ /@self@/: a t'GI.Clutter.Objects.BehaviourEllipse.BehaviourEllipse'
    -> Int32
    -- ^ /@width@/: width of the ellipse
    -> m ()
behaviourEllipseSetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBehaviourEllipse a) =>
a -> Int32 -> m ()
behaviourEllipseSetWidth a
self Int32
width = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BehaviourEllipse
self' <- a -> IO (Ptr BehaviourEllipse)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr BehaviourEllipse -> Int32 -> IO ()
clutter_behaviour_ellipse_set_width Ptr BehaviourEllipse
self' Int32
width
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BehaviourEllipseSetWidthMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsBehaviourEllipse a) => O.OverloadedMethod BehaviourEllipseSetWidthMethodInfo a signature where
    overloadedMethod = behaviourEllipseSetWidth

instance O.OverloadedMethodInfo BehaviourEllipseSetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BehaviourEllipse.behaviourEllipseSetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-BehaviourEllipse.html#v:behaviourEllipseSetWidth"
        })


#endif