{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Sub-class of t'GI.Clutter.Objects.ChildMeta.ChildMeta' specific for layout managers
-- 
-- A t'GI.Clutter.Objects.LayoutManager.LayoutManager' sub-class should create a t'GI.Clutter.Objects.LayoutMeta.LayoutMeta'
-- instance by overriding the t'GI.Clutter.Objects.LayoutManager.LayoutManager'::@/create_child_meta/@()
-- virtual function
-- 
-- /Since: 1.2/

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

module GI.Clutter.Objects.LayoutMeta
    ( 

-- * Exported types
    LayoutMeta(..)                          ,
    IsLayoutMeta                            ,
    toLayoutMeta                            ,


 -- * 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.ChildMeta#g:method:getActor"), [getContainer]("GI.Clutter.Objects.ChildMeta#g:method:getContainer"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getManager]("GI.Clutter.Objects.LayoutMeta#g:method:getManager"), [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"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveLayoutMetaMethod                 ,
#endif

-- ** getManager #method:getManager#

#if defined(ENABLE_OVERLOADING)
    LayoutMetaGetManagerMethodInfo          ,
#endif
    layoutMetaGetManager                    ,




 -- * Properties


-- ** manager #attr:manager#
-- | The t'GI.Clutter.Objects.LayoutManager.LayoutManager' that created this t'GI.Clutter.Objects.LayoutMeta.LayoutMeta'.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    LayoutMetaManagerPropertyInfo           ,
#endif
    constructLayoutMetaManager              ,
    getLayoutMetaManager                    ,
#if defined(ENABLE_OVERLOADING)
    layoutMetaManager                       ,
#endif




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

#endif

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

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

foreign import ccall "clutter_layout_meta_get_type"
    c_clutter_layout_meta_get_type :: IO B.Types.GType

instance B.Types.TypedObject LayoutMeta where
    glibType :: IO GType
glibType = IO GType
c_clutter_layout_meta_get_type

instance B.Types.GObject LayoutMeta

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

instance O.HasParentTypes LayoutMeta
type instance O.ParentTypes LayoutMeta = '[Clutter.ChildMeta.ChildMeta, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveLayoutMetaMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveLayoutMetaMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveLayoutMetaMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveLayoutMetaMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveLayoutMetaMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveLayoutMetaMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveLayoutMetaMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveLayoutMetaMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveLayoutMetaMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveLayoutMetaMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveLayoutMetaMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveLayoutMetaMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveLayoutMetaMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveLayoutMetaMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveLayoutMetaMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveLayoutMetaMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveLayoutMetaMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveLayoutMetaMethod "getActor" o = Clutter.ChildMeta.ChildMetaGetActorMethodInfo
    ResolveLayoutMetaMethod "getContainer" o = Clutter.ChildMeta.ChildMetaGetContainerMethodInfo
    ResolveLayoutMetaMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveLayoutMetaMethod "getManager" o = LayoutMetaGetManagerMethodInfo
    ResolveLayoutMetaMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveLayoutMetaMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveLayoutMetaMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveLayoutMetaMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveLayoutMetaMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveLayoutMetaMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data LayoutMetaManagerPropertyInfo
instance AttrInfo LayoutMetaManagerPropertyInfo where
    type AttrAllowedOps LayoutMetaManagerPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LayoutMetaManagerPropertyInfo = IsLayoutMeta
    type AttrSetTypeConstraint LayoutMetaManagerPropertyInfo = Clutter.LayoutManager.IsLayoutManager
    type AttrTransferTypeConstraint LayoutMetaManagerPropertyInfo = Clutter.LayoutManager.IsLayoutManager
    type AttrTransferType LayoutMetaManagerPropertyInfo = Clutter.LayoutManager.LayoutManager
    type AttrGetType LayoutMetaManagerPropertyInfo = Clutter.LayoutManager.LayoutManager
    type AttrLabel LayoutMetaManagerPropertyInfo = "manager"
    type AttrOrigin LayoutMetaManagerPropertyInfo = LayoutMeta
    attrGet = getLayoutMetaManager
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Clutter.LayoutManager.LayoutManager v
    attrConstruct = constructLayoutMetaManager
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.LayoutMeta.manager"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.6/docs/GI-Clutter-Objects-LayoutMeta.html#g:attr:manager"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList LayoutMeta
type instance O.AttributeList LayoutMeta = LayoutMetaAttributeList
type LayoutMetaAttributeList = ('[ '("actor", Clutter.ChildMeta.ChildMetaActorPropertyInfo), '("container", Clutter.ChildMeta.ChildMetaContainerPropertyInfo), '("manager", LayoutMetaManagerPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
layoutMetaManager :: AttrLabelProxy "manager"
layoutMetaManager = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "clutter_layout_meta_get_manager" clutter_layout_meta_get_manager :: 
    Ptr LayoutMeta ->                       -- data : TInterface (Name {namespace = "Clutter", name = "LayoutMeta"})
    IO (Ptr Clutter.LayoutManager.LayoutManager)

-- | Retrieves the actor wrapped by /@data@/
-- 
-- /Since: 1.2/
layoutMetaGetManager ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayoutMeta a) =>
    a
    -- ^ /@data@/: a t'GI.Clutter.Objects.LayoutMeta.LayoutMeta'
    -> m Clutter.LayoutManager.LayoutManager
    -- ^ __Returns:__ a t'GI.Clutter.Objects.LayoutManager.LayoutManager'
layoutMetaGetManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayoutMeta a) =>
a -> m LayoutManager
layoutMetaGetManager a
data_ = IO LayoutManager -> m LayoutManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LayoutManager -> m LayoutManager)
-> IO LayoutManager -> m LayoutManager
forall a b. (a -> b) -> a -> b
$ do
    Ptr LayoutMeta
data_' <- a -> IO (Ptr LayoutMeta)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
data_
    Ptr LayoutManager
result <- Ptr LayoutMeta -> IO (Ptr LayoutManager)
clutter_layout_meta_get_manager Ptr LayoutMeta
data_'
    Text -> Ptr LayoutManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutMetaGetManager" Ptr LayoutManager
result
    LayoutManager
result' <- ((ManagedPtr LayoutManager -> LayoutManager)
-> Ptr LayoutManager -> IO LayoutManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr LayoutManager -> LayoutManager
Clutter.LayoutManager.LayoutManager) Ptr LayoutManager
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
data_
    LayoutManager -> IO LayoutManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutManager
result'

#if defined(ENABLE_OVERLOADING)
data LayoutMetaGetManagerMethodInfo
instance (signature ~ (m Clutter.LayoutManager.LayoutManager), MonadIO m, IsLayoutMeta a) => O.OverloadedMethod LayoutMetaGetManagerMethodInfo a signature where
    overloadedMethod = layoutMetaGetManager

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


#endif