{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.Notification
(
Notification(..) ,
IsNotification ,
toNotification ,
#if defined(ENABLE_OVERLOADING)
ResolveNotificationMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
NotificationAddButtonMethodInfo ,
#endif
notificationAddButton ,
#if defined(ENABLE_OVERLOADING)
NotificationAddButtonWithTargetMethodInfo,
#endif
notificationAddButtonWithTarget ,
notificationNew ,
#if defined(ENABLE_OVERLOADING)
NotificationSetBodyMethodInfo ,
#endif
notificationSetBody ,
#if defined(ENABLE_OVERLOADING)
NotificationSetDefaultActionMethodInfo ,
#endif
notificationSetDefaultAction ,
#if defined(ENABLE_OVERLOADING)
NotificationSetDefaultActionAndTargetMethodInfo,
#endif
notificationSetDefaultActionAndTarget ,
#if defined(ENABLE_OVERLOADING)
NotificationSetIconMethodInfo ,
#endif
notificationSetIcon ,
#if defined(ENABLE_OVERLOADING)
NotificationSetPriorityMethodInfo ,
#endif
notificationSetPriority ,
#if defined(ENABLE_OVERLOADING)
NotificationSetTitleMethodInfo ,
#endif
notificationSetTitle ,
#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.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.Icon as Gio.Icon
newtype Notification = Notification (SP.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)
instance SP.ManagedPtrNewtype Notification where
toManagedPtr :: Notification -> ManagedPtr Notification
toManagedPtr (Notification ManagedPtr Notification
p) = ManagedPtr Notification
p
foreign import ccall "g_notification_get_type"
c_g_notification_get_type :: IO B.Types.GType
instance B.Types.TypedObject Notification where
glibType :: IO GType
glibType = IO GType
c_g_notification_get_type
instance B.Types.GObject Notification
instance B.GValue.IsGValue Notification where
toGValue :: Notification -> IO GValue
toGValue 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 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
class (SP.GObject o, O.IsDescendantOf Notification o) => IsNotification o
instance (SP.GObject o, O.IsDescendantOf Notification o) => IsNotification o
instance O.HasParentTypes Notification
type instance O.ParentTypes Notification = '[GObject.Object.Object]
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, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Notification -> Notification
Notification
#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
foreign import ccall "g_notification_new" g_notification_new ::
CString ->
IO (Ptr Notification)
notificationNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m Notification
notificationNew :: Text -> m Notification
notificationNew 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 Text
"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
foreign import ccall "g_notification_add_button" g_notification_add_button ::
Ptr Notification ->
CString ->
CString ->
IO ()
notificationAddButton ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> T.Text
-> T.Text
-> m ()
notificationAddButton :: a -> Text -> Text -> m ()
notificationAddButton a
notification Text
label 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
foreign import ccall "g_notification_add_button_with_target_value" g_notification_add_button_with_target_value ::
Ptr Notification ->
CString ->
CString ->
Ptr GVariant ->
IO ()
notificationAddButtonWithTarget ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> T.Text
-> T.Text
-> Maybe (GVariant)
-> m ()
notificationAddButtonWithTarget :: a -> Text -> Text -> Maybe GVariant -> m ()
notificationAddButtonWithTarget a
notification Text
label Text
action 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
Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
Just 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
foreign import ccall "g_notification_set_body" g_notification_set_body ::
Ptr Notification ->
CString ->
IO ()
notificationSetBody ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> Maybe (T.Text)
-> m ()
notificationSetBody :: a -> Maybe Text -> m ()
notificationSetBody a
notification 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
Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just 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
foreign import ccall "g_notification_set_default_action" g_notification_set_default_action ::
Ptr Notification ->
CString ->
IO ()
notificationSetDefaultAction ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> T.Text
-> m ()
notificationSetDefaultAction :: a -> Text -> m ()
notificationSetDefaultAction a
notification 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
foreign import ccall "g_notification_set_default_action_and_target_value" g_notification_set_default_action_and_target_value ::
Ptr Notification ->
CString ->
Ptr GVariant ->
IO ()
notificationSetDefaultActionAndTarget ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> T.Text
-> Maybe (GVariant)
-> m ()
notificationSetDefaultActionAndTarget :: a -> Text -> Maybe GVariant -> m ()
notificationSetDefaultActionAndTarget a
notification Text
action 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
Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
Just 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
foreign import ccall "g_notification_set_icon" g_notification_set_icon ::
Ptr Notification ->
Ptr Gio.Icon.Icon ->
IO ()
notificationSetIcon ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a, Gio.Icon.IsIcon b) =>
a
-> b
-> m ()
notificationSetIcon :: a -> b -> m ()
notificationSetIcon a
notification 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
foreign import ccall "g_notification_set_priority" g_notification_set_priority ::
Ptr Notification ->
CUInt ->
IO ()
notificationSetPriority ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> Gio.Enums.NotificationPriority
-> m ()
notificationSetPriority :: a -> NotificationPriority -> m ()
notificationSetPriority a
notification 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
foreign import ccall "g_notification_set_title" g_notification_set_title ::
Ptr Notification ->
CString ->
IO ()
notificationSetTitle ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> T.Text
-> m ()
notificationSetTitle :: a -> Text -> m ()
notificationSetTitle a
notification 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
foreign import ccall "g_notification_set_urgent" g_notification_set_urgent ::
Ptr Notification ->
CInt ->
IO ()
{-# DEPRECATED notificationSetUrgent ["(Since version 2.42)","Since 2.42, this has been deprecated in favour of"," 'GI.Gio.Objects.Notification.notificationSetPriority'."] #-}
notificationSetUrgent ::
(B.CallStack.HasCallStack, MonadIO m, IsNotification a) =>
a
-> Bool
-> m ()
notificationSetUrgent :: a -> Bool -> m ()
notificationSetUrgent a
notification 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