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

-- * Exported types
    Constraint(..)                          ,
    IsConstraint                            ,
    toConstraint                            ,


 -- * 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)
    ResolveConstraintMethod                 ,
#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.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.ActorMeta as Clutter.ActorMeta
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "clutter_constraint_get_type"
    c_clutter_constraint_get_type :: IO B.Types.GType

instance B.Types.TypedObject Constraint where
    glibType :: IO GType
glibType = IO GType
c_clutter_constraint_get_type

instance B.Types.GObject Constraint

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

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

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

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

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

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif