{-# 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.Interfaces.MemoryMonitor.MemoryMonitor' will monitor system memory and suggest to the application
-- when to free memory so as to leave more room for other applications.
-- It is implemented on Linux using the <https://gitlab.freedesktop.org/hadess/low-memory-monitor/ Low Memory Monitor>
-- (<https://hadess.pages.freedesktop.org/low-memory-monitor/ API documentation>).
-- 
-- There is also an implementation for use inside Flatpak sandboxes.
-- 
-- Possible actions to take when the signal is received are:
-- 
-- * Free caches
-- * Save files that haven\'t been looked at in a while to disk, ready to be reopened when needed
-- * Run a garbage collection cycle
-- * Try and compress fragmented allocations
-- * Exit on idle if the process has no reason to stay around
-- 
-- 
-- See t'GI.Gio.Enums.MemoryMonitorWarningLevel' for details on the various warning levels.
-- 
-- 
-- === /C code/
-- >
-- >static void
-- >warning_cb (GMemoryMonitor *m, GMemoryMonitorWarningLevel level)
-- >{
-- >  g_debug ("Warning level: %d", level);
-- >  if (warning_level > G_MEMORY_MONITOR_WARNING_LEVEL_LOW)
-- >    drop_caches ();
-- >}
-- >
-- >static GMemoryMonitor *
-- >monitor_low_memory (void)
-- >{
-- >  GMemoryMonitor *m;
-- >  m = g_memory_monitor_dup_default ();
-- >  g_signal_connect (G_OBJECT (m), "low-memory-warning",
-- >                    G_CALLBACK (warning_cb), NULL);
-- >  return m;
-- >}
-- 
-- 
-- Don\'t forget to disconnect the [lowMemoryWarning]("GI.Gio.Interfaces.MemoryMonitor#g:signal:lowMemoryWarning")
-- signal, and unref the t'GI.Gio.Interfaces.MemoryMonitor.MemoryMonitor' itself when exiting.
-- 
-- /Since: 2.64/

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

module GI.Gio.Interfaces.MemoryMonitor
    ( 

-- * Exported types
    MemoryMonitor(..)                       ,
    IsMemoryMonitor                         ,
    toMemoryMonitor                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveMemoryMonitorMethod              ,
#endif


-- ** dupDefault #method:dupDefault#

    memoryMonitorDupDefault                 ,




 -- * Signals
-- ** lowMemoryWarning #signal:lowMemoryWarning#

    C_MemoryMonitorLowMemoryWarningCallback ,
    MemoryMonitorLowMemoryWarningCallback   ,
#if defined(ENABLE_OVERLOADING)
    MemoryMonitorLowMemoryWarningSignalInfo ,
#endif
    afterMemoryMonitorLowMemoryWarning      ,
    genClosure_MemoryMonitorLowMemoryWarning,
    mk_MemoryMonitorLowMemoryWarningCallback,
    noMemoryMonitorLowMemoryWarningCallback ,
    onMemoryMonitorLowMemoryWarning         ,
    wrap_MemoryMonitorLowMemoryWarningCallback,




    ) 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.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 Control.Monad.IO.Class as MIO
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
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable

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

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

foreign import ccall "g_memory_monitor_get_type"
    c_g_memory_monitor_get_type :: IO B.Types.GType

instance B.Types.TypedObject MemoryMonitor where
    glibType :: IO GType
glibType = IO GType
c_g_memory_monitor_get_type

instance B.Types.GObject MemoryMonitor

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

-- | Type class for types which can be safely cast to `MemoryMonitor`, for instance with `toMemoryMonitor`.
class (SP.GObject o, O.IsDescendantOf MemoryMonitor o) => IsMemoryMonitor o
instance (SP.GObject o, O.IsDescendantOf MemoryMonitor o) => IsMemoryMonitor o

instance O.HasParentTypes MemoryMonitor
type instance O.ParentTypes MemoryMonitor = '[Gio.Initable.Initable, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
#endif

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

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

#endif

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

foreign import ccall "g_memory_monitor_dup_default" g_memory_monitor_dup_default :: 
    IO (Ptr MemoryMonitor)

-- | Gets a reference to the default t'GI.Gio.Interfaces.MemoryMonitor.MemoryMonitor' for the system.
-- 
-- /Since: 2.64/
memoryMonitorDupDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m MemoryMonitor
    -- ^ __Returns:__ a new reference to the default t'GI.Gio.Interfaces.MemoryMonitor.MemoryMonitor'
memoryMonitorDupDefault :: m MemoryMonitor
memoryMonitorDupDefault  = IO MemoryMonitor -> m MemoryMonitor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MemoryMonitor -> m MemoryMonitor)
-> IO MemoryMonitor -> m MemoryMonitor
forall a b. (a -> b) -> a -> b
$ do
    Ptr MemoryMonitor
result <- IO (Ptr MemoryMonitor)
g_memory_monitor_dup_default
    Text -> Ptr MemoryMonitor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"memoryMonitorDupDefault" Ptr MemoryMonitor
result
    MemoryMonitor
result' <- ((ManagedPtr MemoryMonitor -> MemoryMonitor)
-> Ptr MemoryMonitor -> IO MemoryMonitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MemoryMonitor -> MemoryMonitor
MemoryMonitor) Ptr MemoryMonitor
result
    MemoryMonitor -> IO MemoryMonitor
