{-# 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.Effect.Effect' structure contains only private data and should
-- be accessed using the provided API
-- 
-- /Since: 1.4/

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

module GI.Clutter.Objects.Effect
    ( 

-- * Exported types
    Effect(..)                              ,
    IsEffect                                ,
    toEffect                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [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"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [queueRepaint]("GI.Clutter.Objects.Effect#g:method:queueRepaint"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [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
-- [getActor]("GI.Clutter.Objects.ActorMeta#g:method:getActor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEnabled]("GI.Clutter.Objects.ActorMeta#g:method:getEnabled"), [getName]("GI.Clutter.Objects.ActorMeta#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setEnabled]("GI.Clutter.Objects.ActorMeta#g:method:setEnabled"), [setName]("GI.Clutter.Objects.ActorMeta#g:method:setName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveEffectMethod                     ,
#endif

-- ** queueRepaint #method:queueRepaint#

#if defined(ENABLE_OVERLOADING)
    EffectQueueRepaintMethodInfo            ,
#endif
    effectQueueRepaint                      ,




    ) 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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#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.Group as Clutter.Group
import {-# SOURCE #-} qualified GI.Clutter.Objects.InputDevice as Clutter.InputDevice
import {-# SOURCE #-} qualified GI.Clutter.Objects.Interval as Clutter.Interval
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutManager as Clutter.LayoutManager
import {-# SOURCE #-} qualified GI.Clutter.Objects.LayoutMeta as Clutter.LayoutMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.Script as Clutter.Script
import {-# SOURCE #-} qualified GI.Clutter.Objects.Shader as Clutter.Shader
import {-# SOURCE #-} qualified GI.Clutter.Objects.Stage as Clutter.Stage
import {-# SOURCE #-} qualified GI.Clutter.Objects.State as Clutter.State
import {-# SOURCE #-} qualified GI.Clutter.Objects.Timeline as Clutter.Timeline
import {-# SOURCE #-} qualified GI.Clutter.Objects.Transition as Clutter.Transition
import {-# SOURCE #-} qualified GI.Clutter.Structs.ActorBox as Clutter.ActorBox
import {-# SOURCE #-} qualified GI.Clutter.Structs.AnimatorKey as Clutter.AnimatorKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.ButtonEvent as Clutter.ButtonEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Color as Clutter.Color
import {-# SOURCE #-} qualified GI.Clutter.Structs.CrossingEvent as Clutter.CrossingEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.EventSequence as Clutter.EventSequence
import {-# SOURCE #-} qualified GI.Clutter.Structs.Fog as Clutter.Fog
import {-# SOURCE #-} qualified GI.Clutter.Structs.Geometry as Clutter.Geometry
import {-# SOURCE #-} qualified GI.Clutter.Structs.KeyEvent as Clutter.KeyEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Margin as Clutter.Margin
import {-# SOURCE #-} qualified GI.Clutter.Structs.Matrix as Clutter.Matrix
import {-# SOURCE #-} qualified GI.Clutter.Structs.MotionEvent as Clutter.MotionEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.PaintVolume as Clutter.PaintVolume
import {-# SOURCE #-} qualified GI.Clutter.Structs.Perspective as Clutter.Perspective
import {-# SOURCE #-} qualified GI.Clutter.Structs.Point as Clutter.Point
import {-# SOURCE #-} qualified GI.Clutter.Structs.Rect as Clutter.Rect
import {-# SOURCE #-} qualified GI.Clutter.Structs.ScrollEvent as Clutter.ScrollEvent
import {-# SOURCE #-} qualified GI.Clutter.Structs.Size as Clutter.Size
import {-# SOURCE #-} qualified GI.Clutter.Structs.StateKey as Clutter.StateKey
import {-# SOURCE #-} qualified GI.Clutter.Structs.Vertex as Clutter.Vertex
import {-# SOURCE #-} qualified GI.Clutter.Unions.Event as Clutter.Event
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ObjectClass as GObject.ObjectClass
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Json.Structs.Node as Json.Node
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.Layout as Pango.Layout

#else
import {-# SOURCE #-} qualified GI.Clutter.Objects.ActorMeta as Clutter.ActorMeta
import qualified GI.GObject.Objects.Object as GObject.Object

#endif

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

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

foreign import ccall "clutter_effect_get_type"
    c_clutter_effect_get_type :: IO B.Types.GType

instance B.Types.TypedObject Effect where
    glibType :: IO GType
glibType = IO GType
c_clutter_effect_get_type

instance B.Types.GObject Effect

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

instance O.HasParentTypes Effect
type instance O.ParentTypes Effect = '[Clutter.ActorMeta.ActorMeta, GObject.Object.Object]

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

-- | Convert 'Effect' 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 Effect) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_effect_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Effect -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Effect
P.Nothing = Ptr GValue -> Ptr Effect -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Effect
forall a. Ptr a
FP.nullPtr :: FP.Ptr Effect)
    gvalueSet_ Ptr GValue
gv (P.Just Effect
obj) = Effect -> (Ptr Effect -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Effect
obj (Ptr GValue -> Ptr Effect -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Effect)
gvalueGet_ Ptr GValue
gv = do
        Ptr Effect
ptr <- Ptr GValue -> IO (Ptr Effect)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Effect)
        if Ptr Effect
ptr Ptr Effect -> Ptr Effect -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Effect
forall a. Ptr a
FP.nullPtr
        then Effect -> Maybe Effect
forall a. a -> Maybe a
P.Just (Effect -> Maybe Effect) -> IO Effect -> IO (Maybe Effect)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Effect -> Effect) -> Ptr Effect -> IO Effect
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Effect -> Effect
Effect Ptr Effect
ptr
        else Maybe Effect -> IO (Maybe Effect)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Effect
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveEffectMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveEffectMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveEffectMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveEffectMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveEffectMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveEffectMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveEffectMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveEffectMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveEffectMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveEffectMethod "queueRepaint" o = EffectQueueRepaintMethodInfo
    ResolveEffectMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveEffectMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveEffectMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveEffectMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveEffectMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveEffectMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveEffectMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveEffectMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveEffectMethod "getActor" o = Clutter.ActorMeta.ActorMetaGetActorMethodInfo
    ResolveEffectMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveEffectMethod "getEnabled" o = Clutter.ActorMeta.ActorMetaGetEnabledMethodInfo
    ResolveEffectMethod "getName" o = Clutter.ActorMeta.ActorMetaGetNameMethodInfo
    ResolveEffectMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveEffectMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveEffectMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveEffectMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveEffectMethod "setEnabled" o = Clutter.ActorMeta.ActorMetaSetEnabledMethodInfo
    ResolveEffectMethod "setName" o = Clutter.ActorMeta.ActorMetaSetNameMethodInfo
    ResolveEffectMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveEffectMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Effect
type instance O.AttributeList Effect = EffectAttributeList
type EffectAttributeList = ('[ '("actor", Clutter.ActorMeta.ActorMetaActorPropertyInfo), '("enabled", Clutter.ActorMeta.ActorMetaEnabledPropertyInfo), '("name", Clutter.ActorMeta.ActorMetaNamePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Effect = EffectSignalList
type EffectSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Effect::queue_repaint
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "effect"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Effect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #ClutterEffect which needs redrawing"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_effect_queue_repaint" clutter_effect_queue_repaint :: 
    Ptr Effect ->                           -- effect : TInterface (Name {namespace = "Clutter", name = "Effect"})
    IO ()

-- | Queues a repaint of the effect. The effect can detect when the ‘paint’
-- method is called as a result of this function because it will not
-- have the 'GI.Clutter.Flags.EffectPaintFlagsActorDirty' flag set. In that case the
-- effect is free to assume that the actor has not changed its
-- appearance since the last time it was painted so it doesn\'t need to
-- call 'GI.Clutter.Objects.Actor.actorContinuePaint' if it can draw a cached
-- image. This is mostly intended for effects that are using a
-- @/CoglOffscreen/@ to redirect the actor (such as
-- @/ClutterOffscreenEffect/@). In that case the effect can save a bit of
-- rendering time by painting the cached texture without causing the
-- entire actor to be painted.
-- 
-- This function can be used by effects that have their own animatable
-- parameters. For example, an effect which adds a varying degree of a
-- red tint to an actor by redirecting it through a CoglOffscreen
-- might have a property to specify the level of tint. When this value
-- changes, the underlying actor doesn\'t need to be redrawn so the
-- effect can call 'GI.Clutter.Objects.Effect.effectQueueRepaint' to make sure the
-- effect is repainted.
-- 
-- Note however that modifying the position of the parent of an actor
-- may change the appearance of the actor because its transformation
-- matrix would change. In this case a redraw wouldn\'t be queued on
-- the actor itself so the 'GI.Clutter.Flags.EffectPaintFlagsActorDirty' would still
-- not be set. The effect can detect this case by keeping track of the
-- last modelview matrix that was used to render the actor and
-- veryifying that it remains the same in the next paint.
-- 
-- Any other effects that are layered on top of the passed in effect
-- will still be passed the 'GI.Clutter.Flags.EffectPaintFlagsActorDirty' flag. If
-- anything queues a redraw on the actor without specifying an effect
-- or with an effect that is lower in the chain of effects than this
-- one then that will override this call. In that case this effect
-- will instead be called with the 'GI.Clutter.Flags.EffectPaintFlagsActorDirty'
-- flag set.
-- 
-- /Since: 1.8/
effectQueueRepaint ::
    (B.CallStack.HasCallStack, MonadIO m, IsEffect a) =>
    a
    -- ^ /@effect@/: A t'GI.Clutter.Objects.Effect.Effect' which needs redrawing
    -> m ()
effectQueueRepaint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEffect a) =>
a -> m ()
effectQueueRepaint 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 Effect
effect' <- a -> IO (Ptr Effect)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
effect
    Ptr Effect -> IO ()
clutter_effect_queue_repaint Ptr Effect
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 EffectQueueRepaintMethodInfo
instance (signature ~ (m ()), MonadIO m, IsEffect a) => O.OverloadedMethod EffectQueueRepaintMethodInfo a signature where
    overloadedMethod = effectQueueRepaint

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


#endif