{-# 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.Notification.Notification' is a mechanism for creating a notification to be shown
-- to the user -- typically as a pop-up notification presented by the
-- desktop environment shell.
-- 
-- The key difference between t'GI.Gio.Objects.Notification.Notification' and other similar APIs is
-- that, if supported by the desktop environment, notifications sent
-- with t'GI.Gio.Objects.Notification.Notification' will persist after the application has exited,
-- and even across system reboots.
-- 
-- Since the user may click on a notification while the application is
-- not running, applications using t'GI.Gio.Objects.Notification.Notification' should be able to be
-- started as a D-Bus service, using t'GI.Gio.Objects.Application.Application'.
-- 
-- User interaction with a notification (either the default action, or
-- buttons) must be associated with actions on the application (ie:
-- \"app.\" actions).  It is not possible to route user interaction
-- through the notification itself, because the object will not exist if
-- the application is autostarted as a result of a notification being
-- clicked.
-- 
-- A notification can be sent with 'GI.Gio.Objects.Application.applicationSendNotification'.
-- 
-- /Since: 2.40/

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

module GI.Gio.Objects.Notification
    ( 

-- * Exported types
    Notification(..)                        ,
    IsNotification                          ,
    toNotification                          ,
    noNotification                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveNotificationMethod               ,
#endif


-- ** addButton #method:addButton#

#if defined(ENABLE_OVERLOADING)
    NotificationAddButtonMethodInfo         ,
#endif
    notificationAddButton                   ,


-- ** addButtonWithTarget #method:addButtonWithTarget#

#if defined(ENABLE_OVERLOADING)
    NotificationAddButtonWithTargetMethodInfo,
#endif
    notificationAddButtonWithTarget         ,


-- ** new #method:new#

    notificationNew                         ,


-- ** setBody #method:setBody#

#if defined(ENABLE_OVERLOADING)
    NotificationSetBodyMethodInfo           ,
#endif
    notificationSetBody                     ,


-- ** setDefaultAction #method:setDefaultAction#

#if defined(ENABLE_OVERLOADING)
    NotificationSetDefaultActionMethodInfo  ,
#endif
    notificationSetDefaultAction            ,


-- ** setDefaultActionAndTarget #method:setDefaultActionAndTarget#

#if defined(ENABLE_OVERLOADING)
    NotificationSetDefaultActionAndTargetMethodInfo,
#endif
    notificationSetDefaultActionAndTarget   ,


-- ** setIcon #method:setIcon#

#if defined(ENABLE_OVERLOADING)
    NotificationSetIconMethodInfo           ,
#endif
    notificationSetIcon                     ,


-- ** setPriority #method:setPriority#

#if defined(ENABLE_OVERLOADING)
    NotificationSetPriorityMethodInfo       ,
#endif
    notificationSetPriority                 ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    NotificationSetTitleMethodInfo          ,
#endif
    notificationSetTitle                    ,


-- ** setUrgent #method:setUrgent#

#if defined(ENABLE_OVERLOADING)
    NotificationSetUrgentMethodInfo         ,
#endif
    notificationSetUrgent                   ,




    ) 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
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon

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

instance GObject Notification where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_notification_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `Notification`.
noNotification :: Maybe Notification
noNotification :: Maybe Notification
noNotification = Maybe Notification
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveNotificationMethod (t :: Symbol) (o :: *) :: * where
    ResolveNotificationMethod "addButton" o = NotificationAddButtonMethodInfo
    ResolveNotificationMethod "addButtonWithTarget" o = NotificationAddButtonWithTargetMethodInfo
    ResolveNotificationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveNotificationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveNotificationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveNotificationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveNotificationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveNotificationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveNotificationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveNotificationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveNotificationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveNotificationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveNotificationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveNotificationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveNotificationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveNotificationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveNotificationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveNotificationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveNotificationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveNotificationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveNotificationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveNotificationMethod "setBody" o = NotificationSetBodyMethodInfo
    ResolveNotificationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveNotificationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveNotificationMethod "setDefaultAction" o = NotificationSetDefaultActionMethodInfo
    ResolveNotificationMethod "setDefaultActionAndTarget" o = NotificationSetDefaultActionAndTargetMethodInfo
    ResolveNotificationMethod "setIcon" o = NotificationSetIconMethodInfo
    ResolveNotificationMethod "setPriority" o = NotificationSetPriorityMethodInfo
    ResolveNotificationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveNotificationMethod "setTitle" o = NotificationSetTitleMethodInfo
    ResolveNotificationMethod "setUrgent" o = NotificationSetUrgentMethodInfo
    ResolveNotificationMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method Notification::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the title of the notification"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "Notification" })
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_new" g_notification_new :: 
    CString ->                              -- title : TBasicType TUTF8
    IO (Ptr Notification)

-- | Creates a new t'GI.Gio.Objects.Notification.Notification' with /@title@/ as its title.
-- 
-- After populating /@notification@/ with more details, it can be sent to
-- the desktop shell with 'GI.Gio.Objects.Application.applicationSendNotification'. Changing
-- any properties after this call will not have any effect until
-- resending /@notification@/.
-- 
-- /Since: 2.40/
notificationNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@title@/: the title of the notification
    -> m Notification
    -- ^ __Returns:__ a new t'GI.Gio.Objects.Notification.Notification' instance
notificationNew :: Text -> m Notification
notificationNew title :: Text
title = IO Notification -> m Notification
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Notification -> m Notification)
-> IO Notification -> m Notification
forall a b. (a -> b) -> a -> b
$ do
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr Notification
result <- CString -> IO (Ptr Notification)
g_notification_new CString
title'
    Text -> Ptr Notification -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "notificationNew" Ptr Notification
result
    Notification
result' <- ((ManagedPtr Notification -> Notification)
-> Ptr Notification -> IO Notification
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Notification -> Notification
Notification) Ptr Notification
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    Notification -> IO Notification
forall (m :: * -> *) a. Monad m => a -> m a
return Notification
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Notification::add_button
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "label of the button"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detailed_action"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a detailed action name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_add_button" g_notification_add_button :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CString ->                              -- label : TBasicType TUTF8
    CString ->                              -- detailed_action : TBasicType TUTF8
    IO ()

