{-# LANGUAGE ForeignFunctionInterface #-} module Graphics.UI.AppIndicator ( -- * Detail -- -- | An 'AppIndicator' represents the values that are needed to show a unique -- status in the panel for an application. In general, applications should try -- to fit in the other indicators that are available on the panel before using -- this. But, sometimes it is necissary. -- * Class Hierarchy -- -- | -- @ -- | 'System.Glib.GObject' -- | +----'AppIndicator' -- @ -- * Types AppIndicator, AppIndicatorClass, castToAppIndicator, gTypeAppIndicator, toAppIndicator, AppIndicatorCategory (..), AppIndicatorStatus (..), -- * Constructors appIndicatorNew, appIndicatorNewWithPath, -- * Methods appIndicatorBuildMenuFromDesktop, appIndicatorGetMenu, appIndicatorSetMenu, appIndicatorGetStatus, appIndicatorSetStatus, appIndicatorGetCategory, -- * Attributes appIndicatorAttentionIconDesc, appIndicatorAttentionIconName, appIndicatorCategory, appIndicatorConnected, appIndicatorIconDesc, appIndicatorIconName, appIndicatorIconThemePath, appIndicatorId, appIndicatorLabel, appIndicatorLabelGuide, appIndicatorOrderingIndex, appIndicatorStatus, -- * Signals appIndicatorNewIcon, appIndicatorNewAttentionIcon, appIndicatorNewStatus, appIndicatorNewLabel, appIndicatorConnectionChanged, appIndicatorNewIconThemePath, appIndicatorScrollEvent, ) where import Control.Monad (liftM) import Graphics.UI.Gtk (Signal (..)) import Graphics.UI.Gtk.Abstract.Object (makeNewObject) import Graphics.UI.GtkInternals (Menu, MenuClass, mkMenu, toMenu, unMenu) import System.Glib.Attributes (Attr, ReadAttr) import System.Glib.FFI (CString, CULong (..), Ptr, withForeignPtr) import System.Glib.Properties (newAttrFromMaybeStringProperty, newAttrFromUIntProperty, readAttrFromBoolProperty) import System.Glib.UTFString (GlibString, withUTFString) import Graphics.UI.AppIndicator.Signals import Graphics.UI.AppIndicator.Types -- * Types -- | The category of an 'AppIndicator'. data AppIndicatorCategory = AppIndicatorCategoryApplicationStatus | AppIndicatorCategoryCommunications | AppIndicatorCategorySystemServices | AppIndicatorCategoryHardware | AppIndicatorCategoryOther deriving (Bounded, Enum, Eq, Show) -- | The status of an 'AppIndicator'. data AppIndicatorStatus = AppIndicatorStatusPassive | AppIndicatorStatusActive | AppIndicatorStatusAttention deriving (Bounded, Enum, Eq, Show) -- * Constructors -- | Creates a new 'AppIndicator' object. appIndicatorNew :: (GlibString id, GlibString iconName) => id -- ^ The ID for this indicator, which should be -- unique, but used consistently by this program and -- its indicator. -> iconName -- ^ The name of the regular icon that is shown for -- the indicator. -> AppIndicatorCategory -- ^ The type of 'AppIndicator' that this represents. -- Please don't use 'AppIndicatorCategoryOther'. -> IO AppIndicator -- ^ Returns the new 'AppIndicator'. appIndicatorNew id iconName cat = makeNewObject mkAppIndicator $ withUTFString id $ \idPtr -> withUTFString iconName $ \iconNamePtr -> app_indicator_new idPtr iconNamePtr (fromIntegral $ fromEnum cat) foreign import ccall safe "app_indicator_new" app_indicator_new :: CString -> CString -> CULong -> IO (Ptr AppIndicator) -- | Creates a new 'AppIndicator' object with an additional place to look for -- icon names that may be installed by the application. appIndicatorNewWithPath :: (GlibString id, GlibString iconName, GlibString iconThemePath) => id -- ^ The ID for this indicator, which should be -- unique, but used consistently by this program and -- its indicator. -> iconName -- ^ The name of the regular icon that is shown for -- the indicator. -> AppIndicatorCategory -- ^ The type of indicator that this represents. -- Please don't use 'AppIndicatorCategoryOther'. -> iconThemePath -- ^ An additional place to look for icon names that -- may be installed by the application. -> IO AppIndicator -- ^ Returns the new 'AppIndicator'. appIndicatorNewWithPath id iconName cat iconThemePath = makeNewObject mkAppIndicator $ withUTFString id $ \idPtr -> withUTFString iconName $ \iconNamePtr -> withUTFString iconThemePath $ \iconThemePathPtr -> app_indicator_new_with_path idPtr iconNamePtr (fromIntegral $ fromEnum cat) iconThemePathPtr foreign import ccall safe "app_indicator_new_with_path" app_indicator_new_with_path :: CString -> CString -> CULong -> CString -> IO (Ptr AppIndicator) -- * Methods -- | Updates an 'AppIndicator' based on the specification of a provided -- -- and associated desktop profile that determines which actions are available. -- -- This should rarely be used, and only with a -- compliant desktop. appIndicatorBuildMenuFromDesktop :: (AppIndicatorClass self, GlibString desktopFile, GlibString desktopProfile) => self -- ^ The 'AppIndicator' being operated on. -> desktopFile -- ^ The path to the . -> desktopProfile -- ^ The name used by the \"OnlyShowIn\" sections of the -- desktop file. -> IO () appIndicatorBuildMenuFromDesktop self desktopFile desktopProfile = withForeignPtr (unAppIndicator $ toAppIndicator self) $ \selfPtr -> withUTFString desktopFile $ \desktopFilePtr -> withUTFString desktopProfile $ \desktopProfilePtr -> app_indicator_build_menu_from_desktop selfPtr desktopFilePtr desktopProfilePtr foreign import ccall safe "app_indicator_build_menu_from_desktop" app_indicator_build_menu_from_desktop :: Ptr AppIndicator -> CString -> CString -> IO () -- | Returns the current 'Menu' of the given 'AppIndicator'. appIndicatorGetMenu :: AppIndicatorClass self => self -- ^ The 'AppIndicator' being operated on. -> IO Menu -- ^ Returns the current 'Menu' of the given 'AppIndicator'. appIndicatorGetMenu self = makeNewObject mkMenu $ withForeignPtr (unAppIndicator $ toAppIndicator self) $ \selfPtr -> app_indicator_get_menu selfPtr foreign import ccall safe "app_indicator_get_menu" app_indicator_get_menu :: Ptr AppIndicator -> IO (Ptr Menu) -- | Sets the 'Menu' of the given 'AppIndicator'. appIndicatorSetMenu :: (AppIndicatorClass self, MenuClass menu) => self -- ^ The 'AppIndicator' being operated on. -> menu -- ^ The 'Menu' being set. -> IO () appIndicatorSetMenu self menu = withForeignPtr (unAppIndicator $ toAppIndicator self) $ \selfPtr -> withForeignPtr (unMenu $ toMenu menu) $ \menuPtr -> app_indicator_set_menu selfPtr menuPtr foreign import ccall safe "app_indicator_set_menu" app_indicator_set_menu :: Ptr AppIndicator -> Ptr Menu -> IO () -- | Returns the current 'ApplicationStatus' of the given 'AppIndicator'. appIndicatorGetStatus :: AppIndicatorClass self => self -- ^ The 'AppIndicator' being operated on. -> IO AppIndicatorStatus -- ^ Returns the current 'ApplicationStatus' of the -- given 'AppIndicator'. appIndicatorGetStatus self = liftM (toEnum . fromIntegral) $ withForeignPtr (unAppIndicator $ toAppIndicator self) $ \selfPtr -> app_indicator_get_status selfPtr foreign import ccall safe "app_indicator_get_status" app_indicator_get_status :: Ptr AppIndicator -> IO CULong -- | Sets the 'ApplicationStatus' of the given 'AppIndicator'. appIndicatorSetStatus :: AppIndicatorClass self => self -- ^ The 'AppIndicator' being operated on. -> AppIndicatorStatus -- ^ The 'ApplicationStatus' being set. -> IO () appIndicatorSetStatus self stat = withForeignPtr (unAppIndicator $ toAppIndicator self) $ \selfPtr -> app_indicator_set_status selfPtr (fromIntegral $ fromEnum stat) foreign import ccall safe "app_indicator_set_status" app_indicator_set_status :: Ptr AppIndicator -> CULong -> IO () -- | Returns the 'AppIndicatorCategory' of the given 'AppIndicator'. appIndicatorGetCategory :: AppIndicatorClass self => self -- ^ The 'AppIndicator' being operated on. -> IO AppIndicatorCategory -- ^ Returns the 'AppIndicatorCategory' of the -- given 'AppIndicator'. appIndicatorGetCategory self = liftM (toEnum . fromIntegral) $ withForeignPtr (unAppIndicator $ toAppIndicator self) $ \selfPtr -> app_indicator_get_category selfPtr foreign import ccall safe "app_indicator_get_category" app_indicator_get_category :: Ptr AppIndicator -> IO CULong -- * Attributes -- | If the 'AppIndicator' sets its 'AppIndicatorStatus' to -- 'AppIndicatorStatusAttention', then this textual description of the icon is -- shown. appIndicatorAttentionIconDesc :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ The textual description of the icon being shown. appIndicatorAttentionIconDesc = newAttrFromMaybeStringProperty "attention-icon-desc" -- | If the 'AppIndicator' sets its 'AppIndicatorStatus' to -- 'AppIndicatorStatusAttention', then this icon is shown. appIndicatorAttentionIconName :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ The icon being shown. appIndicatorAttentionIconName = newAttrFromMaybeStringProperty "attention-icon-name" -- | The type of 'AppIndicator' that this represents. Please don't use -- \"Other\". appIndicatorCategory :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ The type of 'AppIndicator' that this represents. appIndicatorCategory = newAttrFromMaybeStringProperty "category" -- | Pretty simple, 'True' if we have a reasonable expectation of being -- displayed through this object. You should hide your -- 'Graphics.UI.Gtk.Display.StatusIcon.StatusIcon' if so. appIndicatorConnected :: AppIndicatorClass self => ReadAttr self Bool -- ^ 'True' if we have a reasonable expectation of being -- displayed. appIndicatorConnected = readAttrFromBoolProperty "connected" -- | The description of the regular icon that is shown for the 'AppIndicator'. appIndicatorIconDesc :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ The description of the regular icon that is -- shown. appIndicatorIconDesc = newAttrFromMaybeStringProperty "icon-desc" -- | The name of the regular icon that is shown for the 'AppIndicator'. appIndicatorIconName :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ The name of the regular icon that is shown. appIndicatorIconName = newAttrFromMaybeStringProperty "icon-name" -- | An additional place to look for icon names that may be installed by the -- application. appIndicatorIconThemePath :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ Path to an additional place to look for icon -- names that may be installed by the application. appIndicatorIconThemePath = newAttrFromMaybeStringProperty "icon-theme-path" -- | The ID for this 'AppIndicator', which should be unique, but used -- consistently by this program and its 'AppIndicator'. appIndicatorId :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ The ID for this 'AppIndicator'. appIndicatorId = newAttrFromMaybeStringProperty "id" -- | A label that can be shown next to the string in the 'AppIndicator'. The -- label will not be shown unless there is an icon as well. The label is useful -- for numerical and other frequently updated information. In general, it -- shouldn't be shown unless a user requests it as it can take up a significant -- amount of space on the user's panel. This may not be shown in all -- visualizations. appIndicatorLabel :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ A label that can be shown next to the string in -- the 'AppIndicator'. appIndicatorLabel = newAttrFromMaybeStringProperty "label" -- | An optional string to provide guidance to the panel on how big the -- 'appIndicatorLabel' string could get. If this is set correctly then the panel -- should never \"jiggle\" as the string adjusts throughout the range of -- options. For instance, if you were providing a percentage like \"54% thrust\" -- in 'appIndicatorLabel', you'd want to set this string to \"100% thrust\" to -- ensure space when Scotty can get you enough power. appIndicatorLabelGuide :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ An optional string to provide guidance to the -- panel on how big the 'appIndicatorLabel' string -- could get. appIndicatorLabelGuide = newAttrFromMaybeStringProperty "label-guide" -- | The ordering index is an odd parameter, and if you think you don't need -- it, you're probably right. In general, the 'AppIndicator' tries to place the -- applications in a recreatable place taking into account which -- 'AppIndicatorCategory' they're in to try and group them. But, there are some -- cases where you'd want to ensure 'AppIndicator's are next to each other. To -- do that you can override the generated ordering index and replace it with a -- new one. Again, you probably don't want to be doing this, but in case you do, -- this is the way. appIndicatorOrderingIndex :: AppIndicatorClass self => Attr self Int -- ^ Overrides the generated ordering index and replaces it -- with a new one. appIndicatorOrderingIndex = newAttrFromUIntProperty "ordering-index" -- | Whether the 'AppIndicator' is shown or requests attention. Defaults to -- \"Passive\". appIndicatorStatus :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) -- ^ The 'AppIndicator' status. appIndicatorStatus = newAttrFromMaybeStringProperty "status" -- -- * Signals -- | Emitted when 'appIndicatorIconName' is changed. appIndicatorNewIcon :: AppIndicatorClass self => Signal self (IO ()) appIndicatorNewIcon = Signal (connect_NONE__NONE "new-icon") -- | Emitted when 'appIndicatorAttentionIconName' is changed. appIndicatorNewAttentionIcon :: AppIndicatorClass self => Signal self (IO ()) appIndicatorNewAttentionIcon = Signal (connect_NONE__NONE "new-attention-icon") -- | Emitted when 'appIndicatorStatus' is changed. appIndicatorNewStatus :: (AppIndicatorClass self, GlibString str) => Signal self (str -> IO ()) appIndicatorNewStatus = Signal (connect_GLIBSTRING__NONE "new-status") -- | Emitted when either 'appIndicatorLabel' or 'appIndicatorLabelGuide' are -- changed. appIndicatorNewLabel :: (AppIndicatorClass self, GlibString label, GlibString guide) => Signal self (label -> guide -> IO ()) appIndicatorNewLabel = Signal (connect_GLIBSTRING_GLIBSTRING__NONE "new-label") -- | Emitted when we connect to a watcher, or when it drops away. appIndicatorConnectionChanged :: AppIndicatorClass self => Signal self (Bool -> IO ()) appIndicatorConnectionChanged = Signal (connect_BOOL__NONE "connection-changed") -- | Emitted when the 'appIndicatorIconThemePath' is changed. appIndicatorNewIconThemePath :: (AppIndicatorClass self, GlibString str) => Signal self (str -> IO ()) appIndicatorNewIconThemePath = Signal (connect_GLIBSTRING__NONE "new-icon-theme-path") -- | Emitted when the 'AppIndicator' receives a scroll event. appIndicatorScrollEvent :: AppIndicatorClass self => Signal self (Int -> Int -> IO ()) appIndicatorScrollEvent = Signal (connect_INT_INT__NONE "scroll-event")