{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- 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
--  - Call <http://developer.gnome.org/gio/stable/man:malloc_trim `malloc_trim(3)`> to return cached heap pages to
--    the kernel (if supported by your libc)
-- 
-- Note that some actions may not always improve system performance, and so
-- should be profiled for your application. @malloc_trim()@, for example, may
-- make future heap allocations slower (due to releasing cached heap pages back
-- to the kernel).
-- 
-- 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 [MemoryMonitor::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
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [init]("GI.Gio.Interfaces.Initable#g:method:init"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveMemoryMonitorMethod              ,
#endif

-- ** dupDefault #method:dupDefault#

    memoryMonitorDupDefault                 ,




 -- * Signals


-- ** lowMemoryWarning #signal:lowMemoryWarning#

    MemoryMonitorLowMemoryWarningCallback   ,
#if defined(ENABLE_OVERLOADING)
    MemoryMonitorLowMemoryWarningSignalInfo ,
#endif
    afterMemoryMonitorLowMemoryWarning      ,
    onMemoryMonitorLowMemoryWarning         ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import 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
$c== :: MemoryMonitor -> MemoryMonitor -> Bool
== :: MemoryMonitor -> MemoryMonitor -> Bool
$c/= :: MemoryMonitor -> MemoryMonitor -> Bool
/= :: 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

-- | 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 :: (MIO.MonadIO m, IsMemoryMonitor o) => o -> m MemoryMonitor
toMemoryMonitor :: forall (m :: * -> *) o.
(MonadIO m, IsMemoryMonitor o) =>
o -> m MemoryMonitor
toMemoryMonitor = IO MemoryMonitor -> m MemoryMonitor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr MemoryMonitor -> MemoryMonitor
MemoryMonitor

-- | Convert 'MemoryMonitor' 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 MemoryMonitor) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_memory_monitor_get_type
    gvalueSet_ :: Ptr GValue -> Maybe MemoryMonitor -> IO ()
gvalueSet_ Ptr GValue
gv Maybe MemoryMonitor
P.Nothing = Ptr GValue -> Ptr MemoryMonitor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr MemoryMonitor
forall a. Ptr a
FP.nullPtr :: FP.Ptr MemoryMonitor)
    gvalueSet_ Ptr GValue
gv (P.Just MemoryMonitor
obj) = MemoryMonitor -> (Ptr MemoryMonitor -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr MemoryMonitor
obj (Ptr GValue -> Ptr MemoryMonitor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe MemoryMonitor)
gvalueGet_ Ptr GValue
gv = do
        Ptr MemoryMonitor
ptr <- Ptr GValue -> IO (Ptr MemoryMonitor)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr MemoryMonitor)
        if Ptr MemoryMonitor
ptr Ptr MemoryMonitor -> Ptr MemoryMonitor -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr MemoryMonitor
forall a. Ptr a
FP.nullPtr
        then MemoryMonitor -> Maybe MemoryMonitor
forall a. a -> Maybe a
P.Just (MemoryMonitor -> Maybe MemoryMonitor)
-> IO MemoryMonitor -> IO (Maybe MemoryMonitor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe MemoryMonitor -> IO (Maybe MemoryMonitor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MemoryMonitor
forall a. Maybe a
P.Nothing
        
    

#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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveMemoryMonitorMethod t MemoryMonitor, O.OverloadedMethod info MemoryMonitor p, R.HasField t MemoryMonitor p) => R.HasField t MemoryMonitor p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveMemoryMonitorMethod t MemoryMonitor, O.OverloadedMethodInfo info MemoryMonitor) => OL.IsLabel t (O.MethodProxy info MemoryMonitor) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m MemoryMonitor
memoryMonitorDupDefault  = IO MemoryMonitor -> m MemoryMonitor
forall a. IO a -> m a
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 a. a -> IO a
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 ()

type C_MemoryMonitorLowMemoryWarningCallback =
    Ptr MemoryMonitor ->                    -- 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_MemoryMonitorLowMemoryWarningCallback :: 
    GObject a => (a -> MemoryMonitorLowMemoryWarningCallback) ->
    C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback :: forall a.
GObject a =>
(a -> MemoryMonitorLowMemoryWarningCallback)
-> C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback a -> MemoryMonitorLowMemoryWarningCallback
gi'cb Ptr MemoryMonitor
gi'selfPtr 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
    Ptr MemoryMonitor -> (MemoryMonitor -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr MemoryMonitor
gi'selfPtr ((MemoryMonitor -> IO ()) -> IO ())
-> (MemoryMonitor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \MemoryMonitor
gi'self -> a -> MemoryMonitorLowMemoryWarningCallback
gi'cb (MemoryMonitor -> a
forall a b. Coercible a b => a -> b
Coerce.coerce MemoryMonitor
gi'self)  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 -> ((?self :: a) => MemoryMonitorLowMemoryWarningCallback) -> m SignalHandlerId
onMemoryMonitorLowMemoryWarning :: forall a (m :: * -> *).
(IsMemoryMonitor a, MonadIO m) =>
a
-> ((?self::a) => MemoryMonitorLowMemoryWarningCallback)
-> m SignalHandlerId
onMemoryMonitorLowMemoryWarning a
obj (?self::a) => MemoryMonitorLowMemoryWarningCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> MemoryMonitorLowMemoryWarningCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => MemoryMonitorLowMemoryWarningCallback
MemoryMonitorLowMemoryWarningCallback
cb
    let wrapped' :: C_MemoryMonitorLowMemoryWarningCallback
wrapped' = (a -> MemoryMonitorLowMemoryWarningCallback)
-> C_MemoryMonitorLowMemoryWarningCallback
forall a.
GObject a =>
(a -> MemoryMonitorLowMemoryWarningCallback)
-> C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback a -> MemoryMonitorLowMemoryWarningCallback
wrapped
    FunPtr C_MemoryMonitorLowMemoryWarningCallback
wrapped'' <- C_MemoryMonitorLowMemoryWarningCallback
-> IO (FunPtr C_MemoryMonitorLowMemoryWarningCallback)
mk_MemoryMonitorLowMemoryWarningCallback C_MemoryMonitorLowMemoryWarningCallback
wrapped'
    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
wrapped'' 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
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterMemoryMonitorLowMemoryWarning :: (IsMemoryMonitor a, MonadIO m) => a -> ((?self :: a) => MemoryMonitorLowMemoryWarningCallback) -> m SignalHandlerId
afterMemoryMonitorLowMemoryWarning :: forall a (m :: * -> *).
(IsMemoryMonitor a, MonadIO m) =>
a
-> ((?self::a) => MemoryMonitorLowMemoryWarningCallback)
-> m SignalHandlerId
afterMemoryMonitorLowMemoryWarning a
obj (?self::a) => MemoryMonitorLowMemoryWarningCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> MemoryMonitorLowMemoryWarningCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => MemoryMonitorLowMemoryWarningCallback
MemoryMonitorLowMemoryWarningCallback
cb
    let wrapped' :: C_MemoryMonitorLowMemoryWarningCallback
wrapped' = (a -> MemoryMonitorLowMemoryWarningCallback)
-> C_MemoryMonitorLowMemoryWarningCallback
forall a.
GObject a =>
(a -> MemoryMonitorLowMemoryWarningCallback)
-> C_MemoryMonitorLowMemoryWarningCallback
wrap_MemoryMonitorLowMemoryWarningCallback a -> MemoryMonitorLowMemoryWarningCallback
wrapped
    FunPtr C_MemoryMonitorLowMemoryWarningCallback
wrapped'' <- C_MemoryMonitorLowMemoryWarningCallback
-> IO (FunPtr C_MemoryMonitorLowMemoryWarningCallback)
mk_MemoryMonitorLowMemoryWarningCallback C_MemoryMonitorLowMemoryWarningCallback
wrapped'
    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
wrapped'' 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
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.MemoryMonitor::low-memory-warning"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-MemoryMonitor.html#g:signal:lowMemoryWarning"})

#endif

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

#endif