{-# 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.ActorMeta.ActorMeta' 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.ActorMeta
    ( 

-- * Exported types
    ActorMeta(..)                           ,
    IsActorMeta                             ,
    toActorMeta                             ,


 -- * 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"), [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)
    ResolveActorMetaMethod                  ,
#endif

-- ** getActor #method:getActor#

#if defined(ENABLE_OVERLOADING)
    ActorMetaGetActorMethodInfo             ,
#endif
    actorMetaGetActor                       ,


-- ** getEnabled #method:getEnabled#

#if defined(ENABLE_OVERLOADING)
    ActorMetaGetEnabledMethodInfo           ,
#endif
    actorMetaGetEnabled                     ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    ActorMetaGetNameMethodInfo              ,
#endif
    actorMetaGetName                        ,


-- ** setEnabled #method:setEnabled#

#if defined(ENABLE_OVERLOADING)
    ActorMetaSetEnabledMethodInfo           ,
#endif
    actorMetaSetEnabled                     ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    ActorMetaSetNameMethodInfo              ,
#endif
    actorMetaSetName                        ,




 -- * Properties


-- ** actor #attr:actor#
-- | The t'GI.Clutter.Objects.Actor.Actor' attached to the t'GI.Clutter.Objects.ActorMeta.ActorMeta' instance
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    ActorMetaActorPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    actorMetaActor                          ,
#endif
    getActorMetaActor                       ,


-- ** enabled #attr:enabled#
-- | Whether or not the t'GI.Clutter.Objects.ActorMeta.ActorMeta' is enabled
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    ActorMetaEnabledPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    actorMetaEnabled                        ,
#endif
    constructActorMetaEnabled               ,
    getActorMetaEnabled                     ,
    setActorMetaEnabled                     ,


-- ** name #attr:name#
-- | The unique name to access the t'GI.Clutter.Objects.ActorMeta.ActorMeta'
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    ActorMetaNamePropertyInfo               ,
#endif
#if defined(ENABLE_OVERLOADING)
    actorMetaName                           ,
#endif
    constructActorMetaName                  ,
    getActorMetaName                        ,
    setActorMetaName                        ,




    ) 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.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.Objects.Actor as Clutter.Actor
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "clutter_actor_meta_get_type"
    c_clutter_actor_meta_get_type :: IO B.Types.GType

instance B.Types.TypedObject ActorMeta where
    glibType :: IO GType
glibType = IO GType
c_clutter_actor_meta_get_type

instance B.Types.GObject ActorMeta

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

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

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

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

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

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

#endif

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

#endif

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

-- | Get the value of the “@actor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actorMeta #actor
-- @
getActorMetaActor :: (MonadIO m, IsActorMeta o) => o -> m Clutter.Actor.Actor
getActorMetaActor :: forall (m :: * -> *) o. (MonadIO m, IsActorMeta o) => o -> m Actor
getActorMetaActor o
obj = IO Actor -> m Actor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Actor -> m Actor) -> IO Actor -> m Actor
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Actor) -> IO Actor
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActorMetaActor" (IO (Maybe Actor) -> IO Actor) -> IO (Maybe Actor) -> IO Actor
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Actor -> Actor) -> IO (Maybe Actor)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"actor" ManagedPtr Actor -> Actor
Clutter.Actor.Actor

#if defined(ENABLE_OVERLOADING)
data ActorMetaActorPropertyInfo
instance AttrInfo ActorMetaActorPropertyInfo where
    type AttrAllowedOps ActorMetaActorPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ActorMetaActorPropertyInfo = IsActorMeta
    type AttrSetTypeConstraint ActorMetaActorPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ActorMetaActorPropertyInfo = (~) ()
    type AttrTransferType ActorMetaActorPropertyInfo = ()
    type AttrGetType ActorMetaActorPropertyInfo = Clutter.Actor.Actor
    type AttrLabel ActorMetaActorPropertyInfo = "actor"
    type AttrOrigin ActorMetaActorPropertyInfo = ActorMeta
    attrGet = getActorMetaActor
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.ActorMeta.actor"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-ActorMeta.html#g:attr:actor"
        })
#endif

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

-- | Get the value of the “@enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actorMeta #enabled
-- @
getActorMetaEnabled :: (MonadIO m, IsActorMeta o) => o -> m Bool
getActorMetaEnabled :: forall (m :: * -> *) o. (MonadIO m, IsActorMeta o) => o -> m Bool
getActorMetaEnabled o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"enabled"

