module Libnotify.C.NotifyNotification
( NotifyNotification
, notify_notification_new
, notify_notification_update
, notify_notification_show
, notify_notification_set_app_name
, Timeout(..)
, notify_notification_set_timeout
, notify_notification_set_category
, Urgency(..)
, notify_notification_set_urgency
, notify_notification_set_icon_from_pixbuf
, notify_notification_set_image_from_pixbuf
, notify_notification_set_hint_int32
, notify_notification_set_hint_uint32
, notify_notification_set_hint_double
, notify_notification_set_hint_string
, notify_notification_set_hint_byte
, notify_notification_set_hint_byte_array
, notify_notification_clear_hints
, notify_notification_add_action
, notify_notification_clear_actions
, notify_notification_close
, notify_notification_get_closed_reason
) where
import Control.Exception (throwIO)
import Data.Data (Typeable, Data)
import GHC.Generics (Generic)
import Foreign
import Foreign.C
import Graphics.UI.Gtk.Gdk.Pixbuf (Pixbuf)
import System.Glib.GError (GError)
import System.Glib.GObject (GObjectClass(..), GObject(..), unGObject, wrapNewGObject, objectUnref)
import Unsafe.Coerce (unsafeCoerce)
import qualified Data.ByteString as BS
newtype NotifyNotification = NotifyNotification (ForeignPtr NotifyNotification)
deriving (Show, Eq)
instance GObjectClass NotifyNotification where
toGObject (NotifyNotification p) = GObject (castForeignPtr p)
unsafeCastGObject = NotifyNotification . castForeignPtr . unGObject
notify_notification_new
:: String
-> String
-> String
-> IO NotifyNotification
notify_notification_new summary body icon =
withCString summary $ \p_summary ->
withCString body $ \p_body ->
withCString icon $ \p_icon ->
wrapNewGObject (NotifyNotification, objectUnref) $
notify_notification_new_c p_summary p_body p_icon
notify_notification_update
:: NotifyNotification
-> String
-> String
-> String
-> IO Bool
notify_notification_update (NotifyNotification notify) summary body icon =
withCString summary $ \p_summary ->
withCString body $ \p_body ->
withCString icon $ \p_icon ->
withForeignPtr notify $ \p_notify ->
notify_notification_update_c p_notify p_summary p_body p_icon
notify_notification_show :: NotifyNotification -> IO Bool
notify_notification_show (NotifyNotification notify) =
withForeignPtr notify $ \p_notify ->
alloca $ \pp_error -> do
poke pp_error nullPtr
result <- notify_notification_show_c p_notify pp_error
p_error <- peek pp_error
if p_error == nullPtr
then
return result
else do
gerror <- peek p_error
g_error_free p_error
throwIO gerror
notify_notification_set_app_name :: NotifyNotification -> String -> IO ()
notify_notification_set_app_name (NotifyNotification notify) name =
withForeignPtr notify $ \p_notify ->
withCString name $ \p_name ->
notify_notification_set_app_name_c p_notify p_name
data Timeout =
Default
| Custom Int
| Infinite
deriving (Show, Eq, Typeable, Data, Generic)
notify_notification_set_timeout :: NotifyNotification -> Timeout -> IO ()
notify_notification_set_timeout (NotifyNotification notify) timeout =
withForeignPtr notify $ \p_notify ->
notify_notification_set_timeout_c p_notify $ case timeout of
Default -> 1
Infinite -> 0
Custom t -> fromIntegral t
notify_notification_set_category :: NotifyNotification -> String -> IO ()
notify_notification_set_category (NotifyNotification notify) category =
withForeignPtr notify $ \p_notify ->
withCString category $ \p_category ->
notify_notification_set_category_c p_notify p_category
data Urgency =
Low
| Normal
| Critical
deriving (Show, Eq, Ord, Typeable, Data, Generic)
notify_notification_set_urgency :: NotifyNotification -> Urgency -> IO ()
notify_notification_set_urgency (NotifyNotification notify) urgency =
withForeignPtr notify $ \p_notify ->
notify_notification_set_urgency_c p_notify $ case urgency of
Low -> 0
Normal -> 1
Critical -> 2
notify_notification_set_icon_from_pixbuf :: NotifyNotification -> Pixbuf -> IO ()
notify_notification_set_icon_from_pixbuf (NotifyNotification notify) pixbuf =
withForeignPtr notify $ \p_notify ->
withForeignPtr (unsafeCoerce pixbuf) $ \p_pixbuf ->
notify_notification_set_icon_from_pixbuf_c p_notify p_pixbuf
notify_notification_set_image_from_pixbuf :: NotifyNotification -> Pixbuf -> IO ()
notify_notification_set_image_from_pixbuf (NotifyNotification notify) pixbuf =
withForeignPtr notify $ \p_notify ->
withForeignPtr (unsafeCoerce pixbuf) $ \p_pixbuf ->
notify_notification_set_image_from_pixbuf_c p_notify p_pixbuf
notify_notification_set_hint_int32 :: NotifyNotification -> String -> Int32 -> IO ()
notify_notification_set_hint_int32 (NotifyNotification notify) key value =
withForeignPtr notify $ \p_notify ->
withCString key $ \p_key ->
notify_notification_set_hint_int32_c p_notify p_key (fromIntegral value)
notify_notification_set_hint_uint32 :: NotifyNotification -> String -> Word32 -> IO ()
notify_notification_set_hint_uint32 (NotifyNotification notify) key value =
withForeignPtr notify $ \p_notify ->
withCString key $ \p_key ->
notify_notification_set_hint_uint32_c p_notify p_key (fromIntegral value)
notify_notification_set_hint_double :: NotifyNotification -> String -> Double -> IO ()
notify_notification_set_hint_double (NotifyNotification notify) key value =
withForeignPtr notify $ \p_notify ->
withCString key $ \p_key ->
notify_notification_set_hint_double_c p_notify p_key (realToFrac value)
notify_notification_set_hint_string :: NotifyNotification -> String -> String -> IO ()
notify_notification_set_hint_string (NotifyNotification notify) key value =
withForeignPtr notify $ \p_notify ->
withCString key $ \p_key ->
withCString value $ \p_value ->
notify_notification_set_hint_string_c p_notify p_key p_value
notify_notification_set_hint_byte :: NotifyNotification -> String -> Word8 -> IO ()
notify_notification_set_hint_byte (NotifyNotification notify) key value =
withForeignPtr notify $ \p_notify ->
withCString key $ \p_key ->
notify_notification_set_hint_byte_c p_notify p_key (fromIntegral value)
notify_notification_set_hint_byte_array :: NotifyNotification -> String -> BS.ByteString -> IO ()
notify_notification_set_hint_byte_array (NotifyNotification notify) key value =
withForeignPtr notify $ \p_notify ->
withCString key $ \p_key ->
withArrayLen (BS.foldr' step [] value) $ \len p_bs ->
notify_notification_set_hint_byte_array_c p_notify p_key p_bs (fromIntegral len)
where
step x xs = fromIntegral x:xs
notify_notification_clear_hints :: NotifyNotification -> IO ()
notify_notification_clear_hints (NotifyNotification notify) =
withForeignPtr notify notify_notification_clear_hints_c
type NotifyActionCallback a = Ptr NotifyNotification -> CString -> Ptr a -> IO ()
notify_notification_add_action
:: NotifyNotification
-> String
-> String
-> (NotifyNotification -> String -> IO ())
-> IO ()
notify_notification_add_action (NotifyNotification notify) action label callback =
withForeignPtr notify $ \p_notify ->
withCString action $ \p_action ->
withCString label $ \p_label -> do
p_callback <- wrapActionCallback $ \p_notify' p_action' _ -> do
action' <- peekCString p_action'
fp_notify' <- newForeignPtr_ p_notify'
callback (NotifyNotification fp_notify') action'
notify_notification_add_action_c p_notify p_action p_label p_callback nullPtr nullFunPtr
notify_notification_clear_actions :: NotifyNotification -> IO ()
notify_notification_clear_actions (NotifyNotification notify) =
withForeignPtr notify notify_notification_clear_actions_c
notify_notification_close :: NotifyNotification -> IO Bool
notify_notification_close (NotifyNotification notify) =
withForeignPtr notify $ \p_notify ->
alloca $ \pp_error -> do
poke pp_error nullPtr
result <- notify_notification_close_c p_notify pp_error
p_error <- peek pp_error
if p_error == nullPtr
then
return result
else do
gerror <- peek p_error
g_error_free p_error
throwIO gerror
notify_notification_get_closed_reason :: NotifyNotification -> IO Int
notify_notification_get_closed_reason (NotifyNotification notify) =
withForeignPtr notify notify_notification_get_closed_reason_c
foreign import ccall safe "libnotify/notify.h notify_notification_new"
notify_notification_new_c :: CString -> CString -> CString -> IO (Ptr NotifyNotification)
foreign import ccall safe "libnotify/notify.h notify_notification_update"
notify_notification_update_c :: Ptr NotifyNotification -> CString -> CString -> CString -> IO Bool
foreign import ccall safe "libnotify/notify.h notify_notification_show"
notify_notification_show_c :: Ptr NotifyNotification -> Ptr (Ptr GError) -> IO Bool
foreign import ccall safe "libnotify/notify.h notify_notification_set_app_name"
notify_notification_set_app_name_c :: Ptr NotifyNotification -> CString -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_timeout"
notify_notification_set_timeout_c :: Ptr NotifyNotification -> CInt -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_category"
notify_notification_set_category_c :: Ptr NotifyNotification -> CString -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_urgency"
notify_notification_set_urgency_c :: Ptr NotifyNotification -> CInt -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_icon_from_pixbuf"
notify_notification_set_icon_from_pixbuf_c :: Ptr NotifyNotification -> Ptr Pixbuf -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_image_from_pixbuf"
notify_notification_set_image_from_pixbuf_c :: Ptr NotifyNotification -> Ptr Pixbuf -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_hint_int32"
notify_notification_set_hint_int32_c :: Ptr NotifyNotification -> CString -> CInt -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_hint_uint32"
notify_notification_set_hint_uint32_c :: Ptr NotifyNotification -> CString -> CUInt -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_hint_double"
notify_notification_set_hint_double_c :: Ptr NotifyNotification -> CString -> CDouble -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_hint_string"
notify_notification_set_hint_string_c :: Ptr NotifyNotification -> CString -> CString -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_hint_byte"
notify_notification_set_hint_byte_c :: Ptr NotifyNotification -> CString -> CUChar -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_set_hint_byte_array"
notify_notification_set_hint_byte_array_c :: Ptr NotifyNotification -> CString -> Ptr CUChar -> CSize -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_clear_hints"
notify_notification_clear_hints_c :: Ptr NotifyNotification -> IO ()
foreign import ccall safe "wrapper"
wrapActionCallback :: NotifyActionCallback a -> IO (FunPtr (NotifyActionCallback a))
foreign import ccall safe "libnotify/notify.h notify_notification_add_action"
notify_notification_add_action_c
:: Ptr NotifyNotification
-> CString
-> CString
-> FunPtr (NotifyActionCallback a)
-> Ptr a
-> FunPtr (Ptr a -> IO ())
-> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_clear_actions"
notify_notification_clear_actions_c :: Ptr NotifyNotification -> IO ()
foreign import ccall safe "libnotify/notify.h notify_notification_close"
notify_notification_close_c :: Ptr NotifyNotification -> Ptr (Ptr GError) -> IO Bool
foreign import ccall safe "libnotify/notify.h notify_notification_get_closed_reason"
notify_notification_get_closed_reason_c :: Ptr NotifyNotification -> IO Int
foreign import ccall safe "glib-object.h g_error_free"
g_error_free :: Ptr GError -> IO ()