{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque structure representing a watched @GtkExpression@.
-- 
-- The contents of @GtkExpressionWatch@ should only be accessed through the
-- provided API.

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

module GI.Gtk.Structs.ExpressionWatch
    ( 

-- * Exported types
    ExpressionWatch(..)                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [evaluate]("GI.Gtk.Structs.ExpressionWatch#g:method:evaluate"), [ref]("GI.Gtk.Structs.ExpressionWatch#g:method:ref"), [unref]("GI.Gtk.Structs.ExpressionWatch#g:method:unref"), [unwatch]("GI.Gtk.Structs.ExpressionWatch#g:method:unwatch").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveExpressionWatchMethod            ,
#endif

-- ** evaluate #method:evaluate#

#if defined(ENABLE_OVERLOADING)
    ExpressionWatchEvaluateMethodInfo       ,
#endif
    expressionWatchEvaluate                 ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    ExpressionWatchRefMethodInfo            ,
#endif
    expressionWatchRef                      ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    ExpressionWatchUnrefMethodInfo          ,
#endif
    expressionWatchUnref                    ,


-- ** unwatch #method:unwatch#

#if defined(ENABLE_OVERLOADING)
    ExpressionWatchUnwatchMethodInfo        ,
#endif
    expressionWatchUnwatch                  ,




    ) 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)

#else

#endif

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

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

foreign import ccall "gtk_expression_watch_get_type" c_gtk_expression_watch_get_type :: 
    IO GType

type instance O.ParentTypes ExpressionWatch = '[]
instance O.HasParentTypes ExpressionWatch

instance B.Types.TypedObject ExpressionWatch where
    glibType :: IO GType
glibType = IO GType
c_gtk_expression_watch_get_type

instance B.Types.GBoxed ExpressionWatch

-- | Convert t'ExpressionWatch' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe ExpressionWatch) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_expression_watch_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ExpressionWatch -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ExpressionWatch
P.Nothing = Ptr GValue -> Ptr ExpressionWatch -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr ExpressionWatch
forall a. Ptr a
FP.nullPtr :: FP.Ptr ExpressionWatch)
    gvalueSet_ Ptr GValue
gv (P.Just ExpressionWatch
obj) = ExpressionWatch -> (Ptr ExpressionWatch -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ExpressionWatch
obj (Ptr GValue -> Ptr ExpressionWatch -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ExpressionWatch)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr ExpressionWatch)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr ExpressionWatch)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newBoxed ExpressionWatch ptr
        else return P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ExpressionWatch
type instance O.AttributeList ExpressionWatch = ExpressionWatchAttributeList
type ExpressionWatchAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

-- method ExpressionWatch::evaluate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "watch"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ExpressionWatch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkExpressionWatch`"
--                 , 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` to be set"
--                 , 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_watch_evaluate" gtk_expression_watch_evaluate :: 
    Ptr ExpressionWatch ->                  -- watch : TInterface (Name {namespace = "Gtk", name = "ExpressionWatch"})
    Ptr GValue ->                           -- value : TGValue
    IO CInt

-- | Evaluates the watched expression and on success stores the result
-- in @value@.
-- 
-- This is equivalent to calling 'GI.Gtk.Objects.Expression.expressionEvaluate' with the
-- expression and this pointer originally used to create @watch@.
expressionWatchEvaluate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ExpressionWatch
    -- ^ /@watch@/: a @GtkExpressionWatch@
    -> GValue
    -- ^ /@value@/: an empty @GValue@ to be set
    -> m Bool
    -- ^ __Returns:__ @TRUE@ if the expression could be evaluated and @value@ was set
expressionWatchEvaluate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ExpressionWatch -> GValue -> m Bool
expressionWatchEvaluate ExpressionWatch
watch 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
    watch' <- ExpressionWatch -> IO (Ptr ExpressionWatch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ExpressionWatch
watch
    value' <- unsafeManagedPtrGetPtr value
    result <- gtk_expression_watch_evaluate watch' value'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr watch
    touchManagedPtr value
    return result'

#if defined(ENABLE_OVERLOADING)
data ExpressionWatchEvaluateMethodInfo
instance (signature ~ (GValue -> m Bool), MonadIO m) => O.OverloadedMethod ExpressionWatchEvaluateMethodInfo ExpressionWatch signature where
    overloadedMethod = expressionWatchEvaluate

instance O.OverloadedMethodInfo ExpressionWatchEvaluateMethodInfo ExpressionWatch where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.ExpressionWatch.expressionWatchEvaluate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-ExpressionWatch.html#v:expressionWatchEvaluate"
        })


#endif