-- | Set the value of the “@enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actorMeta [ #enabled 'Data.GI.Base.Attributes.:=' value ]
-- @
setActorMetaEnabled :: (MonadIO m, IsActorMeta o) => o -> Bool -> m ()
setActorMetaEnabled :: forall (m :: * -> *) o.
(MonadIO m, IsActorMeta o) =>
o -> Bool -> m ()
setActorMetaEnabled o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"enabled" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data ActorMetaEnabledPropertyInfo
instance AttrInfo ActorMetaEnabledPropertyInfo where
    type AttrAllowedOps ActorMetaEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ActorMetaEnabledPropertyInfo = IsActorMeta
    type AttrSetTypeConstraint ActorMetaEnabledPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ActorMetaEnabledPropertyInfo = (~) Bool
    type AttrTransferType ActorMetaEnabledPropertyInfo = Bool
    type AttrGetType ActorMetaEnabledPropertyInfo = Bool
    type AttrLabel ActorMetaEnabledPropertyInfo = "enabled"
    type AttrOrigin ActorMetaEnabledPropertyInfo = ActorMeta
    attrGet = getActorMetaEnabled
    attrSet = setActorMetaEnabled
    attrTransfer _ v = do
        return v
    attrConstruct = constructActorMetaEnabled
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.ActorMeta.enabled"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-ActorMeta.html#g:attr:enabled"
        })
#endif

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

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actorMeta #name
-- @
getActorMetaName :: (MonadIO m, IsActorMeta o) => o -> m T.Text
getActorMetaName :: forall (m :: * -> *) o. (MonadIO m, IsActorMeta o) => o -> m Text
getActorMetaName o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActorMetaName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"

-- | Set the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actorMeta [ #name 'Data.GI.Base.Attributes.:=' value ]
-- @
setActorMetaName :: (MonadIO m, IsActorMeta o) => o -> T.Text -> m ()
setActorMetaName :: forall (m :: * -> *) o.
(MonadIO m, IsActorMeta o) =>
o -> Text -> m ()
setActorMetaName o
obj Text
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 -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

#if defined(ENABLE_OVERLOADING)
data ActorMetaNamePropertyInfo
instance AttrInfo ActorMetaNamePropertyInfo where
    type AttrAllowedOps ActorMetaNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ActorMetaNamePropertyInfo = IsActorMeta
    type AttrSetTypeConstraint ActorMetaNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ActorMetaNamePropertyInfo = (~) T.Text
    type AttrTransferType ActorMetaNamePropertyInfo = T.Text
    type AttrGetType ActorMetaNamePropertyInfo = T.Text
    type AttrLabel ActorMetaNamePropertyInfo = "name"
    type AttrOrigin ActorMetaNamePropertyInfo = ActorMeta
    attrGet = getActorMetaName
    attrSet = setActorMetaName
    attrTransfer _ v = do
        return v
    attrConstruct = constructActorMetaName
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.ActorMeta.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-ActorMeta.html#g:attr:name"
        })
#endif

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

#if defined(ENABLE_OVERLOADING)
actorMetaActor :: AttrLabelProxy "actor"
actorMetaActor = AttrLabelProxy

actorMetaEnabled :: AttrLabelProxy "enabled"
actorMetaEnabled = AttrLabelProxy

actorMetaName :: AttrLabelProxy "name"
actorMetaName = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ActorMeta = ActorMetaSignalList
type ActorMetaSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "clutter_actor_meta_get_actor" clutter_actor_meta_get_actor :: 
    Ptr ActorMeta ->                        -- meta : TInterface (Name {namespace = "Clutter", name = "ActorMeta"})
    IO (Ptr Clutter.Actor.Actor)

-- | Retrieves a pointer to the t'GI.Clutter.Objects.Actor.Actor' that owns /@meta@/
-- 
-- /Since: 1.4/
actorMetaGetActor ::
    (B.CallStack.HasCallStack, MonadIO m, IsActorMeta a) =>
    a
    -- ^ /@meta@/: a t'GI.Clutter.Objects.ActorMeta.ActorMeta'
    -> m Clutter.Actor.Actor
    -- ^ __Returns:__ a pointer to a t'GI.Clutter.Objects.Actor.Actor' or 'P.Nothing'
actorMetaGetActor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActorMeta a) =>
a -> m Actor
actorMetaGetActor a
meta = IO Actor -> m Actor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Actor -> m Actor) -> IO Actor -> m Actor
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActorMeta
meta' <- a -> IO (Ptr ActorMeta)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
meta
    Ptr Actor
result <- Ptr ActorMeta -> IO (Ptr Actor)
clutter_actor_meta_get_actor Ptr ActorMeta
meta'
    Text -> Ptr Actor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actorMetaGetActor" Ptr Actor
result
    Actor
result' <- ((ManagedPtr Actor -> Actor) -> Ptr Actor -> IO Actor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Actor -> Actor
Clutter.Actor.Actor) Ptr Actor
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
meta
    Actor -> IO Actor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Actor
result'

#if defined(ENABLE_OVERLOADING)
data ActorMetaGetActorMethodInfo
instance (signature ~ (m Clutter.Actor.Actor), MonadIO m, IsActorMeta a) => O.OverloadedMethod ActorMetaGetActorMethodInfo a signature where
    overloadedMethod = actorMetaGetActor

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


#endif

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

foreign import ccall "clutter_actor_meta_get_enabled" clutter_actor_meta_get_enabled :: 
    Ptr ActorMeta ->                        -- meta : TInterface (Name {namespace = "Clutter", name = "ActorMeta"})
    IO CInt

