-- Generated code. {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# LANGUAGE ForeignFunctionInterface, ConstraintKinds, TypeFamilies, MultiParamTypeClasses, KindSignatures, FlexibleInstances, UndecidableInstances, DataKinds, OverloadedStrings, NegativeLiterals, FlexibleContexts #-} module GI.Notify where import Prelude () import Data.GI.Base.ShortPrelude import Data.Char import Data.Int import Data.Word import qualified Data.ByteString.Char8 as B import Data.ByteString.Char8 (ByteString) import qualified Data.Map as Map import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr) import Foreign.Storable (peek, poke, sizeOf) import Control.Applicative ((<$>)) import Control.Exception (onException) import Control.Monad.IO.Class import qualified Data.Text as T import Data.GI.Base.Attributes hiding (get, set) import Data.GI.Base.BasicTypes import Data.GI.Base.BasicConversions import Data.GI.Base.Closure import Data.GI.Base.GError import Data.GI.Base.GHashTable import Data.GI.Base.GParamSpec import Data.GI.Base.GVariant import Data.GI.Base.GValue import Data.GI.Base.ManagedPtr import Data.GI.Base.Overloading import Data.GI.Base.Properties hiding (new) import Data.GI.Base.Signals (SignalConnectMode(..), connectSignalFunPtr, SignalHandlerId) import Data.GI.Base.Utils import qualified GI.GLib as GLib import qualified GI.GLibAttributes as GLibA import qualified GI.GObject as GObject import qualified GI.GObjectAttributes as GObjectA import qualified GI.GdkPixbuf as GdkPixbuf import qualified GI.GdkPixbufAttributes as GdkPixbufA -- callback ActionCallback actionCallbackClosure :: ActionCallback -> IO Closure actionCallbackClosure cb = newCClosure =<< mkActionCallback wrapped where wrapped = actionCallbackWrapper Nothing cb type ActionCallbackC = Ptr Notification -> CString -> Ptr () -> IO () foreign import ccall "wrapper" mkActionCallback :: ActionCallbackC -> IO (FunPtr ActionCallbackC) type ActionCallback = Notification -> T.Text -> IO () noActionCallback :: Maybe ActionCallback noActionCallback = Nothing actionCallbackWrapper :: Maybe (Ptr (FunPtr (ActionCallbackC))) -> ActionCallback -> Ptr Notification -> CString -> Ptr () -> IO () actionCallbackWrapper funptrptr _cb notification action _ = do notification' <- (newObject Notification) notification action' <- cstringToText action _cb notification' action' maybeReleaseFunPtr funptrptr -- object Notification newtype Notification = Notification (ForeignPtr Notification) noNotification :: Maybe Notification noNotification = Nothing foreign import ccall "notify_notification_get_type" c_notify_notification_get_type :: IO GType type instance ParentTypes Notification = '[GObject.Object] instance GObject Notification where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_notify_notification_get_type class GObject o => NotificationK o instance (GObject o, IsDescendantOf Notification o) => NotificationK o toNotification :: NotificationK o => o -> IO Notification toNotification = unsafeCastTo Notification -- method Notification::new -- method type : Constructor -- Args : [Arg {argName = "summary", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "summary", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Notify" "Notification" -- throws : False -- Skip return : False foreign import ccall "notify_notification_new" notify_notification_new :: CString -> -- summary : TBasicType TUTF8 CString -> -- body : TBasicType TUTF8 CString -> -- icon : TBasicType TUTF8 IO (Ptr Notification) notificationNew :: (MonadIO m) => T.Text -> -- summary Maybe (T.Text) -> -- body Maybe (T.Text) -> -- icon m Notification notificationNew summary body icon = liftIO $ do summary' <- textToCString summary maybeBody <- case body of Nothing -> return nullPtr Just jBody -> do jBody' <- textToCString jBody return jBody' maybeIcon <- case icon of Nothing -> return nullPtr Just jIcon -> do jIcon' <- textToCString jIcon return jIcon' result <- notify_notification_new summary' maybeBody maybeIcon result' <- (wrapObject Notification) result freeMem summary' freeMem maybeBody freeMem maybeIcon return result' -- method Notification::add_action -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "action", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Notify" "ActionCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 4, argDestroy = 5, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "free_func", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "action", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Notify" "ActionCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 4, argDestroy = 5, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_add_action" notify_notification_add_action :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- action : TBasicType TUTF8 CString -> -- label : TBasicType TUTF8 FunPtr ActionCallbackC -> -- callback : TInterface "Notify" "ActionCallback" Ptr () -> -- user_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- free_func : TInterface "GLib" "DestroyNotify" IO () notificationAddAction :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- action T.Text -> -- label ActionCallback -> -- callback m () notificationAddAction _obj action label callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj action' <- textToCString action label' <- textToCString label callback' <- mkActionCallback (actionCallbackWrapper Nothing callback) let user_data = castFunPtrToPtr callback' let free_func = safeFreeFunPtrPtr notify_notification_add_action _obj' action' label' callback' user_data free_func touchManagedPtr _obj freeMem action' freeMem label' return () -- method Notification::clear_actions -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_clear_actions" notify_notification_clear_actions :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" IO () notificationClearActions :: (MonadIO m, NotificationK a) => a -> -- _obj m () notificationClearActions _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj notify_notification_clear_actions _obj' touchManagedPtr _obj return () -- method Notification::clear_hints -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_clear_hints" notify_notification_clear_hints :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" IO () notificationClearHints :: (MonadIO m, NotificationK a) => a -> -- _obj m () notificationClearHints _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj notify_notification_clear_hints _obj' touchManagedPtr _obj return () -- method Notification::close -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "notify_notification_close" notify_notification_close :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" Ptr (Ptr GError) -> -- error IO CInt notificationClose :: (MonadIO m, NotificationK a) => a -> -- _obj m () notificationClose _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj onException (do _ <- propagateGError $ notify_notification_close _obj' touchManagedPtr _obj return () ) (do return () ) -- method Notification::get_closed_reason -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "notify_notification_get_closed_reason" notify_notification_get_closed_reason :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" IO Int32 notificationGetClosedReason :: (MonadIO m, NotificationK a) => a -> -- _obj m Int32 notificationGetClosedReason _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- notify_notification_get_closed_reason _obj' touchManagedPtr _obj return result -- method Notification::set_app_name -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "app_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "app_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_app_name" notify_notification_set_app_name :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- app_name : TBasicType TUTF8 IO () notificationSetAppName :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- app_name m () notificationSetAppName _obj app_name = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj app_name' <- textToCString app_name notify_notification_set_app_name _obj' app_name' touchManagedPtr _obj freeMem app_name' return () -- method Notification::set_category -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "category", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "category", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_category" notify_notification_set_category :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- category : TBasicType TUTF8 IO () notificationSetCategory :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- category m () notificationSetCategory _obj category = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj category' <- textToCString category notify_notification_set_category _obj' category' touchManagedPtr _obj freeMem category' return () -- method Notification::set_hint -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TVariant, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TVariant, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_hint" notify_notification_set_hint :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- key : TBasicType TUTF8 Ptr GVariant -> -- value : TVariant IO () notificationSetHint :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- key Maybe (GVariant) -> -- value m () notificationSetHint _obj key value = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj key' <- textToCString key maybeValue <- case value of Nothing -> return nullPtr Just jValue -> do let jValue' = unsafeManagedPtrGetPtr jValue return jValue' notify_notification_set_hint _obj' key' maybeValue touchManagedPtr _obj freeMem key' return () -- method Notification::set_hint_byte -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_hint_byte" notify_notification_set_hint_byte :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- key : TBasicType TUTF8 Word8 -> -- value : TBasicType TUInt8 IO () {-# DEPRECATED notificationSetHintByte ["(Since version 0.6.)","Use notify_notification_set_hint() instead"]#-} notificationSetHintByte :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- key Word8 -> -- value m () notificationSetHintByte _obj key value = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj key' <- textToCString key notify_notification_set_hint_byte _obj' key' value touchManagedPtr _obj freeMem key' return () -- method Notification::set_hint_byte_array -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_hint_byte_array" notify_notification_set_hint_byte_array :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- key : TBasicType TUTF8 Word8 -> -- value : TBasicType TUInt8 Word64 -> -- len : TBasicType TUInt64 IO () {-# DEPRECATED notificationSetHintByteArray ["(Since version 0.6.)","Use notify_notification_set_hint() instead"]#-} notificationSetHintByteArray :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- key Word8 -> -- value Word64 -> -- len m () notificationSetHintByteArray _obj key value len = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj key' <- textToCString key notify_notification_set_hint_byte_array _obj' key' value len touchManagedPtr _obj freeMem key' return () -- method Notification::set_hint_double -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_hint_double" notify_notification_set_hint_double :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- key : TBasicType TUTF8 CDouble -> -- value : TBasicType TDouble IO () {-# DEPRECATED notificationSetHintDouble ["(Since version 0.6.)","Use notify_notification_set_hint() instead"]#-} notificationSetHintDouble :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- key Double -> -- value m () notificationSetHintDouble _obj key value = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj key' <- textToCString key let value' = realToFrac value notify_notification_set_hint_double _obj' key' value' touchManagedPtr _obj freeMem key' return () -- method Notification::set_hint_int32 -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_hint_int32" notify_notification_set_hint_int32 :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- key : TBasicType TUTF8 Int32 -> -- value : TBasicType TInt32 IO () {-# DEPRECATED notificationSetHintInt32 ["(Since version 0.6.)","Use notify_notification_set_hint() instead"]#-} notificationSetHintInt32 :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- key Int32 -> -- value m () notificationSetHintInt32 _obj key value = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj key' <- textToCString key notify_notification_set_hint_int32 _obj' key' value touchManagedPtr _obj freeMem key' return () -- method Notification::set_hint_string -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_hint_string" notify_notification_set_hint_string :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- key : TBasicType TUTF8 CString -> -- value : TBasicType TUTF8 IO () {-# DEPRECATED notificationSetHintString ["(Since version 0.6.)","Use notify_notification_set_hint() instead"]#-} notificationSetHintString :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- key T.Text -> -- value m () notificationSetHintString _obj key value = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj key' <- textToCString key value' <- textToCString value notify_notification_set_hint_string _obj' key' value' touchManagedPtr _obj freeMem key' freeMem value' return () -- method Notification::set_hint_uint32 -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_hint_uint32" notify_notification_set_hint_uint32 :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- key : TBasicType TUTF8 Word32 -> -- value : TBasicType TUInt32 IO () {-# DEPRECATED notificationSetHintUint32 ["(Since version 0.6.)","Use notify_notification_set_hint() instead"]#-} notificationSetHintUint32 :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- key Word32 -> -- value m () notificationSetHintUint32 _obj key value = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj key' <- textToCString key notify_notification_set_hint_uint32 _obj' key' value touchManagedPtr _obj freeMem key' return () -- method Notification::set_icon_from_pixbuf -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TInterface "GdkPixbuf" "Pixbuf", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TInterface "GdkPixbuf" "Pixbuf", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_icon_from_pixbuf" notify_notification_set_icon_from_pixbuf :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" Ptr GdkPixbuf.Pixbuf -> -- icon : TInterface "GdkPixbuf" "Pixbuf" IO () {-# DEPRECATED notificationSetIconFromPixbuf ["use notify_notification_set_image_from_pixbuf() instead."]#-} notificationSetIconFromPixbuf :: (MonadIO m, NotificationK a, GdkPixbuf.PixbufK b) => a -> -- _obj b -> -- icon m () notificationSetIconFromPixbuf _obj icon = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let icon' = unsafeManagedPtrCastPtr icon notify_notification_set_icon_from_pixbuf _obj' icon' touchManagedPtr _obj touchManagedPtr icon return () -- method Notification::set_image_from_pixbuf -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixbuf", argType = TInterface "GdkPixbuf" "Pixbuf", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pixbuf", argType = TInterface "GdkPixbuf" "Pixbuf", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_image_from_pixbuf" notify_notification_set_image_from_pixbuf :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" Ptr GdkPixbuf.Pixbuf -> -- pixbuf : TInterface "GdkPixbuf" "Pixbuf" IO () notificationSetImageFromPixbuf :: (MonadIO m, NotificationK a, GdkPixbuf.PixbufK b) => a -> -- _obj b -> -- pixbuf m () notificationSetImageFromPixbuf _obj pixbuf = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let pixbuf' = unsafeManagedPtrCastPtr pixbuf notify_notification_set_image_from_pixbuf _obj' pixbuf' touchManagedPtr _obj touchManagedPtr pixbuf return () -- method Notification::set_timeout -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timeout", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timeout", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_timeout" notify_notification_set_timeout :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" Int32 -> -- timeout : TBasicType TInt32 IO () notificationSetTimeout :: (MonadIO m, NotificationK a) => a -> -- _obj Int32 -> -- timeout m () notificationSetTimeout _obj timeout = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj notify_notification_set_timeout _obj' timeout touchManagedPtr _obj return () -- method Notification::set_urgency -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "urgency", argType = TInterface "Notify" "Urgency", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "urgency", argType = TInterface "Notify" "Urgency", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_notification_set_urgency" notify_notification_set_urgency :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CUInt -> -- urgency : TInterface "Notify" "Urgency" IO () notificationSetUrgency :: (MonadIO m, NotificationK a) => a -> -- _obj Urgency -> -- urgency m () notificationSetUrgency _obj urgency = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let urgency' = (fromIntegral . fromEnum) urgency notify_notification_set_urgency _obj' urgency' touchManagedPtr _obj return () -- method Notification::show -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "notify_notification_show" notify_notification_show :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" Ptr (Ptr GError) -> -- error IO CInt notificationShow :: (MonadIO m, NotificationK a) => a -> -- _obj m () notificationShow _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj onException (do _ <- propagateGError $ notify_notification_show _obj' touchManagedPtr _obj return () ) (do return () ) -- method Notification::update -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "summary", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Notify" "Notification", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "summary", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "notify_notification_update" notify_notification_update :: Ptr Notification -> -- _obj : TInterface "Notify" "Notification" CString -> -- summary : TBasicType TUTF8 CString -> -- body : TBasicType TUTF8 CString -> -- icon : TBasicType TUTF8 IO CInt notificationUpdate :: (MonadIO m, NotificationK a) => a -> -- _obj T.Text -> -- summary Maybe (T.Text) -> -- body Maybe (T.Text) -> -- icon m Bool notificationUpdate _obj summary body icon = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj summary' <- textToCString summary maybeBody <- case body of Nothing -> return nullPtr Just jBody -> do jBody' <- textToCString jBody return jBody' maybeIcon <- case icon of Nothing -> return nullPtr Just jIcon -> do jIcon' <- textToCString jIcon return jIcon' result <- notify_notification_update _obj' summary' maybeBody maybeIcon let result' = (/= 0) result touchManagedPtr _obj freeMem summary' freeMem maybeBody freeMem maybeIcon return result' -- signal Notification::closed type NotificationClosedCallback = IO () noNotificationClosedCallback :: Maybe NotificationClosedCallback noNotificationClosedCallback = Nothing type NotificationClosedCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkNotificationClosedCallback :: NotificationClosedCallbackC -> IO (FunPtr NotificationClosedCallbackC) notificationClosedClosure :: NotificationClosedCallback -> IO Closure notificationClosedClosure cb = newCClosure =<< mkNotificationClosedCallback wrapped where wrapped = notificationClosedCallbackWrapper cb notificationClosedCallbackWrapper :: NotificationClosedCallback -> Ptr () -> Ptr () -> IO () notificationClosedCallbackWrapper _cb _ _ = do _cb onNotificationClosed :: (GObject a, MonadIO m) => a -> NotificationClosedCallback -> m SignalHandlerId onNotificationClosed obj cb = liftIO $ connectNotificationClosed obj cb SignalConnectBefore afterNotificationClosed :: (GObject a, MonadIO m) => a -> NotificationClosedCallback -> m SignalHandlerId afterNotificationClosed obj cb = connectNotificationClosed obj cb SignalConnectAfter connectNotificationClosed :: (GObject a, MonadIO m) => a -> NotificationClosedCallback -> SignalConnectMode -> m SignalHandlerId connectNotificationClosed obj cb after = liftIO $ do cb' <- mkNotificationClosedCallback (notificationClosedCallbackWrapper cb) connectSignalFunPtr obj "closed" cb' after -- Enum Urgency data Urgency = UrgencyLow | UrgencyNormal | UrgencyCritical | AnotherUrgency Int deriving (Show, Eq) instance Enum Urgency where fromEnum UrgencyLow = 0 fromEnum UrgencyNormal = 1 fromEnum UrgencyCritical = 2 fromEnum (AnotherUrgency k) = k toEnum 0 = UrgencyLow toEnum 1 = UrgencyNormal toEnum 2 = UrgencyCritical toEnum k = AnotherUrgency k -- constant _EXPIRES_DEFAULT _EXPIRES_DEFAULT :: Int32 _EXPIRES_DEFAULT = -1 -- constant _EXPIRES_NEVER _EXPIRES_NEVER :: Int32 _EXPIRES_NEVER = 0 -- constant _VERSION_MAJOR _VERSION_MAJOR :: Int32 _VERSION_MAJOR = 0 -- constant _VERSION_MICRO _VERSION_MICRO :: Int32 _VERSION_MICRO = 6 -- constant _VERSION_MINOR _VERSION_MINOR :: Int32 _VERSION_MINOR = 7 -- function notify_get_app_name -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "notify_get_app_name" notify_get_app_name :: IO CString getAppName :: (MonadIO m) => m T.Text getAppName = liftIO $ do result <- notify_get_app_name result' <- cstringToText result return result' -- function notify_get_server_caps -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TGList (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "notify_get_server_caps" notify_get_server_caps :: IO (Ptr (GList CString)) getServerCaps :: (MonadIO m) => m [T.Text] getServerCaps = liftIO $ do result <- notify_get_server_caps result' <- unpackGList result result'' <- mapM cstringToText result' mapGList freeMem result g_list_free result return result'' -- function notify_get_server_info -- Args : [Arg {argName = "ret_name", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "ret_vendor", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "ret_version", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "ret_spec_version", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "notify_get_server_info" notify_get_server_info :: Ptr CString -> -- ret_name : TBasicType TUTF8 Ptr CString -> -- ret_vendor : TBasicType TUTF8 Ptr CString -> -- ret_version : TBasicType TUTF8 Ptr CString -> -- ret_spec_version : TBasicType TUTF8 IO CInt getServerInfo :: (MonadIO m) => m (Bool,T.Text,T.Text,T.Text,T.Text) getServerInfo = liftIO $ do ret_name <- allocMem :: IO (Ptr CString) ret_vendor <- allocMem :: IO (Ptr CString) ret_version <- allocMem :: IO (Ptr CString) ret_spec_version <- allocMem :: IO (Ptr CString) result <- notify_get_server_info ret_name ret_vendor ret_version ret_spec_version let result' = (/= 0) result ret_name' <- peek ret_name ret_name'' <- cstringToText ret_name' freeMem ret_name' ret_vendor' <- peek ret_vendor ret_vendor'' <- cstringToText ret_vendor' freeMem ret_vendor' ret_version' <- peek ret_version ret_version'' <- cstringToText ret_version' freeMem ret_version' ret_spec_version' <- peek ret_spec_version ret_spec_version'' <- cstringToText ret_spec_version' freeMem ret_spec_version' freeMem ret_name freeMem ret_vendor freeMem ret_version freeMem ret_spec_version return (result', ret_name'', ret_vendor'', ret_version'', ret_spec_version'') -- function notify_init -- Args : [Arg {argName = "app_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "app_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "notify_init" notify_init :: CString -> -- app_name : TBasicType TUTF8 IO CInt init :: (MonadIO m) => T.Text -> -- app_name m Bool init app_name = liftIO $ do app_name' <- textToCString app_name result <- notify_init app_name' let result' = (/= 0) result freeMem app_name' return result' -- function notify_is_initted -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "notify_is_initted" notify_is_initted :: IO CInt isInitted :: (MonadIO m) => m Bool isInitted = liftIO $ do result <- notify_is_initted let result' = (/= 0) result return result' -- function notify_set_app_name -- Args : [Arg {argName = "app_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "app_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_set_app_name" notify_set_app_name :: CString -> -- app_name : TBasicType TUTF8 IO () setAppName :: (MonadIO m) => T.Text -> -- app_name m () setAppName app_name = liftIO $ do app_name' <- textToCString app_name notify_set_app_name app_name' freeMem app_name' return () -- function notify_uninit -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "notify_uninit" notify_uninit :: IO () uninit :: (MonadIO m) => m () uninit = liftIO $ do notify_uninit return ()