{-# LANGUAGE TypeApplications #-}


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

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

module GI.Gtk.Objects.PropertyExpression
    ( 

-- * Exported types
    PropertyExpression(..)                  ,
    IsPropertyExpression                    ,
    toPropertyExpression                    ,


 -- * 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
-- [getExpression]("GI.Gtk.Objects.PropertyExpression#g:method:getExpression"), [getPspec]("GI.Gtk.Objects.PropertyExpression#g:method:getPspec"), [getValueType]("GI.Gtk.Objects.Expression#g:method:getValueType").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolvePropertyExpressionMethod         ,
#endif

-- ** getExpression #method:getExpression#

#if defined(ENABLE_OVERLOADING)
    PropertyExpressionGetExpressionMethodInfo,
#endif
    propertyExpressionGetExpression         ,


-- ** getPspec #method:getPspec#

#if defined(ENABLE_OVERLOADING)
    PropertyExpressionGetPspecMethodInfo    ,
#endif
    propertyExpressionGetPspec              ,


-- ** new #method:new#

    propertyExpressionNew                   ,


-- ** newForPspec #method:newForPspec#

    propertyExpressionNewForPspec           ,




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

#else
import {-# SOURCE #-} qualified GI.Gtk.Objects.Expression as Gtk.Expression

#endif

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

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

foreign import ccall "gtk_property_expression_get_type"
    c_gtk_property_expression_get_type :: IO B.Types.GType

instance B.Types.TypedObject PropertyExpression where
    glibType :: IO GType
glibType = IO GType
c_gtk_property_expression_get_type

-- | Type class for types which can be safely cast to t'PropertyExpression', for instance with `toPropertyExpression`.
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf PropertyExpression o) => IsPropertyExpression o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf PropertyExpression o) => IsPropertyExpression o

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

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

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

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

#endif

instance (info ~ ResolvePropertyExpressionMethod t PropertyExpression, O.OverloadedMethodInfo info PropertyExpression) => OL.IsLabel t (O.MethodProxy info PropertyExpression) 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 PropertyExpression where
    boxedPtrCopy :: PropertyExpression -> IO PropertyExpression
boxedPtrCopy = PropertyExpression -> IO PropertyExpression
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: PropertyExpression -> IO ()
boxedPtrFree = \PropertyExpression
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- method PropertyExpression::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "this_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The type to expect for the this type"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "expression"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Expression" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Expression to\n  evaluate to get the object to query or `NULL` to\n  query the `this` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of the property"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "PropertyExpression" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_property_expression_new" gtk_property_expression_new :: 
    CGType ->                               -- this_type : TBasicType TGType
    Ptr Gtk.Expression.Expression ->        -- expression : TInterface (Name {namespace = "Gtk", name = "Expression"})
    CString ->                              -- property_name : TBasicType TUTF8
    IO (Ptr PropertyExpression)

-- | Creates an expression that looks up a property.
-- 
-- The object to use is found by evaluating the @expression@,
-- or using the @this@ argument when @expression@ is @NULL@.
-- 
-- If the resulting object conforms to @this_type@, its property named
-- @property_name@ will be queried. Otherwise, this expression\'s
-- evaluation will fail.
-- 
-- The given @this_type@ must have a property with @property_name@.
propertyExpressionNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Expression.IsExpression a) =>
    GType
    -- ^ /@thisType@/: The type to expect for the this type
    -> Maybe (a)
    -- ^ /@expression@/: Expression to
    --   evaluate to get the object to query or @NULL@ to
    --   query the @this@ object
    -> T.Text
    -- ^ /@propertyName@/: name of the property
    -> m PropertyExpression
    -- ^ __Returns:__ a new @GtkExpression@
propertyExpressionNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsExpression a) =>
GType -> Maybe a -> Text -> m PropertyExpression
propertyExpressionNew GType
thisType Maybe a
expression Text
propertyName = IO PropertyExpression -> m PropertyExpression
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyExpression -> m PropertyExpression)
-> IO PropertyExpression -> m PropertyExpression
forall a b. (a -> b) -> a -> b
$ do
    let thisType' :: CGType
thisType' = GType -> CGType
gtypeToCGType GType
thisType
    maybeExpression <- case Maybe a
expression of
        Maybe a
Nothing -> Ptr Expression -> IO (Ptr Expression)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
forall a. Ptr a
FP.nullPtr
        Just a
jExpression -> do
            jExpression' <- a -> IO (Ptr Expression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
