{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-} -- Generated code. {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# LANGUAGE ForeignFunctionInterface, ConstraintKinds, TypeFamilies, MultiParamTypeClasses, KindSignatures, FlexibleInstances, UndecidableInstances, DataKinds, OverloadedStrings, NegativeLiterals, FlexibleContexts #-} module GI.NotifyAttributes 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 GI.Notify -- VVV Prop "app-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getNotificationAppName :: (MonadIO m, NotificationK o) => o -> m T.Text getNotificationAppName obj = liftIO $ getObjectPropertyString obj "app-name" setNotificationAppName :: (MonadIO m, NotificationK o) => o -> T.Text -> m () setNotificationAppName obj val = liftIO $ setObjectPropertyString obj "app-name" val constructNotificationAppName :: T.Text -> IO ([Char], GValue) constructNotificationAppName val = constructObjectPropertyString "app-name" val data NotificationAppNamePropertyInfo instance AttrInfo NotificationAppNamePropertyInfo where type AttrAllowedOps NotificationAppNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NotificationAppNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint NotificationAppNamePropertyInfo = NotificationK type AttrGetType NotificationAppNamePropertyInfo = T.Text type AttrLabel NotificationAppNamePropertyInfo = "Notification::app-name" attrGet _ = getNotificationAppName attrSet _ = setNotificationAppName attrConstruct _ = constructNotificationAppName -- VVV Prop "body" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getNotificationBody :: (MonadIO m, NotificationK o) => o -> m T.Text getNotificationBody obj = liftIO $ getObjectPropertyString obj "body" setNotificationBody :: (MonadIO m, NotificationK o) => o -> T.Text -> m () setNotificationBody obj val = liftIO $ setObjectPropertyString obj "body" val constructNotificationBody :: T.Text -> IO ([Char], GValue) constructNotificationBody val = constructObjectPropertyString "body" val data NotificationBodyPropertyInfo instance AttrInfo NotificationBodyPropertyInfo where type AttrAllowedOps NotificationBodyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NotificationBodyPropertyInfo = (~) T.Text type AttrBaseTypeConstraint NotificationBodyPropertyInfo = NotificationK type AttrGetType NotificationBodyPropertyInfo = T.Text type AttrLabel NotificationBodyPropertyInfo = "Notification::body" attrGet _ = getNotificationBody attrSet _ = setNotificationBody attrConstruct _ = constructNotificationBody -- VVV Prop "closed-reason" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable] getNotificationClosedReason :: (MonadIO m, NotificationK o) => o -> m Int32 getNotificationClosedReason obj = liftIO $ getObjectPropertyCInt obj "closed-reason" data NotificationClosedReasonPropertyInfo instance AttrInfo NotificationClosedReasonPropertyInfo where type AttrAllowedOps NotificationClosedReasonPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint NotificationClosedReasonPropertyInfo = (~) () type AttrBaseTypeConstraint NotificationClosedReasonPropertyInfo = NotificationK type AttrGetType NotificationClosedReasonPropertyInfo = Int32 type AttrLabel NotificationClosedReasonPropertyInfo = "Notification::closed-reason" attrGet _ = getNotificationClosedReason attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "icon-name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getNotificationIconName :: (MonadIO m, NotificationK o) => o -> m T.Text getNotificationIconName obj = liftIO $ getObjectPropertyString obj "icon-name" setNotificationIconName :: (MonadIO m, NotificationK o) => o -> T.Text -> m () setNotificationIconName obj val = liftIO $ setObjectPropertyString obj "icon-name" val constructNotificationIconName :: T.Text -> IO ([Char], GValue) constructNotificationIconName val = constructObjectPropertyString "icon-name" val data NotificationIconNamePropertyInfo instance AttrInfo NotificationIconNamePropertyInfo where type AttrAllowedOps NotificationIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NotificationIconNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint NotificationIconNamePropertyInfo = NotificationK type AttrGetType NotificationIconNamePropertyInfo = T.Text type AttrLabel NotificationIconNamePropertyInfo = "Notification::icon-name" attrGet _ = getNotificationIconName attrSet _ = setNotificationIconName attrConstruct _ = constructNotificationIconName -- VVV Prop "id" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getNotificationId :: (MonadIO m, NotificationK o) => o -> m Int32 getNotificationId obj = liftIO $ getObjectPropertyCInt obj "id" setNotificationId :: (MonadIO m, NotificationK o) => o -> Int32 -> m () setNotificationId obj val = liftIO $ setObjectPropertyCInt obj "id" val constructNotificationId :: Int32 -> IO ([Char], GValue) constructNotificationId val = constructObjectPropertyCInt "id" val data NotificationIdPropertyInfo instance AttrInfo NotificationIdPropertyInfo where type AttrAllowedOps NotificationIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NotificationIdPropertyInfo = (~) Int32 type AttrBaseTypeConstraint NotificationIdPropertyInfo = NotificationK type AttrGetType NotificationIdPropertyInfo = Int32 type AttrLabel NotificationIdPropertyInfo = "Notification::id" attrGet _ = getNotificationId attrSet _ = setNotificationId attrConstruct _ = constructNotificationId -- VVV Prop "summary" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct] getNotificationSummary :: (MonadIO m, NotificationK o) => o -> m T.Text getNotificationSummary obj = liftIO $ getObjectPropertyString obj "summary" setNotificationSummary :: (MonadIO m, NotificationK o) => o -> T.Text -> m () setNotificationSummary obj val = liftIO $ setObjectPropertyString obj "summary" val constructNotificationSummary :: T.Text -> IO ([Char], GValue) constructNotificationSummary val = constructObjectPropertyString "summary" val data NotificationSummaryPropertyInfo instance AttrInfo NotificationSummaryPropertyInfo where type AttrAllowedOps NotificationSummaryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint NotificationSummaryPropertyInfo = (~) T.Text type AttrBaseTypeConstraint NotificationSummaryPropertyInfo = NotificationK type AttrGetType NotificationSummaryPropertyInfo = T.Text type AttrLabel NotificationSummaryPropertyInfo = "Notification::summary" attrGet _ = getNotificationSummary attrSet _ = setNotificationSummary attrConstruct _ = constructNotificationSummary type instance AttributeList Notification = '[ '("app-name", NotificationAppNamePropertyInfo), '("body", NotificationBodyPropertyInfo), '("closed-reason", NotificationClosedReasonPropertyInfo), '("icon-name", NotificationIconNamePropertyInfo), '("id", NotificationIdPropertyInfo), '("summary", NotificationSummaryPropertyInfo)]