{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.AppInfoMonitor.AppInfoMonitor' is a very simple object used for monitoring the app
-- info database for changes (ie: newly installed or removed
-- applications).
-- 
-- Call 'GI.Gio.Objects.AppInfoMonitor.appInfoMonitorGet' to get a t'GI.Gio.Objects.AppInfoMonitor.AppInfoMonitor' and connect
-- to the \"changed\" signal.
-- 
-- In the usual case, applications should try to make note of the change
-- (doing things like invalidating caches) but not act on it.  In
-- particular, applications should avoid making calls to t'GI.Gio.Interfaces.AppInfo.AppInfo' APIs
-- in response to the change signal, deferring these until the time that
-- the data is actually required.  The exception to this case is when
-- application information is actually being displayed on the screen
-- (eg: during a search or when the list of all applications is shown).
-- The reason for this is that changes to the list of installed
-- applications often come in groups (like during system updates) and
-- rescanning the list on every change is pointless and expensive.
-- 
-- /Since: 2.40/

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

module GI.Gio.Objects.AppInfoMonitor
    ( 

-- * Exported types
    AppInfoMonitor(..)                      ,
    IsAppInfoMonitor                        ,
    toAppInfoMonitor                        ,
    noAppInfoMonitor                        ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveAppInfoMonitorMethod             ,
#endif


-- ** get #method:get#

    appInfoMonitorGet                       ,




 -- * Signals
-- ** changed #signal:changed#

    AppInfoMonitorChangedCallback           ,
#if defined(ENABLE_OVERLOADING)
    AppInfoMonitorChangedSignalInfo         ,
#endif
    C_AppInfoMonitorChangedCallback         ,
    afterAppInfoMonitorChanged              ,
    genClosure_AppInfoMonitorChanged        ,
    mk_AppInfoMonitorChangedCallback        ,
    noAppInfoMonitorChangedCallback         ,
    onAppInfoMonitorChanged                 ,
    wrap_AppInfoMonitorChangedCallback      ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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 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 GI.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype AppInfoMonitor = AppInfoMonitor (ManagedPtr AppInfoMonitor)
    deriving (AppInfoMonitor -> AppInfoMonitor -> Bool
(AppInfoMonitor -> AppInfoMonitor -> Bool)
-> (AppInfoMonitor -> AppInfoMonitor -> Bool) -> Eq AppInfoMonitor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AppInfoMonitor -> AppInfoMonitor -> Bool
$c/= :: AppInfoMonitor -> AppInfoMonitor -> Bool
== :: AppInfoMonitor -> AppInfoMonitor -> Bool
$c== :: AppInfoMonitor -> AppInfoMonitor -> Bool
Eq)
foreign import ccall "g_app_info_monitor_get_type"
    c_g_app_info_monitor_get_type :: IO GType

instance GObject AppInfoMonitor where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_app_info_monitor_get_type
    

-- | Convert 'AppInfoMonitor' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue AppInfoMonitor where
    toGValue :: AppInfoMonitor -> IO GValue
toGValue o :: AppInfoMonitor
o = do
        GType
gtype <- IO GType
c_g_app_info_monitor_get_type
        AppInfoMonitor -> (Ptr AppInfoMonitor -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AppInfoMonitor
o (GType
-> (GValue -> Ptr AppInfoMonitor -> IO ())
-> Ptr AppInfoMonitor
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr AppInfoMonitor -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO AppInfoMonitor
fromGValue gv :: GValue
gv = do
        Ptr AppInfoMonitor
ptr <- GValue -> IO (Ptr AppInfoMonitor)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr AppInfoMonitor)
        (ManagedPtr AppInfoMonitor -> AppInfoMonitor)
-> Ptr AppInfoMonitor -> IO AppInfoMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AppInfoMonitor -> AppInfoMonitor
AppInfoMonitor Ptr AppInfoMonitor
ptr
        
    

-- | Type class for types which can be safely cast to `AppInfoMonitor`, for instance with `toAppInfoMonitor`.
class (GObject o, O.IsDescendantOf AppInfoMonitor o) => IsAppInfoMonitor o
instance (GObject o, O.IsDescendantOf AppInfoMonitor o) => IsAppInfoMonitor o

instance O.HasParentTypes AppInfoMonitor
type instance O.ParentTypes AppInfoMonitor = '[GObject.Object.Object]

-- | Cast to `AppInfoMonitor`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toAppInfoMonitor :: (MonadIO m, IsAppInfoMonitor o) => o -> m AppInfoMonitor
toAppInfoMonitor :: o -> m AppInfoMonitor
toAppInfoMonitor = IO AppInfoMonitor -> m AppInfoMonitor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppInfoMonitor -> m AppInfoMonitor)
-> (o -> IO AppInfoMonitor) -> o -> m AppInfoMonitor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AppInfoMonitor -> AppInfoMonitor)
-> o -> IO AppInfoMonitor
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr AppInfoMonitor -> AppInfoMonitor
AppInfoMonitor

-- | A convenience alias for `Nothing` :: `Maybe` `AppInfoMonitor`.
noAppInfoMonitor :: Maybe AppInfoMonitor
noAppInfoMonitor :: Maybe AppInfoMonitor
noAppInfoMonitor = Maybe AppInfoMonitor
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveAppInfoMonitorMethod (t :: Symbol) (o :: *) :: * where
    ResolveAppInfoMonitorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAppInfoMonitorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAppInfoMonitorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAppInfoMonitorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAppInfoMonitorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAppInfoMonitorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAppInfoMonitorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAppInfoMonitorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAppInfoMonitorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAppInfoMonitorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAppInfoMonitorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAppInfoMonitorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAppInfoMonitorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAppInfoMonitorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAppInfoMonitorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAppInfoMonitorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAppInfoMonitorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAppInfoMonitorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAppInfoMonitorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAppInfoMonitorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAppInfoMonitorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAppInfoMonitorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAppInfoMonitorMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveAppInfoMonitorMethod t AppInfoMonitor, O.MethodInfo info AppInfoMonitor p) => OL.IsLabel t (AppInfoMonitor -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal AppInfoMonitor::changed
-- | Signal emitted when the app info database for changes (ie: newly installed
-- or removed applications).
type AppInfoMonitorChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AppInfoMonitorChangedCallback`@.
noAppInfoMonitorChangedCallback :: Maybe AppInfoMonitorChangedCallback
noAppInfoMonitorChangedCallback :: Maybe (IO ())
noAppInfoMonitorChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_AppInfoMonitorChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_AppInfoMonitorChangedCallback`.
foreign import ccall "wrapper"
    mk_AppInfoMonitorChangedCallback :: C_AppInfoMonitorChangedCallback -> IO (FunPtr C_AppInfoMonitorChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_AppInfoMonitorChanged :: MonadIO m => AppInfoMonitorChangedCallback -> m (GClosure C_AppInfoMonitorChangedCallback)
genClosure_AppInfoMonitorChanged :: IO () -> m (GClosure C_AppInfoMonitorChangedCallback)
genClosure_AppInfoMonitorChanged cb :: IO ()
cb = IO (GClosure C_AppInfoMonitorChangedCallback)
-> m (GClosure C_AppInfoMonitorChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AppInfoMonitorChangedCallback)
 -> m (GClosure C_AppInfoMonitorChangedCallback))
-> IO (GClosure C_AppInfoMonitorChangedCallback)
-> m (GClosure C_AppInfoMonitorChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppInfoMonitorChangedCallback
cb' = IO () -> C_AppInfoMonitorChangedCallback
wrap_AppInfoMonitorChangedCallback IO ()
cb
    C_AppInfoMonitorChangedCallback
-> IO (FunPtr C_AppInfoMonitorChangedCallback)
mk_AppInfoMonitorChangedCallback C_AppInfoMonitorChangedCallback
cb' IO (FunPtr C_AppInfoMonitorChangedCallback)
-> (FunPtr C_AppInfoMonitorChangedCallback
    -> IO (GClosure C_AppInfoMonitorChangedCallback))
-> IO (GClosure C_AppInfoMonitorChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AppInfoMonitorChangedCallback
-> IO (GClosure C_AppInfoMonitorChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AppInfoMonitorChangedCallback` into a `C_AppInfoMonitorChangedCallback`.
wrap_AppInfoMonitorChangedCallback ::
    AppInfoMonitorChangedCallback ->
    C_AppInfoMonitorChangedCallback
wrap_AppInfoMonitorChangedCallback :: IO () -> C_AppInfoMonitorChangedCallback
wrap_AppInfoMonitorChangedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' appInfoMonitor #changed callback
-- @
-- 
-- 
onAppInfoMonitorChanged :: (IsAppInfoMonitor a, MonadIO m) => a -> AppInfoMonitorChangedCallback -> m SignalHandlerId
onAppInfoMonitorChanged :: a -> IO () -> m SignalHandlerId
onAppInfoMonitorChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppInfoMonitorChangedCallback
cb' = IO () -> C_AppInfoMonitorChangedCallback
wrap_AppInfoMonitorChangedCallback IO ()
cb
    FunPtr C_AppInfoMonitorChangedCallback
cb'' <- C_AppInfoMonitorChangedCallback
-> IO (FunPtr C_AppInfoMonitorChangedCallback)
mk_AppInfoMonitorChangedCallback C_AppInfoMonitorChangedCallback
cb'
    a
-> Text
-> FunPtr C_AppInfoMonitorChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_AppInfoMonitorChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' appInfoMonitor #changed callback
-- @
-- 
-- 
afterAppInfoMonitorChanged :: (IsAppInfoMonitor a, MonadIO m) => a -> AppInfoMonitorChangedCallback -> m SignalHandlerId
afterAppInfoMonitorChanged :: a -> IO () -> m SignalHandlerId
afterAppInfoMonitorChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppInfoMonitorChangedCallback
cb' = IO () -> C_AppInfoMonitorChangedCallback
wrap_AppInfoMonitorChangedCallback IO ()
cb
    FunPtr C_AppInfoMonitorChangedCallback
cb'' <- C_AppInfoMonitorChangedCallback
-> IO (FunPtr C_AppInfoMonitorChangedCallback)
mk_AppInfoMonitorChangedCallback C_AppInfoMonitorChangedCallback
cb'
    a
-> Text
-> FunPtr C_AppInfoMonitorChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_AppInfoMonitorChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data AppInfoMonitorChangedSignalInfo
instance SignalInfo AppInfoMonitorChangedSignalInfo where
    type HaskellCallbackType AppInfoMonitorChangedSignalInfo = AppInfoMonitorChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AppInfoMonitorChangedCallback cb
        cb'' <- mk_AppInfoMonitorChangedCallback cb'
        connectSignalFunPtr obj "changed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AppInfoMonitor
type instance O.AttributeList AppInfoMonitor = AppInfoMonitorAttributeList
type AppInfoMonitorAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AppInfoMonitor = AppInfoMonitorSignalList
type AppInfoMonitorSignalList = ('[ '("changed", AppInfoMonitorChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method AppInfoMonitor::get
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "AppInfoMonitor" })
-- throws : False
-- Skip return : False

foreign import ccall "g_app_info_monitor_get" g_app_info_monitor_get :: 
    IO (Ptr AppInfoMonitor)

-- | Gets the t'GI.Gio.Objects.AppInfoMonitor.AppInfoMonitor' for the current thread-default main
-- context.
-- 
-- The t'GI.Gio.Objects.AppInfoMonitor.AppInfoMonitor' will emit a \"changed\" signal in the
-- thread-default main context whenever the list of installed
-- applications (as reported by 'GI.Gio.Functions.appInfoGetAll') may have changed.
-- 
-- You must only call 'GI.GObject.Objects.Object.objectUnref' on the return value from under
-- the same main context as you created it.
-- 
-- /Since: 2.40/
appInfoMonitorGet ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m AppInfoMonitor
    -- ^ __Returns:__ a reference to a t'GI.Gio.Objects.AppInfoMonitor.AppInfoMonitor'
appInfoMonitorGet :: m AppInfoMonitor
appInfoMonitorGet  = IO AppInfoMonitor -> m AppInfoMonitor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppInfoMonitor -> m AppInfoMonitor)
-> IO AppInfoMonitor -> m AppInfoMonitor
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppInfoMonitor
result <- IO (Ptr AppInfoMonitor)
g_app_info_monitor_get
    Text -> Ptr AppInfoMonitor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "appInfoMonitorGet" Ptr AppInfoMonitor
result
    AppInfoMonitor
result' <- ((ManagedPtr AppInfoMonitor -> AppInfoMonitor)
-> Ptr AppInfoMonitor -> IO AppInfoMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AppInfoMonitor -> AppInfoMonitor
AppInfoMonitor) Ptr AppInfoMonitor
result
    AppInfoMonitor -> IO AppInfoMonitor
forall (m :: * -> *) a. Monad m => a -> m a
return AppInfoMonitor
result'

#if defined(ENABLE_OVERLOADING)
#endif