Safe Haskell | None |
---|---|
Language | Haskell2010 |
Libnotify.C.NotifyNotification
Description
Low level bindings to libnotify
See also https://developer.gnome.org/libnotify/0.7/NotifyNotification.html. Haddocks here are mostly excerpts from there
Synopsis
- data NotifyNotification
- notify_notification_new :: String -> String -> String -> IO NotifyNotification
- notify_notification_update :: NotifyNotification -> String -> String -> String -> IO Bool
- notify_notification_show :: NotifyNotification -> IO Bool
- notify_notification_set_app_name :: NotifyNotification -> String -> IO ()
- data Timeout
- notify_notification_set_timeout :: NotifyNotification -> Timeout -> IO ()
- notify_notification_set_category :: NotifyNotification -> String -> IO ()
- data Urgency
- notify_notification_set_urgency :: NotifyNotification -> Urgency -> IO ()
- notify_notification_set_icon_from_pixbuf :: NotifyNotification -> Pixbuf -> IO ()
- notify_notification_set_image_from_pixbuf :: NotifyNotification -> Pixbuf -> IO ()
- notify_notification_set_hint_int32 :: NotifyNotification -> String -> Int32 -> IO ()
- notify_notification_set_hint_uint32 :: NotifyNotification -> String -> Word32 -> IO ()
- notify_notification_set_hint_double :: NotifyNotification -> String -> Double -> IO ()
- notify_notification_set_hint_string :: NotifyNotification -> String -> String -> IO ()
- notify_notification_set_hint_byte :: NotifyNotification -> String -> Word8 -> IO ()
- notify_notification_set_hint_byte_array :: NotifyNotification -> String -> ByteString -> IO ()
- notify_notification_clear_hints :: NotifyNotification -> IO ()
- notify_notification_add_action :: NotifyNotification -> String -> String -> (NotifyNotification -> String -> IO ()) -> IO ()
- notify_notification_clear_actions :: NotifyNotification -> IO ()
- notify_notification_close :: NotifyNotification -> IO Bool
- notify_notification_get_closed_reason :: NotifyNotification -> IO Int
Documentation
data NotifyNotification Source #
An opaque notification token
Instances
Eq NotifyNotification Source # | |
Defined in Libnotify.C.NotifyNotification Methods (==) :: NotifyNotification -> NotifyNotification -> Bool # (/=) :: NotifyNotification -> NotifyNotification -> Bool # | |
Show NotifyNotification Source # | |
Defined in Libnotify.C.NotifyNotification Methods showsPrec :: Int -> NotifyNotification -> ShowS # show :: NotifyNotification -> String # showList :: [NotifyNotification] -> ShowS # | |
GObjectClass NotifyNotification Source # | |
Defined in Libnotify.C.NotifyNotification Methods toGObject :: NotifyNotification -> GObject # |
notify_notification_new Source #
Arguments
:: String | Summary |
-> String | Body |
-> String | Icon (icon name or file name) |
-> IO NotifyNotification |
Create a new NotifyNotification
Only summary is required
notify_notification_update Source #
Arguments
:: NotifyNotification | |
-> String | Summary |
-> String | Body |
-> String | Icon (icon name or file name) |
-> IO Bool |
Update the notification text and icon
notify_notification_show :: NotifyNotification -> IO Bool Source #
Display the notification on the screen
notify_notification_set_app_name :: NotifyNotification -> String -> IO () Source #
Set the application name for the notification
Used to override an application name for a specific notification.
See also notify_init
and notify_set_app_name
Timeout after which notification is closed
Constructors
Default | Default server timeout |
Custom Int | User defined timeout (in milliseconds) |
Infinite | Notification will never expire |
Instances
Eq Timeout Source # | |
Data Timeout Source # | |
Defined in Libnotify.C.NotifyNotification Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Timeout -> c Timeout # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Timeout # toConstr :: Timeout -> Constr # dataTypeOf :: Timeout -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Timeout) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Timeout) # gmapT :: (forall b. Data b => b -> b) -> Timeout -> Timeout # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Timeout -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Timeout -> r # gmapQ :: (forall d. Data d => d -> u) -> Timeout -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Timeout -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Timeout -> m Timeout # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Timeout -> m Timeout # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Timeout -> m Timeout # | |
Show Timeout Source # | |
Generic Timeout Source # | |
type Rep Timeout Source # | |
Defined in Libnotify.C.NotifyNotification type Rep Timeout = D1 (MetaData "Timeout" "Libnotify.C.NotifyNotification" "libnotify-0.2.1-JWZmgYuBBe35aIczEgjA7J" False) (C1 (MetaCons "Default" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Custom" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "Infinite" PrefixI False) (U1 :: * -> *))) |
notify_notification_set_timeout :: NotifyNotification -> Timeout -> IO () Source #
Set the timeout of the notification
notify_notification_set_category :: NotifyNotification -> String -> IO () Source #
Set the category of the notification
The urgency level of the notification
Constructors
Low | Low urgency. Used for unimportant notifications |
Normal | Normal urgency. Used for most standard notifications |
Critical | Critical urgency. Used for very important notifications |
Instances
Eq Urgency Source # | |
Data Urgency Source # | |
Defined in Libnotify.C.NotifyNotification Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Urgency -> c Urgency # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Urgency # toConstr :: Urgency -> Constr # dataTypeOf :: Urgency -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Urgency) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Urgency) # gmapT :: (forall b. Data b => b -> b) -> Urgency -> Urgency # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Urgency -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Urgency -> r # gmapQ :: (forall d. Data d => d -> u) -> Urgency -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Urgency -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Urgency -> m Urgency # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Urgency -> m Urgency # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Urgency -> m Urgency # | |
Ord Urgency Source # | |
Defined in Libnotify.C.NotifyNotification | |
Show Urgency Source # | |
Generic Urgency Source # | |
type Rep Urgency Source # | |
Defined in Libnotify.C.NotifyNotification |
notify_notification_set_urgency :: NotifyNotification -> Urgency -> IO () Source #
Set the urgency level of the notification
notify_notification_set_icon_from_pixbuf :: NotifyNotification -> Pixbuf -> IO () Source #
Deprecated: Use notify_notification_set_image_from_pixbuf instead
Set the icon in the notification from the Pixbuf
notify_notification_set_image_from_pixbuf :: NotifyNotification -> Pixbuf -> IO () Source #
Set the icon in the notification from the Pixbuf
notify_notification_set_hint_int32 :: NotifyNotification -> String -> Int32 -> IO () Source #
Set a hint with a 32-bit integer value
notify_notification_set_hint_uint32 :: NotifyNotification -> String -> Word32 -> IO () Source #
Set a hint with an unsigned 32-bit integer value
notify_notification_set_hint_double :: NotifyNotification -> String -> Double -> IO () Source #
Set a hint with a double value
notify_notification_set_hint_string :: NotifyNotification -> String -> String -> IO () Source #
Set a hint with a string value
notify_notification_set_hint_byte :: NotifyNotification -> String -> Word8 -> IO () Source #
Set a hint with a byte value
notify_notification_set_hint_byte_array :: NotifyNotification -> String -> ByteString -> IO () Source #
Set a hint with a byte array value
notify_notification_clear_hints :: NotifyNotification -> IO () Source #
Clear all hints
notify_notification_add_action :: NotifyNotification -> String -> String -> (NotifyNotification -> String -> IO ()) -> IO () Source #
Add an action to a notification. When the action is invoked, the specified callback function will be called
For the callback to be *actually* invoked, some kind of magical glib mainLoop
thing
should be running
notify_notification_clear_actions :: NotifyNotification -> IO () Source #
Clear all actions
notify_notification_close :: NotifyNotification -> IO Bool Source #
Hide the notification from the screen
notify_notification_get_closed_reason :: NotifyNotification -> IO Int Source #
Get the closed reason code for the notification