{-# LANGUAGE TypeApplications #-} -- | Copyright : Will Thompson and Iñaki García Etxebarria -- License : LGPL-2.1 -- Maintainer : Iñaki García Etxebarria -- -- Provides a way to describe references to values. -- -- An important aspect of expressions is that the value can be obtained -- from a source that is several steps away. For example, an expression -- may describe ‘the value of property A of @object1@, which is itself the -- value of a property of @object2@’. And @object1@ may not even exist yet -- at the time that the expression is created. This is contrast to @GObject@ -- property bindings, which can only create direct connections between -- the properties of two objects that must both exist for the duration -- of the binding. -- -- An expression needs to be \"evaluated\" to obtain the value that it currently -- refers to. An evaluation always happens in the context of a current object -- called @this@ (it mirrors the behavior of object-oriented languages), -- which may or may not influence the result of the evaluation. Use -- 'GI.Gtk.Objects.Expression.expressionEvaluate' for evaluating an expression. -- -- Various methods for defining expressions exist, from simple constants via -- t'GI.Gtk.Objects.ConstantExpression.ConstantExpression'.@/new/@() to looking up properties in a @GObject@ -- (even recursively) via 'GI.Gtk.Objects.PropertyExpression.propertyExpressionNew' or providing -- custom functions to transform and combine expressions via -- 'GI.Gtk.Objects.ClosureExpression.closureExpressionNew'. -- -- Here is an example of a complex expression: -- -- -- === /c code/ -- > color_expr = gtk_property_expression_new (GTK_TYPE_LIST_ITEM, -- > NULL, "item"); -- > expression = gtk_property_expression_new (GTK_TYPE_COLOR, -- > color_expr, "name"); -- -- -- when evaluated with @this@ being a @GtkListItem@, it will obtain the -- \"item\" property from the @GtkListItem@, and then obtain the \"name\" property -- from the resulting object (which is assumed to be of type @GTK_TYPE_COLOR@). -- -- A more concise way to describe this would be -- -- -- -- > this->item->name -- -- -- The most likely place where you will encounter expressions is in the context -- of list models and list widgets using them. For example, @GtkDropDown@ is -- evaluating a @GtkExpression@ to obtain strings from the items in its model -- that it can then use to match against the contents of its search entry. -- @GtkStringFilter@ is using a @GtkExpression@ for similar reasons. -- -- By default, expressions are not paying attention to changes and evaluation is -- just a snapshot of the current state at a given time. To get informed about -- changes, an expression needs to be \"watched\" via a t'GI.Gtk.Structs.ExpressionWatch.ExpressionWatch', -- which will cause a callback to be called whenever the value of the expression may -- have changed; 'GI.Gtk.Objects.Expression.expressionWatch' starts watching an expression, and -- 'GI.Gtk.Structs.ExpressionWatch.expressionWatchUnwatch' stops. -- -- Watches can be created for automatically updating the property of an object, -- similar to GObject\'s @GBinding@ mechanism, by using 'GI.Gtk.Objects.Expression.expressionBind'. -- -- == GtkExpression in GObject properties -- -- In order to use a @GtkExpression@ as a @GObject@ property, you must use the -- 'GI.Gtk.Functions.paramSpecExpression' when creating a @GParamSpec@ to install in the -- @GObject@ class being defined; for instance: -- -- -- === /c code/ -- >obj_props[PROP_EXPRESSION] = -- > gtk_param_spec_expression ("expression", -- > "Expression", -- > "The expression used by the widget", -- > G_PARAM_READWRITE | -- > G_PARAM_STATIC_STRINGS | -- > G_PARAM_EXPLICIT_NOTIFY); -- -- -- When implementing the @GObjectClass.set_property@ and @GObjectClass.get_property@ -- virtual functions, you must use 'GI.Gtk.Functions.valueGetExpression', to retrieve the -- stored @GtkExpression@ from the @GValue@ container, and 'GI.Gtk.Functions.valueSetExpression', -- to store the @GtkExpression@ into the @GValue@; for instance: -- -- -- === /c code/ -- > // in set_property()... -- > case PROP_EXPRESSION: -- > foo_widget_set_expression (foo, gtk_value_get_expression (value)); -- > break; -- > -- > // in get_property()... -- > case PROP_EXPRESSION: -- > gtk_value_set_expression (value, foo->expression); -- > break; -- -- -- == GtkExpression in .ui files -- -- @GtkBuilder@ has support for creating expressions. The syntax here can be used where -- a @GtkExpression@ object is needed like in a @\<property>@ tag for an expression -- property, or in a @\<binding name=\"property\">@ tag to bind a property to an expression. -- -- To create a property expression, use the @\<lookup>@ element. It can have a @type@ -- attribute to specify the object type, and a @name@ attribute to specify the property -- to look up. The content of @\<lookup>@ can either be a string that specifies the name -- of the object to use, an element specifying an expression to provide an object, or -- empty to use the @this@ object. -- -- Example: -- -- -- === /xml code/ -- > <lookup name='search'>string_filter</lookup> -- -- -- Since the @\<lookup>@ element creates an expression and its element content can -- itself be an expression, this means that @\<lookup>@ tags can also be nested. -- This is a common idiom when dealing with @GtkListItem@s. See -- t'GI.Gtk.Objects.BuilderListItemFactory.BuilderListItemFactory' for an example of this technique. -- -- To create a constant expression, use the @\<constant>@ element. If the type attribute -- is specified, the element content is interpreted as a value of that type. Otherwise, -- it is assumed to be an object. For instance: -- -- -- === /xml code/ -- > <constant>string_filter</constant> -- > <constant type='gchararray'>Hello, world</constant> -- -- -- To create a closure expression, use the @\<closure>@ element. The @function@ -- attribute specifies what function to use for the closure, and the @type@ -- attribute specifies its return type. The content of the element contains the -- expressions for the parameters. For instance: -- -- -- === /xml code/ -- > <closure type='gchararray' function='combine_args_somehow'> -- > <constant type='gchararray'>File size:</constant> -- > <lookup type='GFile' name='size'>myfile</lookup> -- > </closure> -- -- -- To create a property binding, use the @\<binding>@ element in place of where a -- @\<property>@ tag would ordinarily be used. The @name@ and @object@ attributes are -- supported. The @name@ attribute is required, and pertains to the applicable property -- name. The @object@ attribute is optional. If provided, it will use the specified object -- as the @this@ object when the expression is evaluated. Here is an example in which the -- @label@ property of a @GtkLabel@ is bound to the @string@ property of another arbitrary -- object: -- -- -- === /xml code/ -- > <object class='GtkLabel'> -- > <binding name='label'> -- > <lookup name='string'>some_other_object</lookup> -- > </binding> -- > </object> -- #if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__)) #define ENABLE_OVERLOADING #endif module GI.Gtk.Objects.Expression ( -- * Exported types Expression(..) , IsExpression , toExpression , -- * 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 -- [getValueType]("GI.Gtk.Objects.Expression#g:method:getValueType"). -- -- ==== Setters -- /None/. #if defined(ENABLE_OVERLOADING) ResolveExpressionMethod , #endif -- ** bind #method:bind# #if defined(ENABLE_OVERLOADING) ExpressionBindMethodInfo , #endif expressionBind , -- ** evaluate #method:evaluate# #if defined(ENABLE_OVERLOADING) ExpressionEvaluateMethodInfo , #endif expressionEvaluate , -- ** getValueType #method:getValueType# #if defined(ENABLE_OVERLOADING) ExpressionGetValueTypeMethodInfo , #endif expressionGetValueType , -- ** isStatic #method:isStatic# #if defined(ENABLE_OVERLOADING) ExpressionIsStaticMethodInfo , #endif expressionIsStatic , -- ** ref #method:ref# #if defined(ENABLE_OVERLOADING) ExpressionRefMethodInfo , #endif expressionRef , -- ** unref #method:unref# #if defined(ENABLE_OVERLOADING) ExpressionUnrefMethodInfo , #endif expressionUnref , -- ** watch #method:watch# #if defined(ENABLE_OVERLOADING) ExpressionWatchMethodInfo , #endif expressionWatch , ) 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.Structs.ExpressionWatch as Gtk.ExpressionWatch #else 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.Structs.ExpressionWatch as Gtk.ExpressionWatch #endif -- | Memory-managed wrapper type. newtype Expression = Expression (SP.ManagedPtr Expression) deriving (Expression -> Expression -> Bool (Expression -> Expression -> Bool) -> (Expression -> Expression -> Bool) -> Eq Expression forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Expression -> Expression -> Bool == :: Expression -> Expression -> Bool $c/= :: Expression -> Expression -> Bool /= :: Expression -> Expression -> Bool Eq) instance SP.ManagedPtrNewtype Expression where toManagedPtr :: Expression -> ManagedPtr Expression toManagedPtr (Expression ManagedPtr Expression p) = ManagedPtr Expression p foreign import ccall "gtk_expression_get_type" c_gtk_expression_get_type :: IO B.Types.GType instance B.Types.TypedObject Expression where glibType :: IO GType glibType = IO GType c_gtk_expression_get_type -- | Type class for types which can be safely cast to t'Expression', for instance with `toExpression`. class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf Expression o) => IsExpression o instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf Expression o) => IsExpression o instance O.HasParentTypes Expression type instance O.ParentTypes Expression = '[] -- | Cast to t'Expression', for types for which this is known to be safe. For general casts, use 'Data.GI.Base.ManagedPtr.castTo'. toExpression :: (MIO.MonadIO m, IsExpression o) => o -> m Expression toExpression :: forall (m :: * -> *) o. (MonadIO m, IsExpression o) => o -> m Expression toExpression = IO Expression -> m Expression forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a MIO.liftIO (IO Expression -> m Expression) -> (o -> IO Expression) -> o -> m Expression forall b c a. (b -> c) -> (a -> b) -> a -> c . (ManagedPtr Expression -> Expression) -> o -> IO Expression forall o o'. (HasCallStack, ManagedPtrNewtype o, TypedObject o, ManagedPtrNewtype o', TypedObject o') => (ManagedPtr o' -> o') -> o -> IO o' B.ManagedPtr.unsafeCastTo ManagedPtr Expression -> Expression Expression foreign import ccall "gtk_value_get_expression" gv_get_gtk_value_get_expression :: FP.Ptr B.GValue.GValue -> IO (FP.Ptr Expression) foreign import ccall "gtk_value_set_expression" gv_set_gtk_value_set_expression :: FP.Ptr B.GValue.GValue -> FP.Ptr Expression -> IO () -- | Convert t'Expression' to and from t'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'. instance B.GValue.IsGValue (Maybe Expression) where gvalueGType_ :: IO GType gvalueGType_ = IO GType c_gtk_expression_get_type gvalueSet_ :: Ptr GValue -> Maybe Expression -> IO () gvalueSet_ Ptr GValue gv Maybe Expression P.Nothing = Ptr GValue -> Ptr Expression -> IO () gv_set_gtk_value_set_expression Ptr GValue gv (Ptr Expression forall a. Ptr a FP.nullPtr :: FP.Ptr Expression) gvalueSet_ Ptr GValue gv (P.Just Expression obj) = Expression -> (Ptr Expression -> IO ()) -> IO () forall a c. (HasCallStack, ManagedPtrNewtype a) => a -> (Ptr a -> IO c) -> IO c B.ManagedPtr.withManagedPtr Expression obj (Ptr GValue -> Ptr Expression -> IO () gv_set_gtk_value_set_expression Ptr GValue gv) gvalueGet_ :: Ptr GValue -> IO (Maybe Expression) gvalueGet_ Ptr GValue gv = do ptr <- Ptr GValue -> IO (Ptr Expression) gv_get_gtk_value_get_expression Ptr GValue gv :: IO (FP.Ptr Expression) if ptr /= FP.nullPtr then P.Just <$> B.ManagedPtr.newPtr Expression ptr else return P.Nothing #if defined(ENABLE_OVERLOADING) type family ResolveExpressionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where ResolveExpressionMethod "bind" o = ExpressionBindMethodInfo ResolveExpressionMethod "evaluate" o = ExpressionEvaluateMethodInfo ResolveExpressionMethod "isStatic" o = ExpressionIsStaticMethodInfo ResolveExpressionMethod "ref" o = ExpressionRefMethodInfo ResolveExpressionMethod "unref" o = ExpressionUnrefMethodInfo ResolveExpressionMethod "watch" o = ExpressionWatchMethodInfo ResolveExpressionMethod "getValueType" o = ExpressionGetValueTypeMethodInfo ResolveExpressionMethod l o = O.MethodResolutionFailed l o instance (info ~ ResolveExpressionMethod t Expression, O.OverloadedMethod info Expression p) => OL.IsLabel t (Expression -> 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 ~ ResolveExpressionMethod t Expression, O.OverloadedMethod info Expression p, R.HasField t Expression p) => R.HasField t Expression p where getField = O.overloadedMethod @info #endif instance (info ~ ResolveExpressionMethod t Expression, O.OverloadedMethodInfo info Expression) => OL.IsLabel t (O.MethodProxy info Expression) where #if MIN_VERSION_base(4,10,0) fromLabel = O.MethodProxy #else fromLabel _ = O.MethodProxy #endif #endif foreign import ccall "gtk_expression_ref" _Expression_copy_gtk_expression_ref :: Ptr a -> IO (Ptr a) foreign import ccall "gtk_expression_unref" _Expression_free_gtk_expression_unref :: Ptr a -> IO () instance BoxedPtr Expression where boxedPtrCopy :: Expression -> IO Expression boxedPtrCopy = \Expression p -> Expression -> (Ptr Expression -> IO Expression) -> IO Expression forall a c. (HasCallStack, ManagedPtrNewtype a) => a -> (Ptr a -> IO c) -> IO c B.ManagedPtr.withManagedPtr Expression p (Ptr Expression -> IO (Ptr Expression) forall a. Ptr a -> IO (Ptr a) _Expression_copy_gtk_expression_ref (Ptr Expression -> IO (Ptr Expression)) -> (Ptr Expression -> IO Expression) -> Ptr Expression -> IO Expression forall (m :: * -> *) a b c. Monad m => (a -> m b) -> (b -> m c) -> a -> m c >=> (ManagedPtr Expression -> Expression) -> Ptr Expression -> IO Expression forall a. (HasCallStack, BoxedPtr a) => (ManagedPtr a -> a) -> Ptr a -> IO a B.ManagedPtr.wrapPtr ManagedPtr Expression -> Expression Expression) boxedPtrFree :: Expression -> IO () boxedPtrFree = \Expression p -> Expression -> (Ptr Expression -> IO ()) -> IO () forall a c. (HasCallStack, ManagedPtrNewtype a) => a -> (Ptr a -> IO c) -> IO c B.ManagedPtr.withManagedPtr Expression p Ptr Expression -> IO () forall a. Ptr a -> IO () _Expression_free_gtk_expression_unref -- method Expression::bind -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "self" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "Expression" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a `GtkExpression`" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferEverything -- } -- , Arg -- { argCName = "target" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the target object to bind to" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "property" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "name of the property on `target` to bind to" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "this_" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = -- Just "the this argument for\n the evaluation of `self`" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "Gtk" , name = "ExpressionWatch" }) -- throws : False -- Skip return : False foreign import ccall "gtk_expression_bind" gtk_expression_bind :: Ptr Expression -> -- self : TInterface (Name {namespace = "Gtk", name = "Expression"}) Ptr GObject.Object.Object -> -- target : TInterface (Name {namespace = "GObject", name = "Object"}) CString -> -- property : TBasicType TUTF8 Ptr GObject.Object.Object -> -- this_ : TInterface (Name {namespace = "GObject", name = "Object"}) IO (Ptr Gtk.ExpressionWatch.ExpressionWatch) -- | Bind @target@\'s property named @property@ to @self@. -- -- The value that @self@ evaluates to is set via @g_object_set()@ on -- @target@. This is repeated whenever @self@ changes to ensure that -- the object\'s property stays synchronized with @self@. -- -- If @self@\'s evaluation fails, @target@\'s @property@ is not updated. -- You can ensure that this doesn\'t happen by using a fallback -- expression. -- -- Note that this function takes ownership of @self@. If you want -- to keep it around, you should 'GI.Gtk.Objects.Expression.expressionRef' it beforehand. expressionBind :: (B.CallStack.HasCallStack, MonadIO m, IsExpression a, GObject.Object.IsObject b, GObject.Object.IsObject c) => a -- ^ /@self@/: a @GtkExpression@ -> b -- ^ /@target@/: the target object to bind to -> T.Text -- ^ /@property@/: name of the property on @target@ to bind to -> Maybe (c) -- ^ /@this_@/: the this argument for -- the evaluation of @self@ -> m Gtk.ExpressionWatch.ExpressionWatch -- ^ __Returns:__ a @GtkExpressionWatch@ expressionBind :: forall (m :: * -> *) a b c. (HasCallStack, MonadIO m, IsExpression a, IsObject b, IsObject c) => a -> b -> Text -> Maybe c -> m ExpressionWatch expressionBind a self b target Text property Maybe c this_ = IO ExpressionWatch -> m ExpressionWatch forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO ExpressionWatch -> m ExpressionWatch) -> IO ExpressionWatch -> m ExpressionWatch forall a b. (a -> b) -> a -> b $ do self' <- a -> IO (Ptr Expression) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) B.ManagedPtr.disownManagedPtr a self target' <- unsafeManagedPtrCastPtr target property' <- textToCString property maybeThis_ <- case this_ of Maybe c Nothing -> Ptr Object -> IO (Ptr Object) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return Ptr Object forall a. Ptr a FP.nullPtr Just c jThis_ -> do jThis_' <- c -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr c jThis_ return jThis_' result <- gtk_expression_bind self' target' property' maybeThis_ checkUnexpectedReturnNULL "expressionBind" result result' <- (newBoxed Gtk.ExpressionWatch.ExpressionWatch) result touchManagedPtr self touchManagedPtr target whenJust this_ touchManagedPtr freeMem property' return result' #if defined(ENABLE_OVERLOADING) data ExpressionBindMethodInfo instance (signature ~ (b -> T.Text -> Maybe (c) -> m Gtk.ExpressionWatch.ExpressionWatch), MonadIO m, IsExpression a, GObject.Object.IsObject b, GObject.Object.IsObject c) => O.OverloadedMethod ExpressionBindMethodInfo a signature where overloadedMethod = expressionBind instance O.OverloadedMethodInfo ExpressionBindMethodInfo a where overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo { O.resolvedSymbolName = "GI.Gtk.Objects.Expression.expressionBind", O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Expression.html#v:expressionBind" }) #endif -- method Expression::evaluate -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "self" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "Expression" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a `GtkExpression`" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "this_" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "the this argument for the evaluation" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "value" -- , argType = TGValue -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an empty `GValue`" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "gtk_expression_evaluate" gtk_expression_evaluate :: Ptr Expression -> -- self : TInterface (Name {namespace = "Gtk", name = "Expression"}) Ptr GObject.Object.Object -> -- this_ : TInterface (Name {namespace = "GObject", name = "Object"}) Ptr GValue -> -- value : TGValue IO CInt -- | Evaluates the given expression and on success stores the result -- in /@value@/. -- -- The @GType@ of @value@ will be the type given by -- 'GI.Gtk.Objects.Expression.expressionGetValueType'. -- -- It is possible that expressions cannot be evaluated - for example -- when the expression references objects that have been destroyed or -- set to @NULL@. In that case @value@ will remain empty and @FALSE@ -- will be returned. expressionEvaluate :: (B.CallStack.HasCallStack, MonadIO m, IsExpression a, GObject.Object.IsObject b) => a -- ^ /@self@/: a @GtkExpression@ -> Maybe (b) -- ^ /@this_@/: the this argument for the evaluation -> GValue -- ^ /@value@/: an empty @GValue@ -> m Bool -- ^ __Returns:__ @TRUE@ if the expression could be evaluated expressionEvaluate :: forall (m :: * -> *) a b. (HasCallStack, MonadIO m, IsExpression a, IsObject b) => a -> Maybe b -> GValue -> m Bool expressionEvaluate a self Maybe b this_ GValue value = IO Bool -> m Bool forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do self' <- a -> IO (Ptr Expression) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a self maybeThis_ <- case this_ of Maybe b Nothing -> Ptr Object -> IO (Ptr Object) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return Ptr Object forall a. Ptr a FP.nullPtr Just b jThis_ -> do jThis_' <- b -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr b jThis_ return jThis_' value' <- unsafeManagedPtrGetPtr value result <- gtk_expression_evaluate self' maybeThis_ value' let result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= CInt 0) CInt result touchManagedPtr self whenJust this_ touchManagedPtr touchManagedPtr value return result' #if defined(ENABLE_OVERLOADING) data ExpressionEvaluateMethodInfo instance (signature ~ (Maybe (b) -> GValue -> m Bool), MonadIO m, IsExpression a, GObject.Object.IsObject b) => O.OverloadedMethod ExpressionEvaluateMethodInfo a signature where overloadedMethod = expressionEvaluate instance O.OverloadedMethodInfo ExpressionEvaluateMethodInfo a where overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo { O.resolvedSymbolName = "GI.Gtk.Objects.Expression.expressionEvaluate", O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Expression.html#v:expressionEvaluate" }) #endif -- method Expression::get_value_type -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "self" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "Expression" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a `GtkExpression`" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TGType) -- throws : False -- Skip return : False foreign import ccall "gtk_expression_get_value_type" gtk_expression_get_value_type :: Ptr Expression -> -- self : TInterface (Name {namespace = "Gtk", name = "Expression"}) IO CGType -- | Gets the @GType@ that this expression evaluates to. -- -- This type is constant and will not change over the lifetime -- of this expression. expressionGetValueType :: (B.CallStack.HasCallStack, MonadIO m, IsExpression a) => a -- ^ /@self@/: a @GtkExpression@ -> m GType -- ^ __Returns:__ The type returned from 'GI.Gtk.Objects.Expression.expressionEvaluate' expressionGetValueType :: forall (m :: * -> *) a. (HasCallStack, MonadIO m, IsExpression a) => a -> m GType expressionGetValueType a self = IO GType -> m GType forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO GType -> m GType) -> IO GType -> m GType forall a b. (a -> b) -> a -> b $ do self' <- a -> IO (Ptr Expression) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a self result <- gtk_expression_get_value_type self' let result' = CGType -> GType GType CGType result touchManagedPtr self return result' #if defined(ENABLE_OVERLOADING) data ExpressionGetValueTypeMethodInfo instance (signature ~ (m GType), MonadIO m, IsExpression a) => O.OverloadedMethod ExpressionGetValueTypeMethodInfo a signature where overloadedMethod = expressionGetValueType instance O.OverloadedMethodInfo ExpressionGetValueTypeMethodInfo a where overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo { O.resolvedSymbolName = "GI.Gtk.Objects.Expression.expressionGetValueType", O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Expression.html#v:expressionGetValueType" }) #endif -- method Expression::is_static -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "self" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "Expression" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a `GtkExpression`" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "gtk_expression_is_static" gtk_expression_is_static :: Ptr Expression -> -- self : TInterface (Name {namespace = "Gtk", name = "Expression"}) IO CInt -- | Checks if the expression is static. -- -- A static expression will never change its result when -- 'GI.Gtk.Objects.Expression.expressionEvaluate' is called on it with the same arguments. -- -- That means a call to 'GI.Gtk.Objects.Expression.expressionWatch' is not necessary because -- it will never trigger a notify. expressionIsStatic :: (B.CallStack.HasCallStack, MonadIO m, IsExpression a) => a -- ^ /@self@/: a @GtkExpression@ -> m Bool -- ^ __Returns:__ @TRUE@ if the expression is static expressionIsStatic :: forall (m :: * -> *) a. (HasCallStack, MonadIO m, IsExpression a) => a -> m Bool expressionIsStatic a self = IO Bool -> m Bool forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool forall a b. (a -> b) -> a -> b $ do self' <- a -> IO (Ptr Expression) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a self result <- gtk_expression_is_static self' let result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= CInt 0) CInt result touchManagedPtr self return result' #if defined(ENABLE_OVERLOADING) data ExpressionIsStaticMethodInfo instance (signature ~ (m Bool), MonadIO m, IsExpression a) => O.OverloadedMethod ExpressionIsStaticMethodInfo a signature where overloadedMethod = expressionIsStatic instance O.OverloadedMethodInfo ExpressionIsStaticMethodInfo a where overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo { O.resolvedSymbolName = "GI.Gtk.Objects.Expression.expressionIsStatic", O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Expression.html#v:expressionIsStatic" }) #endif -- method Expression::ref -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "self" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "Expression" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a `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_expression_ref" gtk_expression_ref :: Ptr Expression -> -- self : TInterface (Name {namespace = "Gtk", name = "Expression"}) IO (Ptr Expression) -- | Acquires a reference on the given @GtkExpression@. expressionRef :: (B.CallStack.HasCallStack, MonadIO m, IsExpression a) => a -- ^ /@self@/: a @GtkExpression@ -> m Expression -- ^ __Returns:__ the @GtkExpression@ with an additional reference expressionRef :: forall (m :: * -> *) a. (HasCallStack, MonadIO m, IsExpression a) => a -> m Expression expressionRef a self = IO Expression -> m Expression forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO Expression -> m Expression) -> IO Expression -> m Expression forall a b. (a -> b) -> a -> b $ do self' <- a -> IO (Ptr Expression) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a self result <- gtk_expression_ref self' checkUnexpectedReturnNULL "expressionRef" result result' <- (wrapPtr Expression) result touchManagedPtr self return result' #if defined(ENABLE_OVERLOADING) data ExpressionRefMethodInfo instance (signature ~ (m Expression), MonadIO m, IsExpression a) => O.OverloadedMethod ExpressionRefMethodInfo a signature where overloadedMethod = expressionRef instance O.OverloadedMethodInfo ExpressionRefMethodInfo a where overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo { O.resolvedSymbolName = "GI.Gtk.Objects.Expression.expressionRef", O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Expression.html#v:expressionRef" }) #endif -- method Expression::unref -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "self" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "Expression" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a `GtkExpression`" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferEverything -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "gtk_expression_unref" gtk_expression_unref :: Ptr Expression -> -- self : TInterface (Name {namespace = "Gtk", name = "Expression"}) IO () -- | Releases a reference on the given @GtkExpression@. -- -- If the reference was the last, the resources associated to the @self@ are -- freed. expressionUnref :: (B.CallStack.HasCallStack, MonadIO m, IsExpression a) => a -- ^ /@self@/: a @GtkExpression@ -> m () expressionUnref :: forall (m :: * -> *) a. (HasCallStack, MonadIO m, IsExpression a) => a -> m () expressionUnref a self = IO () -> m () forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do self' <- a -> IO (Ptr Expression) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) B.ManagedPtr.disownManagedPtr a self gtk_expression_unref self' touchManagedPtr self return () #if defined(ENABLE_OVERLOADING) data ExpressionUnrefMethodInfo instance (signature ~ (m ()), MonadIO m, IsExpression a) => O.OverloadedMethod ExpressionUnrefMethodInfo a signature where overloadedMethod = expressionUnref instance O.OverloadedMethodInfo ExpressionUnrefMethodInfo a where overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo { O.resolvedSymbolName = "GI.Gtk.Objects.Expression.expressionUnref", O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Expression.html#v:expressionUnref" }) #endif -- method Expression::watch -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "self" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "Expression" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "a `GtkExpression`" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "this_" -- , argType = -- TInterface Name { namespace = "GObject" , name = "Object" } -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "the `this` argument to\n watch" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "notify" -- , argType = -- TInterface Name { namespace = "Gtk" , name = "ExpressionNotify" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just "callback to invoke when the expression changes" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeNotified -- , argClosure = 3 -- , argDestroy = 4 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "user_data" -- , argType = TBasicType TPtr -- , direction = DirectionIn -- , mayBeNull = True -- , argDoc = -- Documentation -- { rawDocText = Just "user data to pass to the `notify` callback" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "user_destroy" -- , argType = -- TInterface Name { namespace = "GLib" , name = "DestroyNotify" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "destroy notify for `user_data`" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeAsync -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , argCallbackUserData = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just -- (TInterface Name { namespace = "Gtk" , name = "ExpressionWatch" }) -- throws : False -- Skip return : False foreign import ccall "gtk_expression_watch" gtk_expression_watch :: Ptr Expression -> -- self : TInterface (Name {namespace = "Gtk", name = "Expression"}) Ptr GObject.Object.Object -> -- this_ : TInterface (Name {namespace = "GObject", name = "Object"}) FunPtr Gtk.Callbacks.C_ExpressionNotify -> -- notify : TInterface (Name {namespace = "Gtk", name = "ExpressionNotify"}) Ptr () -> -- user_data : TBasicType TPtr FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"}) IO (Ptr Gtk.ExpressionWatch.ExpressionWatch) -- | Watch the given @expression@ for changes. -- -- The /@notify@/ function will be called whenever the evaluation of @self@ -- may have changed. -- -- GTK cannot guarantee that the evaluation did indeed change when the /@notify@/ -- gets invoked, but it guarantees the opposite: When it did in fact change, -- the /@notify@/ will be invoked. expressionWatch :: (B.CallStack.HasCallStack, MonadIO m, IsExpression a, GObject.Object.IsObject b) => a -- ^ /@self@/: a @GtkExpression@ -> Maybe (b) -- ^ /@this_@/: the @this@ argument to -- watch -> Gtk.Callbacks.ExpressionNotify -- ^ /@notify@/: callback to invoke when the expression changes -> m Gtk.ExpressionWatch.ExpressionWatch -- ^ __Returns:__ The newly installed watch. Note that the only -- reference held to the watch will be released when the watch is unwatched -- which can happen automatically, and not just via -- 'GI.Gtk.Structs.ExpressionWatch.expressionWatchUnwatch'. You should call 'GI.Gtk.Structs.ExpressionWatch.expressionWatchRef' -- if you want to keep the watch around. expressionWatch :: forall (m :: * -> *) a b. (HasCallStack, MonadIO m, IsExpression a, IsObject b) => a -> Maybe b -> IO () -> m ExpressionWatch expressionWatch a self Maybe b this_ IO () notify = IO ExpressionWatch -> m ExpressionWatch forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO ExpressionWatch -> m ExpressionWatch) -> IO ExpressionWatch -> m ExpressionWatch forall a b. (a -> b) -> a -> b $ do self' <- a -> IO (Ptr Expression) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a self maybeThis_ <- case this_ of Maybe b Nothing -> Ptr Object -> IO (Ptr Object) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return Ptr Object forall a. Ptr a FP.nullPtr Just b jThis_ -> do jThis_' <- b -> IO (Ptr Object) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr b jThis_ return jThis_' notify' <- Gtk.Callbacks.mk_ExpressionNotify (Gtk.Callbacks.wrap_ExpressionNotify Nothing (Gtk.Callbacks.drop_closures_ExpressionNotify notify)) let userData = FunPtr C_ExpressionNotify -> Ptr () forall a b. FunPtr a -> Ptr b castFunPtrToPtr FunPtr C_ExpressionNotify notify' let userDestroy = FunPtr (Ptr a -> IO ()) forall a. FunPtr (Ptr a -> IO ()) SP.safeFreeFunPtrPtr result <- gtk_expression_watch self' maybeThis_ notify' userData userDestroy checkUnexpectedReturnNULL "expressionWatch" result result' <- (newBoxed Gtk.ExpressionWatch.ExpressionWatch) result touchManagedPtr self whenJust this_ touchManagedPtr return result' #if defined(ENABLE_OVERLOADING) data ExpressionWatchMethodInfo instance (signature ~ (Maybe (b) -> Gtk.Callbacks.ExpressionNotify -> m Gtk.ExpressionWatch.ExpressionWatch), MonadIO m, IsExpression a, GObject.Object.IsObject b) => O.OverloadedMethod ExpressionWatchMethodInfo a signature where overloadedMethod = expressionWatch instance O.OverloadedMethodInfo ExpressionWatchMethodInfo a where overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo { O.resolvedSymbolName = "GI.Gtk.Objects.Expression.expressionWatch", O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Expression.html#v:expressionWatch" }) #endif