-- | Retrieves whether /@meta@/ is enabled
-- 
-- /Since: 1.4/
actorMetaGetEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsActorMeta a) =>
    a
    -- ^ /@meta@/: a t'GI.Clutter.Objects.ActorMeta.ActorMeta'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the t'GI.Clutter.Objects.ActorMeta.ActorMeta' instance is enabled
actorMetaGetEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActorMeta a) =>
a -> m Bool
actorMetaGetEnabled a
meta = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActorMeta
meta' <- a -> IO (Ptr ActorMeta)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
meta
    CInt
result <- Ptr ActorMeta -> IO CInt
clutter_actor_meta_get_enabled Ptr ActorMeta
meta'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
meta
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ActorMetaGetEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsActorMeta a) => O.OverloadedMethod ActorMetaGetEnabledMethodInfo a signature where
    overloadedMethod = actorMetaGetEnabled

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


#endif

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

foreign import ccall "clutter_actor_meta_get_name" clutter_actor_meta_get_name :: 
    Ptr ActorMeta ->                        -- meta : TInterface (Name {namespace = "Clutter", name = "ActorMeta"})
    IO CString

-- | Retrieves the name set using 'GI.Clutter.Objects.ActorMeta.actorMetaSetName'
-- 
-- /Since: 1.4/
actorMetaGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActorMeta a) =>
    a
    -- ^ /@meta@/: a t'GI.Clutter.Objects.ActorMeta.ActorMeta'
    -> m T.Text
    -- ^ __Returns:__ the name of the t'GI.Clutter.Objects.ActorMeta.ActorMeta'
    --   instance, or 'P.Nothing' if none was set. The returned string is owned
    --   by the t'GI.Clutter.Objects.ActorMeta.ActorMeta' instance and it should not be modified
    --   or freed
actorMetaGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActorMeta a) =>
a -> m Text
actorMetaGetName a
meta = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ActorMeta
meta' <- a -> IO (Ptr ActorMeta)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
meta
    CString
result <- Ptr ActorMeta -> IO CString
clutter_actor_meta_get_name Ptr ActorMeta
meta'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actorMetaGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
meta
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ActorMetaGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsActorMeta a) => O.OverloadedMethod ActorMetaGetNameMethodInfo a signature where
    overloadedMethod = actorMetaGetName

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


#endif

-- method ActorMeta::set_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "meta"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "ActorMeta" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActorMeta"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether @meta is enabled"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_actor_meta_set_enabled" clutter_actor_meta_set_enabled :: 
    Ptr ActorMeta ->                        -- meta : TInterface (Name {namespace = "Clutter", name = "ActorMeta"})
    CInt ->                                 -- is_enabled : TBasicType TBoolean
    IO ()

-- | Sets whether /@meta@/ should be enabled or not
-- 
-- /Since: 1.4/
actorMetaSetEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsActorMeta a) =>
    a
    -- ^ /@meta@/: a t'GI.Clutter.Objects.ActorMeta.ActorMeta'
    -> Bool
    -- ^ /@isEnabled@/: whether /@meta@/ is enabled
    -> m ()
actorMetaSetEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActorMeta a) =>
a -> Bool -> m ()
actorMetaSetEnabled a
meta Bool
isEnabled = 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 ActorMeta
meta' <- a -> IO (Ptr ActorMeta)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
meta
    let isEnabled' :: CInt
isEnabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isEnabled
    Ptr ActorMeta -> CInt -> IO ()
clutter_actor_meta_set_enabled Ptr ActorMeta
meta' CInt
isEnabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
meta
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActorMetaSetEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsActorMeta a) => O.OverloadedMethod ActorMetaSetEnabledMethodInfo a signature where
    overloadedMethod = actorMetaSetEnabled

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


#endif

-- method ActorMeta::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "meta"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "ActorMeta" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActorMeta"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of @meta" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_actor_meta_set_name" clutter_actor_meta_set_name :: 
    Ptr ActorMeta ->                        -- meta : TInterface (Name {namespace = "Clutter", name = "ActorMeta"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Sets the name of /@meta@/
-- 
-- The name can be used to identify the t'GI.Clutter.Objects.ActorMeta.ActorMeta' instance
-- 
-- /Since: 1.4/
actorMetaSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActorMeta a) =>
    a
    -- ^ /@meta@/: a t'GI.Clutter.Objects.ActorMeta.ActorMeta'
    -> T.Text
    -- ^ /@name@/: the name of /@meta@/
    -> m ()
actorMetaSetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActorMeta a) =>
a -> Text -> m ()
actorMetaSetName a
meta Text
name = 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 ActorMeta
meta' <- a -> IO (Ptr ActorMeta)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
meta
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr ActorMeta -> CString -> IO ()
clutter_actor_meta_set_name Ptr ActorMeta
meta' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
meta
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ActorMetaSetNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsActorMeta a) => O.OverloadedMethod ActorMetaSetNameMethodInfo a signature where
    overloadedMethod = actorMetaSetName

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


#endif