module Libnotify.C.Notify
( notify_init
, notify_uninit
, notify_is_initted
, notify_get_app_name
, notify_set_app_name
, notify_get_server_caps
, ServerInfo(..)
, notify_get_server_info
) where
import Data.Data (Typeable, Data)
import GHC.Generics (Generic)
import Foreign
import Foreign.C
import System.Glib.GList (GList, readGList)
notify_init
:: String
-> IO Bool
notify_init name = withCString name notify_init_c
notify_uninit :: IO ()
notify_uninit = notify_uninit_c
notify_is_initted :: IO Bool
notify_is_initted = notify_is_initted_c
notify_get_app_name :: IO String
notify_get_app_name = notify_get_app_name_c >>= peekCString
notify_set_app_name :: String -> IO ()
notify_set_app_name name = withCString name notify_set_app_name_c
notify_get_server_caps :: IO [String]
notify_get_server_caps = do
glist <- notify_get_server_caps_c
p_caps <- readGList glist
caps <- mapM peekCString p_caps
mapM_ free p_caps
g_list_free glist
return caps
data ServerInfo = ServerInfo
{ name :: String
, vendor :: String
, version :: String
, specVersion :: String
} deriving (Show, Eq, Typeable, Data, Generic)
notify_get_server_info :: IO (Maybe ServerInfo)
notify_get_server_info =
alloca $ \p_name ->
alloca $ \p_vendor ->
alloca $ \p_version ->
alloca $ \p_specVersion -> do
ret <- notify_get_server_info_c p_name p_vendor p_version p_specVersion
if ret
then do
name <- peekCString =<< peek p_name
vendor <- peekCString =<< peek p_vendor
version <- peekCString =<< peek p_version
specVersion <- peekCString =<< peek p_specVersion
return $ Just ServerInfo { name, vendor, version, specVersion }
else
return Nothing
foreign import ccall safe "libnotify/notify.h notify_init"
notify_init_c :: CString -> IO Bool
foreign import ccall safe "libnotify/notify.h notify_uninit"
notify_uninit_c :: IO ()
foreign import ccall safe "libnotify/notify.h notify_is_initted"
notify_is_initted_c :: IO Bool
foreign import ccall safe "libnotify/notify.h notify_get_app_name"
notify_get_app_name_c :: IO CString
foreign import ccall safe "libnotify/notify.h notify_set_app_name"
notify_set_app_name_c :: CString -> IO ()
foreign import ccall safe "libnotify/notify.h notify_get_server_caps"
notify_get_server_caps_c :: IO GList
foreign import ccall safe "libnotify/notify.h notify_get_server_info"
notify_get_server_info_c :: Ptr CString -> Ptr CString -> Ptr CString -> Ptr CString -> IO Bool
foreign import ccall safe "g_list_free"
g_list_free :: GList -> IO ()