libnotify-0.2.1: Bindings to libnotify library

Safe HaskellSafe
LanguageHaskell2010

Libnotify.C.Notify

Description

Low level bindings to libnotify

See also https://developer.gnome.org/libnotify/0.7/libnotify-notify.html. Haddocks here are mostly excerpts from there

Synopsis

Documentation

notify_init Source #

Arguments

:: String

Application name. Should not be empty!

-> IO Bool 

Initialize libnotify

This must be called before any other functions

notify_uninit :: IO () Source #

Uninitialize libnotify

notify_is_initted :: IO Bool Source #

Get whether libnotify is initialized or not

notify_get_app_name :: IO String Source #

Get the application name

Do not forget to call notify_init before calling this!

notify_set_app_name :: String -> IO () Source #

Set the application name

Do not forget to call notify_init before calling this!

notify_get_server_caps :: IO [String] Source #

Return server capabilities

Synchronously queries the server for its capabilities

>>> notify_get_server_caps
["actions","body","body-markup","body-hyperlinks","icon-static","x-canonical-private-icon-only"]

data ServerInfo Source #

Server information

Instances
Eq ServerInfo Source # 
Instance details

Defined in Libnotify.C.Notify

Data ServerInfo Source # 
Instance details

Defined in Libnotify.C.Notify

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ServerInfo -> c ServerInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ServerInfo #

toConstr :: ServerInfo -> Constr #

dataTypeOf :: ServerInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ServerInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ServerInfo) #

gmapT :: (forall b. Data b => b -> b) -> ServerInfo -> ServerInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ServerInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ServerInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> ServerInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ServerInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ServerInfo -> m ServerInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerInfo -> m ServerInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ServerInfo -> m ServerInfo #

Show ServerInfo Source # 
Instance details

Defined in Libnotify.C.Notify

Generic ServerInfo Source # 
Instance details

Defined in Libnotify.C.Notify

Associated Types

type Rep ServerInfo :: * -> * #

type Rep ServerInfo Source # 
Instance details

Defined in Libnotify.C.Notify

type Rep ServerInfo = D1 (MetaData "ServerInfo" "Libnotify.C.Notify" "libnotify-0.2.1-JWZmgYuBBe35aIczEgjA7J" False) (C1 (MetaCons "ServerInfo" PrefixI True) ((S1 (MetaSel (Just "serverName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "serverVendor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "serverVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "serverSpecVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))

notify_get_server_info :: IO (Maybe ServerInfo) Source #

Return server information

Synchronously queries the server for its information, specifically, the name, vendor, server version, and the version of the notifications specification that it is compliant with

>>> notify_get_server_info
Just (ServerInfo {name = "Xfce Notify Daemon", vendor = "Xfce", version = "0.2.4", specVersion = "0.9"})