{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.PropertyExpression
    ( 
    PropertyExpression(..)                  ,
    IsPropertyExpression                    ,
    toPropertyExpression                    ,
 
#if defined(ENABLE_OVERLOADING)
    ResolvePropertyExpressionMethod         ,
#endif
#if defined(ENABLE_OVERLOADING)
    PropertyExpressionGetExpressionMethodInfo,
#endif
    propertyExpressionGetExpression         ,
#if defined(ENABLE_OVERLOADING)
    PropertyExpressionGetPspecMethodInfo    ,
#endif
    propertyExpressionGetPspec              ,
    propertyExpressionNew                   ,
    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.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.Gtk.Objects.Expression as Gtk.Expression
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
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]
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
#if defined(ENABLE_OVERLOADING)
type family ResolvePropertyExpressionMethod (t :: Symbol) (o :: *) :: * 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
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 ()
foreign import ccall "gtk_property_expression_new" gtk_property_expression_new :: 
    CGType ->                               
    Ptr Gtk.Expression.Expression ->        
    CString ->                              
    IO (Ptr PropertyExpression)
propertyExpressionNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Expression.IsExpression a) =>
    GType
    
    -> Maybe (a)
    
    
    
    -> T.Text
    
    -> m PropertyExpression
    
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
    Ptr Expression
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
nullPtr
        Just a
jExpression -> do
            Ptr Expression
jExpression' <- a -> IO (Ptr Expression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
B.ManagedPtr.disownManagedPtr a
jExpression
            Ptr Expression -> IO (Ptr Expression)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
jExpression'
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr PropertyExpression
result <- CGType -> Ptr Expression -> CString -> IO (Ptr PropertyExpression)
gtk_property_expression_new CGType
thisType' Ptr Expression
maybeExpression CString
propertyName'
    Text -> Ptr PropertyExpression -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"propertyExpressionNew" Ptr PropertyExpression
result
    PropertyExpression
result' <- ((ManagedPtr PropertyExpression -> PropertyExpression)
-> Ptr PropertyExpression -> IO PropertyExpression
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr PropertyExpression -> PropertyExpression
PropertyExpression) Ptr PropertyExpression
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
expression a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    PropertyExpression -> IO PropertyExpression
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyExpression
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_property_expression_new_for_pspec" gtk_property_expression_new_for_pspec :: 
    Ptr Gtk.Expression.Expression ->        
    Ptr GParamSpec ->                       
    IO (Ptr PropertyExpression)
propertyExpressionNewForPspec ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Expression.IsExpression a) =>
    Maybe (a)
    
    
    
    -> GParamSpec
    
    -> m PropertyExpression
    
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
    Ptr Expression
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
nullPtr
        Just a
jExpression -> do
            Ptr Expression
jExpression' <- a -> IO (Ptr Expression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
B.ManagedPtr.disownManagedPtr a
jExpression
            Ptr Expression -> IO (Ptr Expression)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Expression
jExpression'
    Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
    Ptr PropertyExpression
result <- Ptr Expression -> Ptr GParamSpec -> IO (Ptr PropertyExpression)
gtk_property_expression_new_for_pspec Ptr Expression
maybeExpression Ptr GParamSpec
pspec'
    Text -> Ptr PropertyExpression -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"propertyExpressionNewForPspec" Ptr PropertyExpression
result
    PropertyExpression
result' <- ((ManagedPtr PropertyExpression -> PropertyExpression)
-> Ptr PropertyExpression -> IO PropertyExpression
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr PropertyExpression -> PropertyExpression
PropertyExpression) Ptr PropertyExpression
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
expression a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
    PropertyExpression -> IO PropertyExpression
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyExpression
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_property_expression_get_expression" gtk_property_expression_get_expression :: 
    Ptr PropertyExpression ->               
    IO (Ptr Gtk.Expression.Expression)
propertyExpressionGetExpression ::
    (B.CallStack.HasCallStack, MonadIO m, IsPropertyExpression a) =>
    a
    
    -> m (Maybe Gtk.Expression.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
    Ptr PropertyExpression
expression' <- a -> IO (Ptr PropertyExpression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
expression
    Ptr Expression
result <- Ptr PropertyExpression -> IO (Ptr Expression)
gtk_property_expression_get_expression Ptr PropertyExpression
expression'
    Maybe Expression
maybeResult <- Ptr Expression
-> (Ptr Expression -> IO Expression) -> IO (Maybe Expression)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Expression
result ((Ptr Expression -> IO Expression) -> IO (Maybe Expression))
-> (Ptr Expression -> IO Expression) -> IO (Maybe Expression)
forall a b. (a -> b) -> a -> b
$ \Ptr Expression
result' -> do
        Expression
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'
        Expression -> IO Expression
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Expression
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
expression
    Maybe Expression -> IO (Maybe Expression)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Expression
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-gtk-4.0.6/docs/GI-Gtk-Objects-PropertyExpression.html#v:propertyExpressionGetExpression"
        })
#endif
foreign import ccall "gtk_property_expression_get_pspec" gtk_property_expression_get_pspec :: 
    Ptr PropertyExpression ->               
    IO (Ptr GParamSpec)
propertyExpressionGetPspec ::
    (B.CallStack.HasCallStack, MonadIO m, IsPropertyExpression a) =>
    a
    
    -> m GParamSpec
    
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
    Ptr PropertyExpression
expression' <- a -> IO (Ptr PropertyExpression)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
expression
    Ptr GParamSpec
result <- Ptr PropertyExpression -> IO (Ptr GParamSpec)
gtk_property_expression_get_pspec Ptr PropertyExpression
expression'
    Text -> Ptr GParamSpec -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"propertyExpressionGetPspec" Ptr GParamSpec
result
    GParamSpec
result' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
expression
    GParamSpec -> IO GParamSpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GParamSpec
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-gtk-4.0.6/docs/GI-Gtk-Objects-PropertyExpression.html#v:propertyExpressionGetPspec"
        })
#endif