-- method ExpressionWatch::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "watch"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ExpressionWatch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkExpressionWatch`"
--                 , 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_watch_ref" gtk_expression_watch_ref :: 
    Ptr ExpressionWatch ->                  -- watch : TInterface (Name {namespace = "Gtk", name = "ExpressionWatch"})
    IO (Ptr ExpressionWatch)

-- | Acquires a reference on the given @GtkExpressionWatch@.
expressionWatchRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ExpressionWatch
    -- ^ /@watch@/: a @GtkExpressionWatch@
    -> m ExpressionWatch
    -- ^ __Returns:__ the @GtkExpressionWatch@ with an additional reference
expressionWatchRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ExpressionWatch -> m ExpressionWatch
expressionWatchRef ExpressionWatch
watch = 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
    watch' <- ExpressionWatch -> IO (Ptr ExpressionWatch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ExpressionWatch
watch
    result <- gtk_expression_watch_ref watch'
    checkUnexpectedReturnNULL "expressionWatchRef" result
    result' <- (wrapBoxed ExpressionWatch) result
    touchManagedPtr watch
    return result'

#if defined(ENABLE_OVERLOADING)
data ExpressionWatchRefMethodInfo
instance (signature ~ (m ExpressionWatch), MonadIO m) => O.OverloadedMethod ExpressionWatchRefMethodInfo ExpressionWatch signature where
    overloadedMethod = expressionWatchRef

instance O.OverloadedMethodInfo ExpressionWatchRefMethodInfo ExpressionWatch where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.ExpressionWatch.expressionWatchRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-ExpressionWatch.html#v:expressionWatchRef"
        })


#endif

-- method ExpressionWatch::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "watch"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ExpressionWatch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkExpressionWatch`"
--                 , 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_watch_unref" gtk_expression_watch_unref :: 
    Ptr ExpressionWatch ->                  -- watch : TInterface (Name {namespace = "Gtk", name = "ExpressionWatch"})
    IO ()

-- | Releases a reference on the given @GtkExpressionWatch@.
-- 
-- If the reference was the last, the resources associated to @self@ are
-- freed.
expressionWatchUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ExpressionWatch
    -- ^ /@watch@/: a @GtkExpressionWatch@
    -> m ()
expressionWatchUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ExpressionWatch -> m ()
expressionWatchUnref ExpressionWatch
watch = 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
    watch' <- ExpressionWatch -> IO (Ptr ExpressionWatch)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed ExpressionWatch
watch
    gtk_expression_watch_unref watch'
    touchManagedPtr watch
    return ()

#if defined(ENABLE_OVERLOADING)
data ExpressionWatchUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ExpressionWatchUnrefMethodInfo ExpressionWatch signature where
    overloadedMethod = expressionWatchUnref

instance O.OverloadedMethodInfo ExpressionWatchUnrefMethodInfo ExpressionWatch where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.ExpressionWatch.expressionWatchUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-ExpressionWatch.html#v:expressionWatchUnref"
        })


#endif

-- method ExpressionWatch::unwatch
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "watch"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ExpressionWatch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "watch to release" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_expression_watch_unwatch" gtk_expression_watch_unwatch :: 
    Ptr ExpressionWatch ->                  -- watch : TInterface (Name {namespace = "Gtk", name = "ExpressionWatch"})
    IO ()

-- | Stops watching an expression.
-- 
-- See 'GI.Gtk.Objects.Expression.expressionWatch' for how the watch
-- was established.
expressionWatchUnwatch ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ExpressionWatch
    -- ^ /@watch@/: watch to release
    -> m ()
expressionWatchUnwatch :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ExpressionWatch -> m ()
expressionWatchUnwatch ExpressionWatch
watch = 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
    watch' <- ExpressionWatch -> IO (Ptr ExpressionWatch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ExpressionWatch
watch
    gtk_expression_watch_unwatch watch'
    touchManagedPtr watch
    return ()

#if defined(ENABLE_OVERLOADING)
data ExpressionWatchUnwatchMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ExpressionWatchUnwatchMethodInfo ExpressionWatch signature where
    overloadedMethod = expressionWatchUnwatch

instance O.OverloadedMethodInfo ExpressionWatchUnwatchMethodInfo ExpressionWatch where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.ExpressionWatch.expressionWatchUnwatch",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-ExpressionWatch.html#v:expressionWatchUnwatch"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveExpressionWatchMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveExpressionWatchMethod "evaluate" o = ExpressionWatchEvaluateMethodInfo
    ResolveExpressionWatchMethod "ref" o = ExpressionWatchRefMethodInfo
    ResolveExpressionWatchMethod "unref" o = ExpressionWatchUnrefMethodInfo
    ResolveExpressionWatchMethod "unwatch" o = ExpressionWatchUnwatchMethodInfo
    ResolveExpressionWatchMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif