{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Clutter.Objects.DeformEffect
(
DeformEffect(..) ,
IsDeformEffect ,
toDeformEffect ,
#if defined(ENABLE_OVERLOADING)
ResolveDeformEffectMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeformEffectGetBackMaterialMethodInfo ,
#endif
deformEffectGetBackMaterial ,
#if defined(ENABLE_OVERLOADING)
DeformEffectGetNTilesMethodInfo ,
#endif
deformEffectGetNTiles ,
#if defined(ENABLE_OVERLOADING)
DeformEffectInvalidateMethodInfo ,
#endif
deformEffectInvalidate ,
#if defined(ENABLE_OVERLOADING)
DeformEffectSetBackMaterialMethodInfo ,
#endif
deformEffectSetBackMaterial ,
#if defined(ENABLE_OVERLOADING)
DeformEffectSetNTilesMethodInfo ,
#endif
deformEffectSetNTiles ,
#if defined(ENABLE_OVERLOADING)
DeformEffectXTilesPropertyInfo ,
#endif
constructDeformEffectXTiles ,
#if defined(ENABLE_OVERLOADING)
deformEffectXTiles ,
#endif
getDeformEffectXTiles ,
setDeformEffectXTiles ,
#if defined(ENABLE_OVERLOADING)
DeformEffectYTilesPropertyInfo ,
#endif
constructDeformEffectYTiles ,
#if defined(ENABLE_OVERLOADING)
deformEffectYTiles ,
#endif
getDeformEffectYTiles ,
setDeformEffectYTiles ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.RectangleInt as Cairo.RectangleInt
import qualified GI.Clutter.Callbacks as Clutter.Callbacks
import {-# SOURCE #-} qualified GI.Clutter.Enums as Clutter.Enums
import {-# SOURCE #-} qualified GI.Clutter.Flags as Clutter.Flags
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Animatable as Clutter.Animatable
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Container as Clutter.Container
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Content as Clutter.Content
import {-# SOURCE #-} qualified GI.Clutter.Interfaces.Scriptable as Clutter.Scriptable
import {-# SOURCE #-} qualified GI.Clutter.Objects.Action as Clutter.Action
import {-# SOURCE #-} qualified GI.Clutter.Objects.Actor as Clutter.Actor
import {-# SOURCE #-} qualified GI.Clutter.Objects.ActorMeta as Clutter.ActorMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Alpha as Clutter.Alpha
import {-# SOURCE #-} qualified GI.Clutter.Objects.Animation as Clutter.Animation
import {-# SOURCE #-} qualified GI.Clutter.Objects.Animator as Clutter.Animator
import {-# SOURCE #-} qualified GI.Clutter.Objects.Backend as Clutter.Backend
import {-# SOURCE #-} qualified GI.Clutter.Objects.ChildMeta as Clutter.ChildMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Constraint as Clutter.Constraint
import {-# SOURCE #-} qualified GI.Clutter.Objects.DeviceManager as Clutter.DeviceManager
import {-# SOURCE #-} qualified GI.Clutter.Objects.Effect as Clutter.Effect
import {-# SOURCE #-} qualified GI.Clutter.Objects.Group as Clutter.Group
import {-# SOURCE #-} qualified GI.Clutter.Objects.InputDevice as Clutter.InputDevice
import {-# SOURCE #-} qualified GI.Clutter.Objects.Interval as Clutter.Interval
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutManager as Clutter.LayoutManager
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutMeta as Clutter.LayoutMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.OffscreenEffect as Clutter.OffscreenEffect
import {-# SOURCE #-} qualified GI.Clutter.Objects.Script as Clutter.Script
import {-# SOURCE #-} qualified GI.Clutter.Objects.Shader as Clutter.Shader
import {-# SOURCE #-} qualified GI.Clutter.Objects.Stage as Clutter.Stage
import {-# SOURCE #-} qualified GI.Clutter.Objects.State as Clutter.State
import {-# SOURCE #-} qualified GI.Clutter.Objects.Timeline as Clutter.Timeline
import {-# SOURCE #-} qualified GI.Clutter.Objects.Transition as Clutter.Transition
import {-# SOURCE #-} qualified GI.Clutter.Structs.ActorBox as Clutter.ActorBox
import {-# SOURCE #-} qualified GI.Clutter.Structs.AnimatorKey as Clutter.AnimatorKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.ButtonEvent as Clutter.ButtonEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Color as Clutter.Color
import {-# SOURCE #-} qualified GI.Clutter.Structs.CrossingEvent as Clutter.CrossingEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.EventSequence as Clutter.EventSequence
import {-# SOURCE #-} qualified GI.Clutter.Structs.Fog as Clutter.Fog
import {-# SOURCE #-} qualified GI.Clutter.Structs.Geometry as Clutter.Geometry
import {-# SOURCE #-} qualified GI.Clutter.Structs.KeyEvent as Clutter.KeyEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Margin as Clutter.Margin
import {-# SOURCE #-} qualified GI.Clutter.Structs.Matrix as Clutter.Matrix
import {-# SOURCE #-} qualified GI.Clutter.Structs.MotionEvent as Clutter.MotionEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.PaintVolume as Clutter.PaintVolume
import {-# SOURCE #-} qualified GI.Clutter.Structs.Perspective as Clutter.Perspective
import {-# SOURCE #-} qualified GI.Clutter.Structs.Point as Clutter.Point
import {-# SOURCE #-} qualified GI.Clutter.Structs.Rect as Clutter.Rect
import {-# SOURCE #-} qualified GI.Clutter.Structs.ScrollEvent as Clutter.ScrollEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Size as Clutter.Size
import {-# SOURCE #-} qualified GI.Clutter.Structs.StateKey as Clutter.StateKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.Vertex as Clutter.Vertex
import {-# SOURCE #-} qualified GI.Clutter.Unions.Event as Clutter.Event
import qualified GI.Cogl.Structs.Material as Cogl.Material
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ObjectClass as GObject.ObjectClass
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Json.Structs.Node as Json.Node
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.Layout as Pango.Layout
#else
import {-# SOURCE #-} qualified GI.Clutter.Objects.ActorMeta as Clutter.ActorMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Effect as Clutter.Effect
import {-# SOURCE #-} qualified GI.Clutter.Objects.OffscreenEffect as Clutter.OffscreenEffect
import qualified GI.GObject.Objects.Object as GObject.Object
#endif
newtype DeformEffect = DeformEffect (SP.ManagedPtr DeformEffect)
deriving (DeformEffect -> DeformEffect -> Bool
(DeformEffect -> DeformEffect -> Bool)
-> (DeformEffect -> DeformEffect -> Bool) -> Eq DeformEffect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeformEffect -> DeformEffect -> Bool
== :: DeformEffect -> DeformEffect -> Bool
$c/= :: DeformEffect -> DeformEffect -> Bool
/= :: DeformEffect -> DeformEffect -> Bool
Eq)
instance SP.ManagedPtrNewtype DeformEffect where
toManagedPtr :: DeformEffect -> ManagedPtr DeformEffect
toManagedPtr (DeformEffect ManagedPtr DeformEffect
p) = ManagedPtr DeformEffect
p
foreign import ccall "clutter_deform_effect_get_type"
c_clutter_deform_effect_get_type :: IO B.Types.GType
instance B.Types.TypedObject DeformEffect where
glibType :: IO GType
glibType = IO GType
c_clutter_deform_effect_get_type
instance B.Types.GObject DeformEffect
class (SP.GObject o, O.IsDescendantOf DeformEffect o) => IsDeformEffect o
instance (SP.GObject o, O.IsDescendantOf DeformEffect o) => IsDeformEffect o
instance O.HasParentTypes DeformEffect
type instance O.ParentTypes DeformEffect = '[Clutter.OffscreenEffect.OffscreenEffect, Clutter.Effect.Effect, Clutter.ActorMeta.ActorMeta, GObject.Object.Object]
toDeformEffect :: (MIO.MonadIO m, IsDeformEffect o) => o -> m DeformEffect
toDeformEffect :: forall (m :: * -> *) o.
(MonadIO m, IsDeformEffect o) =>
o -> m DeformEffect
toDeformEffect = IO DeformEffect -> m DeformEffect
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DeformEffect -> m DeformEffect)
-> (o -> IO DeformEffect) -> o -> m DeformEffect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DeformEffect -> DeformEffect) -> o -> IO DeformEffect
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DeformEffect -> DeformEffect
DeformEffect
instance B.GValue.IsGValue (Maybe DeformEffect) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_deform_effect_get_type
gvalueSet_ :: Ptr GValue -> Maybe DeformEffect -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DeformEffect
P.Nothing = Ptr GValue -> Ptr DeformEffect -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DeformEffect
forall a. Ptr a
FP.nullPtr :: FP.Ptr DeformEffect)
gvalueSet_ Ptr GValue
gv (P.Just DeformEffect
obj) = DeformEffect -> (Ptr DeformEffect -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DeformEffect
obj (Ptr GValue -> Ptr DeformEffect -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DeformEffect)
gvalueGet_ Ptr GValue
gv = do
Ptr DeformEffect
ptr <- Ptr GValue -> IO (Ptr DeformEffect)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DeformEffect)
if Ptr DeformEffect
ptr Ptr DeformEffect -> Ptr DeformEffect -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DeformEffect
forall a. Ptr a
FP.nullPtr
then DeformEffect -> Maybe DeformEffect
forall a. a -> Maybe a
P.Just (DeformEffect -> Maybe DeformEffect)
-> IO DeformEffect -> IO (Maybe DeformEffect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DeformEffect -> DeformEffect)
-> Ptr DeformEffect -> IO DeformEffect
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DeformEffect -> DeformEffect
DeformEffect Ptr DeformEffect
ptr
else Maybe DeformEffect -> IO (Maybe DeformEffect)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeformEffect
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDeformEffectMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDeformEffectMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDeformEffectMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDeformEffectMethod "createTexture" o = Clutter.OffscreenEffect.OffscreenEffectCreateTextureMethodInfo
ResolveDeformEffectMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDeformEffectMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDeformEffectMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDeformEffectMethod "invalidate" o = DeformEffectInvalidateMethodInfo
ResolveDeformEffectMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDeformEffectMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDeformEffectMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDeformEffectMethod "paintTarget" o = Clutter.OffscreenEffect.OffscreenEffectPaintTargetMethodInfo
ResolveDeformEffectMethod "queueRepaint" o = Clutter.Effect.EffectQueueRepaintMethodInfo
ResolveDeformEffectMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDeformEffectMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDeformEffectMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDeformEffectMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDeformEffectMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDeformEffectMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDeformEffectMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDeformEffectMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDeformEffectMethod "getActor" o = Clutter.ActorMeta.ActorMetaGetActorMethodInfo
ResolveDeformEffectMethod "getBackMaterial" o = DeformEffectGetBackMaterialMethodInfo
ResolveDeformEffectMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDeformEffectMethod "getEnabled" o = Clutter.ActorMeta.ActorMetaGetEnabledMethodInfo
ResolveDeformEffectMethod "getNTiles" o = DeformEffectGetNTilesMethodInfo
ResolveDeformEffectMethod "getName" o = Clutter.ActorMeta.ActorMetaGetNameMethodInfo
ResolveDeformEffectMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDeformEffectMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDeformEffectMethod "getTarget" o = Clutter.OffscreenEffect.OffscreenEffectGetTargetMethodInfo
ResolveDeformEffectMethod "getTargetRect" o = Clutter.OffscreenEffect.OffscreenEffectGetTargetRectMethodInfo
ResolveDeformEffectMethod "getTargetSize" o = Clutter.OffscreenEffect.OffscreenEffectGetTargetSizeMethodInfo
ResolveDeformEffectMethod "getTexture" o = Clutter.OffscreenEffect.OffscreenEffectGetTextureMethodInfo
ResolveDeformEffectMethod "setBackMaterial" o = DeformEffectSetBackMaterialMethodInfo
ResolveDeformEffectMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDeformEffectMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDeformEffectMethod "setEnabled" o = Clutter.ActorMeta.ActorMetaSetEnabledMethodInfo
ResolveDeformEffectMethod "setNTiles" o = DeformEffectSetNTilesMethodInfo
ResolveDeformEffectMethod "setName" o = Clutter.ActorMeta.ActorMetaSetNameMethodInfo
ResolveDeformEffectMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDeformEffectMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDeformEffectMethod t DeformEffect, O.OverloadedMethod info DeformEffect p) => OL.IsLabel t (DeformEffect -> 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 ~ ResolveDeformEffectMethod t DeformEffect, O.OverloadedMethod info DeformEffect p, R.HasField t DeformEffect p) => R.HasField t DeformEffect p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDeformEffectMethod t DeformEffect, O.OverloadedMethodInfo info DeformEffect) => OL.IsLabel t (O.MethodProxy info DeformEffect) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDeformEffectXTiles :: (MonadIO m, IsDeformEffect o) => o -> m Word32
getDeformEffectXTiles :: forall (m :: * -> *) o.
(MonadIO m, IsDeformEffect o) =>
o -> m Word32
getDeformEffectXTiles o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"x-tiles"
setDeformEffectXTiles :: (MonadIO m, IsDeformEffect o) => o -> Word32 -> m ()
setDeformEffectXTiles :: forall (m :: * -> *) o.
(MonadIO m, IsDeformEffect o) =>
o -> Word32 -> m ()
setDeformEffectXTiles o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"x-tiles" Word32
val
constructDeformEffectXTiles :: (IsDeformEffect o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDeformEffectXTiles :: forall o (m :: * -> *).
(IsDeformEffect o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDeformEffectXTiles Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"x-tiles" Word32
val
#if defined(ENABLE_OVERLOADING)
data DeformEffectXTilesPropertyInfo
instance AttrInfo DeformEffectXTilesPropertyInfo where
type AttrAllowedOps DeformEffectXTilesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DeformEffectXTilesPropertyInfo = IsDeformEffect
type AttrSetTypeConstraint DeformEffectXTilesPropertyInfo = (~) Word32
type AttrTransferTypeConstraint DeformEffectXTilesPropertyInfo = (~) Word32
type AttrTransferType DeformEffectXTilesPropertyInfo = Word32
type AttrGetType DeformEffectXTilesPropertyInfo = Word32
type AttrLabel DeformEffectXTilesPropertyInfo = "x-tiles"
type AttrOrigin DeformEffectXTilesPropertyInfo = DeformEffect
attrGet = getDeformEffectXTiles
attrSet = setDeformEffectXTiles
attrTransfer _ v = do
return v
attrConstruct = constructDeformEffectXTiles
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.DeformEffect.xTiles"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeformEffect.html#g:attr:xTiles"
})
#endif
getDeformEffectYTiles :: (MonadIO m, IsDeformEffect o) => o -> m Word32
getDeformEffectYTiles :: forall (m :: * -> *) o.
(MonadIO m, IsDeformEffect o) =>
o -> m Word32
getDeformEffectYTiles o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"y-tiles"
setDeformEffectYTiles :: (MonadIO m, IsDeformEffect o) => o -> Word32 -> m ()
setDeformEffectYTiles :: forall (m :: * -> *) o.
(MonadIO m, IsDeformEffect o) =>
o -> Word32 -> m ()
setDeformEffectYTiles o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"y-tiles" Word32
val
constructDeformEffectYTiles :: (IsDeformEffect o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDeformEffectYTiles :: forall o (m :: * -> *).
(IsDeformEffect o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDeformEffectYTiles Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"y-tiles" Word32
val
#if defined(ENABLE_OVERLOADING)
data DeformEffectYTilesPropertyInfo
instance AttrInfo DeformEffectYTilesPropertyInfo where
type AttrAllowedOps DeformEffectYTilesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint DeformEffectYTilesPropertyInfo = IsDeformEffect
type AttrSetTypeConstraint DeformEffectYTilesPropertyInfo = (~) Word32
type AttrTransferTypeConstraint DeformEffectYTilesPropertyInfo = (~) Word32
type AttrTransferType DeformEffectYTilesPropertyInfo = Word32
type AttrGetType DeformEffectYTilesPropertyInfo = Word32
type AttrLabel DeformEffectYTilesPropertyInfo = "y-tiles"
type AttrOrigin DeformEffectYTilesPropertyInfo = DeformEffect
attrGet = getDeformEffectYTiles
attrSet = setDeformEffectYTiles
attrTransfer _ v = do
return v
attrConstruct = constructDeformEffectYTiles
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.DeformEffect.yTiles"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeformEffect.html#g:attr:yTiles"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeformEffect
type instance O.AttributeList DeformEffect = DeformEffectAttributeList
type DeformEffectAttributeList = ('[ '("actor", Clutter.ActorMeta.ActorMetaActorPropertyInfo), '("enabled", Clutter.ActorMeta.ActorMetaEnabledPropertyInfo), '("name", Clutter.ActorMeta.ActorMetaNamePropertyInfo), '("xTiles", DeformEffectXTilesPropertyInfo), '("yTiles", DeformEffectYTilesPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
deformEffectXTiles :: AttrLabelProxy "xTiles"
deformEffectXTiles = AttrLabelProxy
deformEffectYTiles :: AttrLabelProxy "yTiles"
deformEffectYTiles = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DeformEffect = DeformEffectSignalList
type DeformEffectSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "clutter_deform_effect_get_back_material" clutter_deform_effect_get_back_material ::
Ptr DeformEffect ->
IO (Ptr ())
deformEffectGetBackMaterial ::
(B.CallStack.HasCallStack, MonadIO m, IsDeformEffect a) =>
a
-> m (Ptr ())
deformEffectGetBackMaterial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeformEffect a) =>
a -> m (Ptr ())
deformEffectGetBackMaterial a
effect = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
Ptr DeformEffect
effect' <- a -> IO (Ptr DeformEffect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
effect
Ptr ()
result <- Ptr DeformEffect -> IO (Ptr ())
clutter_deform_effect_get_back_material Ptr DeformEffect
effect'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
effect
Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data DeformEffectGetBackMaterialMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsDeformEffect a) => O.OverloadedMethod DeformEffectGetBackMaterialMethodInfo a signature where
overloadedMethod = deformEffectGetBackMaterial
instance O.OverloadedMethodInfo DeformEffectGetBackMaterialMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.DeformEffect.deformEffectGetBackMaterial",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeformEffect.html#v:deformEffectGetBackMaterial"
})
#endif
foreign import ccall "clutter_deform_effect_get_n_tiles" clutter_deform_effect_get_n_tiles ::
Ptr DeformEffect ->
Ptr Word32 ->
Ptr Word32 ->
IO ()
deformEffectGetNTiles ::
(B.CallStack.HasCallStack, MonadIO m, IsDeformEffect a) =>
a
-> m ((Word32, Word32))
deformEffectGetNTiles :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeformEffect a) =>
a -> m (Word32, Word32)
deformEffectGetNTiles a
effect = IO (Word32, Word32) -> m (Word32, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word32, Word32) -> m (Word32, Word32))
-> IO (Word32, Word32) -> m (Word32, Word32)
forall a b. (a -> b) -> a -> b
$ do
Ptr DeformEffect
effect' <- a -> IO (Ptr DeformEffect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
effect
Ptr Word32
xTiles <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr Word32
yTiles <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr DeformEffect -> Ptr Word32 -> Ptr Word32 -> IO ()
clutter_deform_effect_get_n_tiles Ptr DeformEffect
effect' Ptr Word32
xTiles Ptr Word32
yTiles
Word32
xTiles' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
xTiles
Word32
yTiles' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
yTiles
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
effect
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
xTiles
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
yTiles
(Word32, Word32) -> IO (Word32, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
xTiles', Word32
yTiles')
#if defined(ENABLE_OVERLOADING)
data DeformEffectGetNTilesMethodInfo
instance (signature ~ (m ((Word32, Word32))), MonadIO m, IsDeformEffect a) => O.OverloadedMethod DeformEffectGetNTilesMethodInfo a signature where
overloadedMethod = deformEffectGetNTiles
instance O.OverloadedMethodInfo DeformEffectGetNTilesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.DeformEffect.deformEffectGetNTiles",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeformEffect.html#v:deformEffectGetNTiles"
})
#endif
foreign import ccall "clutter_deform_effect_invalidate" clutter_deform_effect_invalidate ::
Ptr DeformEffect ->
IO ()
deformEffectInvalidate ::
(B.CallStack.HasCallStack, MonadIO m, IsDeformEffect a) =>
a
-> m ()
deformEffectInvalidate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeformEffect a) =>
a -> m ()
deformEffectInvalidate a
effect = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DeformEffect
effect' <- a -> IO (Ptr DeformEffect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
effect
Ptr DeformEffect -> IO ()
clutter_deform_effect_invalidate Ptr DeformEffect
effect'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
effect
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DeformEffectInvalidateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDeformEffect a) => O.OverloadedMethod DeformEffectInvalidateMethodInfo a signature where
overloadedMethod = deformEffectInvalidate
instance O.OverloadedMethodInfo DeformEffectInvalidateMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.DeformEffect.deformEffectInvalidate",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeformEffect.html#v:deformEffectInvalidate"
})
#endif
foreign import ccall "clutter_deform_effect_set_back_material" clutter_deform_effect_set_back_material ::
Ptr DeformEffect ->
Ptr () ->
IO ()
deformEffectSetBackMaterial ::
(B.CallStack.HasCallStack, MonadIO m, IsDeformEffect a) =>
a
-> Ptr ()
-> m ()
deformEffectSetBackMaterial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeformEffect a) =>
a -> Ptr () -> m ()
deformEffectSetBackMaterial a
effect Ptr ()
material = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DeformEffect
effect' <- a -> IO (Ptr DeformEffect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
effect
Ptr DeformEffect -> Ptr () -> IO ()
clutter_deform_effect_set_back_material Ptr DeformEffect
effect' Ptr ()
material
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
effect
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DeformEffectSetBackMaterialMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m, IsDeformEffect a) => O.OverloadedMethod DeformEffectSetBackMaterialMethodInfo a signature where
overloadedMethod = deformEffectSetBackMaterial
instance O.OverloadedMethodInfo DeformEffectSetBackMaterialMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.DeformEffect.deformEffectSetBackMaterial",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeformEffect.html#v:deformEffectSetBackMaterial"
})
#endif
foreign import ccall "clutter_deform_effect_set_n_tiles" clutter_deform_effect_set_n_tiles ::
Ptr DeformEffect ->
Word32 ->
Word32 ->
IO ()
deformEffectSetNTiles ::
(B.CallStack.HasCallStack, MonadIO m, IsDeformEffect a) =>
a
-> Word32
-> Word32
-> m ()
deformEffectSetNTiles :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeformEffect a) =>
a -> Word32 -> Word32 -> m ()
deformEffectSetNTiles a
effect Word32
xTiles Word32
yTiles = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr DeformEffect
effect' <- a -> IO (Ptr DeformEffect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
effect
Ptr DeformEffect -> Word32 -> Word32 -> IO ()
clutter_deform_effect_set_n_tiles Ptr DeformEffect
effect' Word32
xTiles Word32
yTiles
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
effect
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DeformEffectSetNTilesMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m, IsDeformEffect a) => O.OverloadedMethod DeformEffectSetNTilesMethodInfo a signature where
overloadedMethod = deformEffectSetNTiles
instance O.OverloadedMethodInfo DeformEffectSetNTilesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Clutter.Objects.DeformEffect.deformEffectSetNTiles",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-DeformEffect.html#v:deformEffectSetNTiles"
})
#endif