libnotify-0.2.1: Bindings to libnotify library

Safe HaskellNone
LanguageHaskell2010

Libnotify

Contents

Description

High level interface to libnotify API

Synopsis

Notification API

data Notification Source #

Notification object

Instances
Eq Notification Source # 
Instance details

Defined in Libnotify

Show Notification Source # 
Instance details

Defined in Libnotify

display :: Mod Notification -> IO Notification Source #

Display notification

>>> token <- display (summary "Greeting" <> body "Hello world!" <> icon "face-smile-big")

You can reuse notification tokens:

>>> display_ (reuse token <> body "Hey!")

display_ :: Mod Notification -> IO () Source #

Display and discard notification token

>>> display_ (summary "Greeting" <> body "Hello world!" <> icon "face-smile-big")

close :: Notification -> IO () Source #

Close notification

Modifiers

data Mod a Source #

A notification modifier

Instances
Semigroup (Mod a) Source # 
Instance details

Defined in Libnotify

Methods

(<>) :: Mod a -> Mod a -> Mod a #

sconcat :: NonEmpty (Mod a) -> Mod a #

stimes :: Integral b => b -> Mod a -> Mod a #

Monoid (Mod a) Source # 
Instance details

Defined in Libnotify

Methods

mempty :: Mod a #

mappend :: Mod a -> Mod a -> Mod a #

mconcat :: [Mod a] -> Mod a #

summary :: String -> Mod Notification Source #

Set notification summary

>>> display_ (summary "Hello!")

body :: String -> Mod Notification Source #

Set notification body

>>> display_ (body "Hello world!")

icon :: String -> Mod Notification Source #

Set notification icon

>>> display_ (icon "face-smile")

The argument is either icon name or file name

timeout :: Timeout -> Mod Notification Source #

Set notification timeout

data Timeout Source #

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 # 
Instance details

Defined in Libnotify.C.NotifyNotification

Methods

(==) :: Timeout -> Timeout -> Bool #

(/=) :: Timeout -> Timeout -> Bool #

Data Timeout Source # 
Instance details

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 # 
Instance details

Defined in Libnotify.C.NotifyNotification

Generic Timeout Source # 
Instance details

Defined in Libnotify.C.NotifyNotification

Associated Types

type Rep Timeout :: * -> * #

Methods

from :: Timeout -> Rep Timeout x #

to :: Rep Timeout x -> Timeout #

type Rep Timeout Source # 
Instance details

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 :: * -> *)))

category :: String -> Mod Notification Source #

Set notification category

urgency :: Urgency -> Mod Notification Source #

Set notification urgency

data Urgency Source #

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 # 
Instance details

Defined in Libnotify.C.NotifyNotification

Methods

(==) :: Urgency -> Urgency -> Bool #

(/=) :: Urgency -> Urgency -> Bool #

Data Urgency Source # 
Instance details

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 # 
Instance details

Defined in Libnotify.C.NotifyNotification

Show Urgency Source # 
Instance details

Defined in Libnotify.C.NotifyNotification

Generic Urgency Source # 
Instance details

Defined in Libnotify.C.NotifyNotification

Associated Types

type Rep Urgency :: * -> * #

Methods

from :: Urgency -> Rep Urgency x #

to :: Rep Urgency x -> Urgency #

type Rep Urgency Source # 
Instance details

Defined in Libnotify.C.NotifyNotification

type Rep Urgency = D1 (MetaData "Urgency" "Libnotify.C.NotifyNotification" "libnotify-0.2.1-JWZmgYuBBe35aIczEgjA7J" False) (C1 (MetaCons "Low" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Normal" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Critical" PrefixI False) (U1 :: * -> *)))

image :: Pixbuf -> Mod Notification Source #

Set notification image

class Hint v where Source #

Add a hint to notification

It's perfectly OK to add multiple hints to a single notification

Minimal complete definition

hint

Methods

hint :: String -> v -> Mod Notification Source #

Instances
Hint Double Source # 
Instance details

Defined in Libnotify

Hint Int32 Source # 
Instance details

Defined in Libnotify

Hint Word8 Source # 
Instance details

Defined in Libnotify

Hint String Source # 
Instance details

Defined in Libnotify

Hint ByteString Source # 
Instance details

Defined in Libnotify

nohints :: Mod Notification Source #

Remove all hints from the notification

action Source #

Arguments

:: String

Name

-> String

Button label

-> (Notification -> String -> IO a)

Callback

-> Mod Notification 

Add an action to notification

It's perfectly OK to add multiple actions to a single notification

>>> display_ (action "hello" "Hello world!" (\_ _ -> return ()))

noactions :: Mod Notification Source #

Remove all actions from the notification

>>> let callback _ _ = return ()
>>> display_ (summary "No hello for you!" <> action "hello" "Hello world!" callback <> noactions)

appName :: String -> Mod Notification Source #

Set the application name.

reuse :: Notification -> Mod Notification Source #

Reuse existing notification token, instead of creating a new one

If you try to reuse multiple tokens, the last one wins, e.g.

>>> foo <- display (body "foo")
>>> bar <- display (body "bar")
>>> display_ (base foo <> base bar)

will show only "bar"