libnotify-0.2: Bindings to libnotify library

Safe HaskellNone
LanguageHaskell2010

Libnotify

Contents

Description

High level interface to libnotify API

Synopsis

Notification API

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

Monoid (Mod a) Source # 

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 # 

Methods

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

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

Data Timeout Source # 

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 # 

Associated Types

type Rep Timeout :: * -> * #

Methods

from :: Timeout -> Rep Timeout x #

to :: Rep Timeout x -> Timeout #

type Rep Timeout Source # 
type Rep Timeout = D1 (MetaData "Timeout" "Libnotify.C.NotifyNotification" "libnotify-0.2-5AqadcxnGEHCrUwV0JiX8Z" False) ((:+:) (C1 (MetaCons "Default" PrefixI False) U1) ((:+:) (C1 (MetaCons "Custom" PrefixI False) (S1 (MetaSel (Nothing 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 # 

Methods

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

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

Data Urgency Source # 

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 # 
Show Urgency Source # 
Generic Urgency Source # 

Associated Types

type Rep Urgency :: * -> * #

Methods

from :: Urgency -> Rep Urgency x #

to :: Rep Urgency x -> Urgency #

type Rep Urgency Source # 
type Rep Urgency = D1 (MetaData "Urgency" "Libnotify.C.NotifyNotification" "libnotify-0.2-5AqadcxnGEHCrUwV0JiX8Z" 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 #

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"

Convenience re-exports

class Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ByteString 
Monoid IntSet 
Monoid [a] 

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

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

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

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

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

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

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

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

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

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

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

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

(Ord a, Bounded a) => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

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

(Ord a, Bounded a) => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

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

Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

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

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

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

Monoid (Endo a) 

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

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

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

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

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

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

Monoid (First a) 

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

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

Monoid (Last a) 

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

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

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

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

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

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

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

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

Monoid (Mod a) # 

Methods

mempty :: Mod a #

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

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

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

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

(Monoid a, Monoid b) => Monoid (a, b) 

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0