{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GObject@ value in a @GtkExpression@.

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

module GI.Gtk.Objects.ObjectExpression
    ( 

-- * Exported types
    ObjectExpression(..)                    ,
    IsObjectExpression                      ,
    toObjectExpression                      ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bind]("GI.Gtk.Objects.Expression#g:method:bind"), [evaluate]("GI.Gtk.Objects.Expression#g:method:evaluate"), [isStatic]("GI.Gtk.Objects.Expression#g:method:isStatic"), [ref]("GI.Gtk.Objects.Expression#g:method:ref"), [unref]("GI.Gtk.Objects.Expression#g:method:unref"), [watch]("GI.Gtk.Objects.Expression#g:method:watch").
-- 
-- ==== Getters
-- [getObject]("GI.Gtk.Objects.ObjectExpression#g:method:getObject"), [getValueType]("GI.Gtk.Objects.Expression#g:method:getValueType").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveObjectExpressionMethod           ,
#endif

-- ** getObject #method:getObject#

#if defined(ENABLE_OVERLOADING)
    ObjectExpressionGetObjectMethodInfo     ,
#endif
    objectExpressionGetObject               ,


-- ** new #method:new#

    objectExpressionNew                     ,




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

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

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

foreign import ccall "gtk_object_expression_get_type"
    c_gtk_object_expression_get_type :: IO B.Types.GType

instance B.Types.TypedObject ObjectExpression where
    glibType :: IO GType
glibType = IO GType
c_gtk_object_expression_get_type

-- | Type class for types which can be safely cast to `ObjectExpression`, for instance with `toObjectExpression`.
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf ObjectExpression o) => IsObjectExpression o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf ObjectExpression o) => IsObjectExpression o

instance O.HasParentTypes ObjectExpression
type instance O.ParentTypes ObjectExpression = '[Gtk.Expression.Expression]

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

--- XXX Missing getter and/or setter, so no GValue instance could be generated.
#if defined(ENABLE_OVERLOADING)
type family ResolveObjectExpressionMethod (t :: Symbol) (o :: *) :: * where
    ResolveObjectExpressionMethod "bind" o = Gtk.Expression.ExpressionBindMethodInfo
    ResolveObjectExpressionMethod "evaluate" o = Gtk.Expression.ExpressionEvaluateMethodInfo
    ResolveObjectExpressionMethod "isStatic" o = Gtk.Expression.ExpressionIsStaticMethodInfo
    ResolveObjectExpressionMethod "ref" o = Gtk.Expression.ExpressionRefMethodInfo
    ResolveObjectExpressionMethod "unref" o = Gtk.Expression.ExpressionUnrefMethodInfo
    ResolveObjectExpressionMethod "watch" o = Gtk.Expression.ExpressionWatchMethodInfo
    ResolveObjectExpressionMethod "getObject" o = ObjectExpressionGetObjectMethodInfo
    ResolveObjectExpressionMethod "getValueType" o = Gtk.Expression.ExpressionGetValueTypeMethodInfo
    ResolveObjectExpressionMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr ObjectExpression where
    boxedPtrCopy :: ObjectExpression -> IO ObjectExpression
boxedPtrCopy = ObjectExpression -> IO ObjectExpression
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: ObjectExpression -> IO ()
boxedPtrFree = \ObjectExpression
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- method ObjectExpression::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "object to watch" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "ObjectExpression" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_object_expression_new" gtk_object_expression_new :: 
    Ptr GObject.Object.Object ->            -- object : TInterface (Name {namespace = "GObject", name = "Object"})
    IO (Ptr ObjectExpression)

-- | Creates an expression evaluating to the given @object@ with a weak reference.
-- 
-- Once the @object@ is disposed, it will fail to evaluate.
-- 
-- This expression is meant to break reference cycles.
-- 
-- If you want to keep a reference to @object@, use t'GI.Gtk.Objects.ConstantExpression.ConstantExpression'.@/new/@().
objectExpressionNew ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
    a
    -- ^ /@object@/: object to watch
    -> m ObjectExpression
    -- ^ __Returns:__ a new @GtkExpression@
objectExpressionNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m ObjectExpression
objectExpressionNew a
object = IO ObjectExpression -> m ObjectExpression
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ObjectExpression -> m ObjectExpression)
-> IO ObjectExpression -> m ObjectExpression
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    Ptr ObjectExpression
result <- Ptr Object -> IO (Ptr ObjectExpression)
gtk_object_expression_new Ptr Object
object'
    Text -> Ptr ObjectExpression -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectExpressionNew" Ptr ObjectExpression
result
    ObjectExpression
result' <- ((ManagedPtr ObjectExpression -> ObjectExpression)
-> Ptr ObjectExpression -> IO ObjectExpression
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ObjectExpression -> ObjectExpression
ObjectExpression) Ptr ObjectExpression
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    ObjectExpression -> IO ObjectExpression
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ObjectExpression
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ObjectExpression::get_object
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "expression"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ObjectExpression" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an object `GtkExpression`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GObject" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_object_expression_get_object" gtk_object_expression_get_object :: 
    Ptr ObjectExpression ->                 -- expression : TInterface (Name {namespace = "Gtk", name = "ObjectExpression"})
    IO (Ptr GObject.Object.Object)

-- | Gets the object that the expression evaluates to.
objectExpressionGetObject ::
    (B.CallStack.HasCallStack, MonadIO m, IsObjectExpression a) =>
    a
    -- ^ /@expression@/: an object @GtkExpression@
    -> m (Maybe GObject.Object.Object)
    -- ^ __Returns:__ the object, or @NULL@
objectExpressionGetObject :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObjectExpression a) =>
a -> m (Maybe Object)
objectExpressionGetObject a
expression = IO (Maybe Object) -> m (Maybe Object)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ObjectExpression
expression' <- a -> IO (Ptr ObjectExpression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
expression
    Ptr Object
result <- Ptr ObjectExpression -> IO (Ptr Object)
gtk_object_expression_get_object Ptr ObjectExpression
expression'
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
result' -> do
        Object
result'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result'
        Object -> IO Object
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
expression
    Maybe Object -> IO (Maybe Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

#if defined(ENABLE_OVERLOADING)
data ObjectExpressionGetObjectMethodInfo
instance (signature ~ (m (Maybe GObject.Object.Object)), MonadIO m, IsObjectExpression a) => O.OverloadedMethod ObjectExpressionGetObjectMethodInfo a signature where
    overloadedMethod = objectExpressionGetObject

instance O.OverloadedMethodInfo ObjectExpressionGetObjectMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ObjectExpression.objectExpressionGetObject",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-ObjectExpression.html#v:objectExpressionGetObject"
        })


#endif