forall (m :: * -> *) a. Monad m => a -> m a
return MemoryMonitor
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- signal MemoryMonitor::low-memory-warning
-- | Emitted when the system is running low on free memory. The signal
-- handler should then take the appropriate action depending on the
-- warning level. See the t'GI.Gio.Enums.MemoryMonitorWarningLevel' documentation for
-- details.
-- 
-- /Since: 2.64/
type MemoryMonitorLowMemoryWarningCallback =
    Gio.Enums.MemoryMonitorWarningLevel
    -- ^ /@level@/: the t'GI.Gio.Enums.MemoryMonitorWarningLevel' warning level
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MemoryMonitorLowMemoryWarningCallback`@.
noMemoryMonitorLowMemoryWarningCallback :: Maybe MemoryMonitorLowMemoryWarningCallback
noMemoryMonitorLowMemoryWarningCallback :: Maybe MemoryMonitorLowMemoryWarningCallback
noMemoryMonitorLowMemoryWarningCallback = Maybe MemoryMonitorLowMemoryWarningCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_MemoryMonitorLowMemoryWarning :: MonadIO m => MemoryMonitorLowMemoryWarningCallback -> m (GClosure C_MemoryMonitorLowMemoryWarningCallback)
genClosure_MemoryMonitorLowMemoryWarning :: MemoryMonitorLowMemoryWarningCallback
-> m (GClosure C_MemoryMonitorLowMemoryWarningCallback)
genClosure_MemoryMonitorLowMemoryWarning MemoryMonitorLowMemoryWarningCallback
cb = IO (GClosure C_MemoryMonitorLowMemoryWarningCallback)
-> m (GClosure C_MemoryMonitorLowMemoryWarningCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MemoryMonitorLowMemoryWarningCallback)
 -> m (GClosure C_MemoryMonitorLowMemoryWarningCallback))
-> IO (GClosure C_MemoryMonitorLowMemoryWarningCallback)
-> m (GClosure C_MemoryMonitorLowMemoryWarningCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MemoryMonitorLowMemoryWarningCallback
cb' = MemoryMonitorLowMemoryWarningCallback
-> C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback MemoryMonitorLowMemoryWarningCallback
cb
    C_MemoryMonitorLowMemoryWarningCallback
-> IO (FunPtr C_MemoryMonitorLowMemoryWarningCallback)
mk_MemoryMonitorLowMemoryWarningCallback C_MemoryMonitorLowMemoryWarningCallback
cb' IO (FunPtr C_MemoryMonitorLowMemoryWarningCallback)
-> (FunPtr C_MemoryMonitorLowMemoryWarningCallback
    -> IO (GClosure C_MemoryMonitorLowMemoryWarningCallback))
-> IO (GClosure C_MemoryMonitorLowMemoryWarningCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MemoryMonitorLowMemoryWarningCallback
-> IO (GClosure C_MemoryMonitorLowMemoryWarningCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MemoryMonitorLowMemoryWarningCallback` into a `C_MemoryMonitorLowMemoryWarningCallback`.
wrap_MemoryMonitorLowMemoryWarningCallback ::
    MemoryMonitorLowMemoryWarningCallback ->
    C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback :: MemoryMonitorLowMemoryWarningCallback