B.ManagedPtr.disownManagedPtr a
jExpression
            return jExpression'
    propertyName' <- textToCString propertyName
    result <- gtk_property_expression_new thisType' maybeExpression propertyName'
    checkUnexpectedReturnNULL "propertyExpressionNew" result
    result' <- (wrapPtr PropertyExpression) result
    whenJust expression touchManagedPtr
    freeMem propertyName'
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PropertyExpression::new_for_pspec
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "expression"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Expression" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Expression to\n  evaluate to get the object to query or `NULL` to\n  query the `this` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "pspec"
--           , argType = TParamSpec
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GParamSpec` for the property to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "PropertyExpression" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_property_expression_new_for_pspec" gtk_property_expression_new_for_pspec :: 
    Ptr Gtk.Expression.Expression ->        -- expression : TInterface (Name {namespace = "Gtk", name = "Expression"})
    Ptr GParamSpec ->                       -- pspec : TParamSpec
    IO (Ptr PropertyExpression)

-- | Creates an expression that looks up a property.
-- 
-- The object to use is found by evaluating the @expression@,
-- or using the @this@ argument when @expression@ is @NULL@.
-- 
-- If the resulting object conforms to @this_type@, its
-- property specified by @pspec@ will be queried.
-- Otherwise, this expression\'s evaluation will fail.
propertyExpressionNewForPspec ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Expression.IsExpression a) =>
    Maybe (a)
    -- ^ /@expression@/: Expression to
    --   evaluate to get the object to query or @NULL@ to
    --   query the @this@ object
    -> GParamSpec
    -- ^ /@pspec@/: the @GParamSpec@ for the property to query
    -> m PropertyExpression
    -- ^ __Returns:__ a new @GtkExpression@
propertyExpressionNewForPspec :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsExpression a) =>
Maybe a -> GParamSpec -> m PropertyExpression
propertyExpressionNewForPspec Maybe a
expression GParamSpec
pspec = IO PropertyExpression -> m PropertyExpression
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyExpression -> m PropertyExpression)
-> IO PropertyExpression -> m PropertyExpression
forall a b. (a -> b) -> a -> b
$ do
    maybeExpression <- case Maybe a
expression of
        Maybe a
Nothing -> Ptr Expression -> IO (Ptr Expression)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
forall a. Ptr a
FP.nullPtr
        Just a
jExpression -> do
            jExpression' <- a -> IO (Ptr Expression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
B.ManagedPtr.disownManagedPtr a
jExpression
            return jExpression'
    pspec' <- unsafeManagedPtrGetPtr pspec
    result <- gtk_property_expression_new_for_pspec maybeExpression pspec'
    checkUnexpectedReturnNULL "propertyExpressionNewForPspec" result
    result' <- (wrapPtr PropertyExpression) result
    whenJust expression touchManagedPtr
    touchManagedPtr pspec
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_property_expression_get_expression" gtk_property_expression_get_expression :: 
    Ptr PropertyExpression ->               -- expression : TInterface (Name {namespace = "Gtk", name = "PropertyExpression"})
    IO (Ptr Gtk.Expression.Expression)

-- | Gets the expression specifying the object of
-- a property expression.
propertyExpressionGetExpression ::
    (B.CallStack.HasCallStack, MonadIO m, IsPropertyExpression a) =>
    a
    -- ^ /@expression@/: a property @GtkExpression@
    -> m (Maybe Gtk.Expression.Expression)
    -- ^ __Returns:__ the object expression
propertyExpressionGetExpression :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPropertyExpression a) =>
a -> m (Maybe Expression)
propertyExpressionGetExpression a
expression = IO (Maybe Expression) -> m (Maybe Expression)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Expression) -> m (Maybe Expression))
-> IO (Maybe Expression) -> m (Maybe Expression)
forall a b. (a -> b) -> a -> b
$ do
    expression' <- a -> IO (Ptr PropertyExpression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
expression
    result <- gtk_property_expression_get_expression expression'
    maybeResult <- convertIfNonNull result $ \Ptr Expression
result' -> do
        result'' <- ((ManagedPtr Expression -> Expression)
-> Ptr Expression -> IO Expression
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Expression -> Expression
Gtk.Expression.Expression) Ptr Expression
result'
        return result''
    touchManagedPtr expression
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data PropertyExpressionGetExpressionMethodInfo
instance (signature ~ (m (Maybe Gtk.Expression.Expression)), MonadIO m, IsPropertyExpression a) => O.OverloadedMethod PropertyExpressionGetExpressionMethodInfo a signature where
    overloadedMethod = propertyExpressionGetExpression

instance O.OverloadedMethodInfo PropertyExpressionGetExpressionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PropertyExpression.propertyExpressionGetExpression",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PropertyExpression.html#v:propertyExpressionGetExpression"
        })


#endif

-- method PropertyExpression::get_pspec
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "expression"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PropertyExpression" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a property `GtkExpression`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TParamSpec
-- throws : False
-- Skip return : False

foreign import ccall "gtk_property_expression_get_pspec" gtk_property_expression_get_pspec :: 
    Ptr PropertyExpression ->               -- expression : TInterface (Name {namespace = "Gtk", name = "PropertyExpression"})
    IO (Ptr GParamSpec)

-- | Gets the @GParamSpec@ specifying the property of
-- a property expression.
propertyExpressionGetPspec ::
    (B.CallStack.HasCallStack, MonadIO m, IsPropertyExpression a) =>
    a
    -- ^ /@expression@/: a property @GtkExpression@
    -> m GParamSpec
    -- ^ __Returns:__ the @GParamSpec@ for the property
propertyExpressionGetPspec :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPropertyExpression a) =>
a -> m GParamSpec
propertyExpressionGetPspec a
expression = IO GParamSpec -> m GParamSpec
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec
forall a b. (a -> b) -> a -> b
$ do
    expression' <- a -> IO (Ptr PropertyExpression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
expression
    result <- gtk_property_expression_get_pspec expression'
    checkUnexpectedReturnNULL "propertyExpressionGetPspec" result
    result' <- B.GParamSpec.newGParamSpecFromPtr result
    touchManagedPtr expression
    return result'

#if defined(ENABLE_OVERLOADING)
data PropertyExpressionGetPspecMethodInfo
instance (signature ~ (m GParamSpec), MonadIO m, IsPropertyExpression a) => O.OverloadedMethod PropertyExpressionGetPspecMethodInfo a signature where
    overloadedMethod = propertyExpressionGetPspec

instance O.OverloadedMethodInfo PropertyExpressionGetPspecMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PropertyExpression.propertyExpressionGetPspec",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PropertyExpression.html#v:propertyExpressionGetPspec"
        })


#endif