-- | Adds a button to /@notification@/ that activates the action in
-- /@detailedAction@/ when clicked. That action must be an
-- application-wide action (starting with \"app.\"). If /@detailedAction@/
-- contains a target, the action will be activated with that target as
-- its parameter.
-- 
-- See 'GI.Gio.Functions.actionParseDetailedName' for a description of the format
-- for /@detailedAction@/.
-- 
-- /Since: 2.40/
notificationAddButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> T.Text
    -- ^ /@label@/: label of the button
    -> T.Text
    -- ^ /@detailedAction@/: a detailed action name
    -> m ()
notificationAddButton :: a -> Text -> Text -> m ()
notificationAddButton notification :: a
notification label :: Text
label detailedAction :: Text
detailedAction = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    CString
label' <- Text -> IO CString
textToCString Text
label
    CString
detailedAction' <- Text -> IO CString
textToCString Text
detailedAction
    Ptr Notification -> CString -> CString -> IO ()
g_notification_add_button Ptr Notification
notification' CString
label' CString
detailedAction'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
label'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
detailedAction'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationAddButtonMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationAddButtonMethodInfo a signature where
    overloadedMethod = notificationAddButton

#endif

-- method Notification::add_button_with_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "label of the button"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an action name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GVariant to use as @action's parameter, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_add_button_with_target_value" g_notification_add_button_with_target_value :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CString ->                              -- label : TBasicType TUTF8
    CString ->                              -- action : TBasicType TUTF8
    Ptr GVariant ->                         -- target : TVariant
    IO ()

-- | Adds a button to /@notification@/ that activates /@action@/ when clicked.
-- /@action@/ must be an application-wide action (it must start with \"app.\").
-- 
-- If /@target@/ is non-'P.Nothing', /@action@/ will be activated with /@target@/ as
-- its parameter.
-- 
-- /Since: 2.40/
notificationAddButtonWithTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> T.Text
    -- ^ /@label@/: label of the button
    -> T.Text
    -- ^ /@action@/: an action name
    -> Maybe (GVariant)
    -- ^ /@target@/: a t'GVariant' to use as /@action@/\'s parameter, or 'P.Nothing'
    -> m ()
notificationAddButtonWithTarget :: a -> Text -> Text -> Maybe GVariant -> m ()
notificationAddButtonWithTarget notification :: a
notification label :: Text
label action :: Text
action target :: Maybe GVariant
target = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    CString
label' <- Text -> IO CString
textToCString Text
label
    CString
action' <- Text -> IO CString
textToCString Text
action
    Ptr GVariant
maybeTarget <- case Maybe GVariant
target of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jTarget :: GVariant
jTarget -> do
            Ptr GVariant
jTarget' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jTarget
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jTarget'
    Ptr Notification -> CString -> CString -> Ptr GVariant -> IO ()
g_notification_add_button_with_target_value Ptr Notification
notification' CString
label' CString
action' Ptr GVariant
maybeTarget
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
target GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
label'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
action'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationAddButtonWithTargetMethodInfo
instance (signature ~ (T.Text -> T.Text -> Maybe (GVariant) -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationAddButtonWithTargetMethodInfo a signature where
    overloadedMethod = notificationAddButtonWithTarget

#endif

-- method Notification::set_body
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "body"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new body for @notification, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_set_body" g_notification_set_body :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CString ->                              -- body : TBasicType TUTF8
    IO ()

-- | Sets the body of /@notification@/ to /@body@/.
-- 
-- /Since: 2.40/
notificationSetBody ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> Maybe (T.Text)
    -- ^ /@body@/: the new body for /@notification@/, or 'P.Nothing'
    -> m ()
notificationSetBody :: a -> Maybe Text -> m ()
notificationSetBody notification :: a
notification body :: Maybe Text
body = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    CString
maybeBody <- case Maybe Text
body of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jBody :: Text
jBody -> do
            CString
jBody' <- Text -> IO CString
textToCString Text
jBody
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jBody'
    Ptr Notification -> CString -> IO ()
g_notification_set_body Ptr Notification
notification' CString
maybeBody
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeBody
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationSetBodyMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationSetBodyMethodInfo a signature where
    overloadedMethod = notificationSetBody

#endif

-- method Notification::set_default_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detailed_action"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a detailed action name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_set_default_action" g_notification_set_default_action :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CString ->                              -- detailed_action : TBasicType TUTF8
    IO ()

-- | Sets the default action of /@notification@/ to /@detailedAction@/. This
-- action is activated when the notification is clicked on.
-- 
-- The action in /@detailedAction@/ must be an application-wide action (it
-- must start with \"app.\"). If /@detailedAction@/ contains a target, the
-- given action will be activated with that target as its parameter.
-- See 'GI.Gio.Functions.actionParseDetailedName' for a description of the format
-- for /@detailedAction@/.
-- 
-- When no default action is set, the application that the notification
-- was sent on is activated.
-- 
-- /Since: 2.40/
notificationSetDefaultAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> T.Text
    -- ^ /@detailedAction@/: a detailed action name
    -> m ()
notificationSetDefaultAction :: a -> Text -> m ()
notificationSetDefaultAction notification :: a
notification detailedAction :: Text
detailedAction = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    CString
detailedAction' <- Text -> IO CString
textToCString Text
detailedAction
    Ptr Notification -> CString -> IO ()
g_notification_set_default_action Ptr Notification
notification' CString
detailedAction'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
detailedAction'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationSetDefaultActionMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationSetDefaultActionMethodInfo a signature where
    overloadedMethod = notificationSetDefaultAction

#endif

-- method Notification::set_default_action_and_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an action name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GVariant to use as @action's parameter, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_set_default_action_and_target_value" g_notification_set_default_action_and_target_value :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CString ->                              -- action : TBasicType TUTF8
    Ptr GVariant ->                         -- target : TVariant
    IO ()

-- | Sets the default action of /@notification@/ to /@action@/. This action is
-- activated when the notification is clicked on. It must be an
-- application-wide action (start with \"app.\").
-- 
-- If /@target@/ is non-'P.Nothing', /@action@/ will be activated with /@target@/ as
-- its parameter.
-- 
-- When no default action is set, the application that the notification
-- was sent on is activated.
-- 
-- /Since: 2.40/
notificationSetDefaultActionAndTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> T.Text
    -- ^ /@action@/: an action name
    -> Maybe (GVariant)
    -- ^ /@target@/: a t'GVariant' to use as /@action@/\'s parameter, or 'P.Nothing'
    -> m ()
notificationSetDefaultActionAndTarget :: a -> Text -> Maybe GVariant -> m ()
notificationSetDefaultActionAndTarget notification :: a
notification action :: Text
action target :: Maybe GVariant
target = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    CString
action' <- Text -> IO CString
textToCString Text
action
    Ptr GVariant
maybeTarget <- case Maybe GVariant
target of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jTarget :: GVariant
jTarget -> do
            Ptr GVariant
jTarget' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jTarget
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jTarget'
    Ptr Notification -> CString -> Ptr GVariant -> IO ()
g_notification_set_default_action_and_target_value Ptr Notification
notification' CString
action' Ptr GVariant
maybeTarget
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
target GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
action'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationSetDefaultActionAndTargetMethodInfo
instance (signature ~ (T.Text -> Maybe (GVariant) -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationSetDefaultActionAndTargetMethodInfo a signature where
    overloadedMethod = notificationSetDefaultActionAndTarget

#endif

-- method Notification::set_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the icon to be shown in @notification, as a #GIcon"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_set_icon" g_notification_set_icon :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO ()

-- | Sets the icon of /@notification@/ to /@icon@/.
-- 
-- /Since: 2.40/
notificationSetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> b
    -- ^ /@icon@/: the icon to be shown in /@notification@/, as a t'GI.Gio.Interfaces.Icon.Icon'
    -> m ()
notificationSetIcon :: a -> b -> m ()
notificationSetIcon notification :: a
notification icon :: b
icon = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    Ptr Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    Ptr Notification -> Ptr Icon -> IO ()
g_notification_set_icon Ptr Notification
notification' Ptr Icon
icon'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationSetIconMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsNotification a, Gio.Icon.IsIcon b) => O.MethodInfo NotificationSetIconMethodInfo a signature where
    overloadedMethod = notificationSetIcon

#endif

-- method Notification::set_priority
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "priority"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "NotificationPriority" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotificationPriority"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_set_priority" g_notification_set_priority :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CUInt ->                                -- priority : TInterface (Name {namespace = "Gio", name = "NotificationPriority"})
    IO ()

-- | Sets the priority of /@notification@/ to /@priority@/. See
-- t'GI.Gio.Enums.NotificationPriority' for possible values.
notificationSetPriority ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> Gio.Enums.NotificationPriority
    -- ^ /@priority@/: a t'GI.Gio.Enums.NotificationPriority'
    -> m ()
notificationSetPriority :: a -> NotificationPriority -> m ()
notificationSetPriority notification :: a
notification priority :: NotificationPriority
priority = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    let priority' :: CUInt
priority' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (NotificationPriority -> Int) -> NotificationPriority -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NotificationPriority -> Int
forall a. Enum a => a -> Int
fromEnum) NotificationPriority
priority
    Ptr Notification -> CUInt -> IO ()
g_notification_set_priority Ptr Notification
notification' CUInt
priority'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationSetPriorityMethodInfo
instance (signature ~ (Gio.Enums.NotificationPriority -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationSetPriorityMethodInfo a signature where
    overloadedMethod = notificationSetPriority

#endif

-- method Notification::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new title for @notification"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_set_title" g_notification_set_title :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Sets the title of /@notification@/ to /@title@/.
-- 
-- /Since: 2.40/
notificationSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> T.Text
    -- ^ /@title@/: the new title for /@notification@/
    -> m ()
notificationSetTitle :: a -> Text -> m ()
notificationSetTitle notification :: a
notification title :: Text
title = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr Notification -> CString -> IO ()
g_notification_set_title Ptr Notification
notification' CString
title'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationSetTitleMethodInfo a signature where
    overloadedMethod = notificationSetTitle

#endif

-- method Notification::set_urgent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "notification"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Notification" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GNotification" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "urgent"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE if @notification is urgent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_notification_set_urgent" g_notification_set_urgent :: 
    Ptr Notification ->                     -- notification : TInterface (Name {namespace = "Gio", name = "Notification"})
    CInt ->                                 -- urgent : TBasicType TBoolean
    IO ()

{-# DEPRECATED notificationSetUrgent ["(Since version 2.42)","Since 2.42, this has been deprecated in favour of","   'GI.Gio.Objects.Notification.notificationSetPriority'."] #-}
-- | Deprecated in favor of 'GI.Gio.Objects.Notification.notificationSetPriority'.
-- 
-- /Since: 2.40/
notificationSetUrgent ::
    (B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
    a
    -- ^ /@notification@/: a t'GI.Gio.Objects.Notification.Notification'
    -> Bool
    -- ^ /@urgent@/: 'P.True' if /@notification@/ is urgent
    -> m ()
notificationSetUrgent :: a -> Bool -> m ()
notificationSetUrgent notification :: a
notification urgent :: Bool
urgent = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Notification
notification' <- a -> IO (Ptr Notification)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
notification
    let urgent' :: CInt
urgent' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
urgent
    Ptr Notification -> CInt -> IO ()
g_notification_set_urgent Ptr Notification
notification' CInt
urgent'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
notification
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NotificationSetUrgentMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsNotification a) => O.MethodInfo NotificationSetUrgentMethodInfo a signature where
    overloadedMethod = notificationSetUrgent

#endif