-> C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback MemoryMonitorLowMemoryWarningCallback
_cb Ptr ()
_ CUInt
level Ptr ()
_ = do
    let level' :: MemoryMonitorWarningLevel
level' = (Int -> MemoryMonitorWarningLevel
forall a. Enum a => Int -> a
toEnum (Int -> MemoryMonitorWarningLevel)
-> (CUInt -> Int) -> CUInt -> MemoryMonitorWarningLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
level
    MemoryMonitorLowMemoryWarningCallback
_cb  MemoryMonitorWarningLevel
level'


-- | Connect a signal handler for the [lowMemoryWarning](#signal:lowMemoryWarning) 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' memoryMonitor #lowMemoryWarning callback
-- @
-- 
-- 
onMemoryMonitorLowMemoryWarning :: (IsMemoryMonitor a, MonadIO m) => a -> MemoryMonitorLowMemoryWarningCallback -> m SignalHandlerId
onMemoryMonitorLowMemoryWarning :: a -> MemoryMonitorLowMemoryWarningCallback -> m SignalHandlerId
onMemoryMonitorLowMemoryWarning a
obj MemoryMonitorLowMemoryWarningCallback
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_MemoryMonitorLowMemoryWarningCallback
cb' = MemoryMonitorLowMemoryWarningCallback
-> C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback MemoryMonitorLowMemoryWarningCallback
cb
    FunPtr C_MemoryMonitorLowMemoryWarningCallback
cb'' <- C_MemoryMonitorLowMemoryWarningCallback
-> IO (FunPtr C_MemoryMonitorLowMemoryWarningCallback)
mk_MemoryMonitorLowMemoryWarningCallback C_MemoryMonitorLowMemoryWarningCallback
cb'
    a
-> Text
-> FunPtr C_MemoryMonitorLowMemoryWarningCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"low-memory-warning" FunPtr C_MemoryMonitorLowMemoryWarningCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [lowMemoryWarning](#signal:lowMemoryWarning) 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' memoryMonitor #lowMemoryWarning callback
-- @
-- 
-- 
afterMemoryMonitorLowMemoryWarning :: (IsMemoryMonitor a, MonadIO m) => a -> MemoryMonitorLowMemoryWarningCallback -> m SignalHandlerId
afterMemoryMonitorLowMemoryWarning :: a -> MemoryMonitorLowMemoryWarningCallback -> m SignalHandlerId
afterMemoryMonitorLowMemoryWarning a
obj MemoryMonitorLowMemoryWarningCallback
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_MemoryMonitorLowMemoryWarningCallback
cb' = MemoryMonitorLowMemoryWarningCallback
-> C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback MemoryMonitorLowMemoryWarningCallback
cb
    FunPtr C_MemoryMonitorLowMemoryWarningCallback
cb'' <- C_MemoryMonitorLowMemoryWarningCallback
-> IO (FunPtr C_MemoryMonitorLowMemoryWarningCallback)
mk_MemoryMonitorLowMemoryWarningCallback C_MemoryMonitorLowMemoryWarningCallback
cb'
    a
-> Text
-> FunPtr C_MemoryMonitorLowMemoryWarningCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"low-memory-warning" FunPtr C_MemoryMonitorLowMemoryWarningCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MemoryMonitorLowMemoryWarningSignalInfo
instance SignalInfo MemoryMonitorLowMemoryWarningSignalInfo where
    type HaskellCallbackType MemoryMonitorLowMemoryWarningSignalInfo = MemoryMonitorLowMemoryWarningCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MemoryMonitorLowMemoryWarningCallback cb
        cb'' <- mk_MemoryMonitorLowMemoryWarningCallback cb'
        connectSignalFunPtr obj "low-memory-warning" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList MemoryMonitor = MemoryMonitorSignalList
type MemoryMonitorSignalList = ('[ '("lowMemoryWarning", MemoryMonitorLowMemoryWarningSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif