{-# LANGUAGE ForeignFunctionInterface #-} module Graphics.UI.AppIndicator ( -- * Detail -- -- | The applications indication area is used for menus that provide some -- kind of status about the system; there are several predefined menus (for -- example, relating to sound, mail), and additional ones can be added. On -- platforms not supporting this functionality, the library will fallback -- to using a status icon (see Graphics.UI.Gtk.Display.StatusIcon in the -- gtk package). -- * Class Hierarchy -- -- | -- @ -- | 'GObject' -- | +----AppIndicator -- @ -- * Types AppIndicator, AppIndicatorClass, toAppIndicator, AppIndicatorCategory (..), AppIndicatorStatus (..), -- NOTE: libappindicator doesn't appear to offer a gtk_appindicator_get_type -- function which is required to implement the following two functions. As -- they appear to be unnecessary anyway, I am simply not going to implement -- them. If I'm being an idiot, please let me know. -- castToAppIndicator, -- gTypeAppIndicator, -- * 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 -- | Represents the category of an Application Indicator. data AppIndicatorCategory = AppIndicatorCategoryApplicationStatus | AppIndicatorCategoryCommunications | AppIndicatorCategorySystemServices | AppIndicatorCategoryHardware | AppIndicatorCategoryOther deriving (Bounded, Enum, Eq, Show) -- | Represents the status of an Application Indicator. data AppIndicatorStatus = AppIndicatorStatusPassive | AppIndicatorStatusActive | AppIndicatorStatusAttention deriving (Bounded, Enum, Eq, Show) -- * Constructors -- | Creates an empty AppIndicator object, setting the properties: "id" with id, -- | "category" with category and "icon-name" with icon_name. appIndicatorNew :: (GlibString id', GlibString iconName) => id' -> iconName -> AppIndicatorCategory -> IO 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 setting the properties: "id" with id, "category" -- | with category, "icon-name" with icon_name and "icon-theme-path" with -- | icon_theme_path. appIndicatorNewWithPath :: (GlibString id', GlibString iconName, GlibString iconThemePath) => id' -> iconName -> AppIndicatorCategory -> iconThemePath -> IO 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 -- | This function allows for building the Application Indicator menu from a static -- | desktop file. appIndicatorBuildMenuFromDesktop :: (AppIndicatorClass self, GlibString desktopFile, GlibString desktopProfile) => self -> desktopFile -> desktopProfile -> 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 () -- | This function retrieves the Application Indicator menu. appIndicatorGetMenu :: AppIndicatorClass self => self -> IO Menu 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) -- | This function sets the Application Indicator menu. appIndicatorSetMenu :: (AppIndicatorClass self, MenuClass menu) => self -> menu -> 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 () -- | This function retrieves the current status of the Application Indicator. appIndicatorGetStatus :: AppIndicatorClass self => self -> IO AppIndicatorStatus 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 -- | This function set the status of the Application Indicator. appIndicatorSetStatus :: AppIndicatorClass self => self -> AppIndicatorStatus -> 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 () -- | This function retrieves the category of the Application Indicator. appIndicatorGetCategory :: AppIndicatorClass self => self -> IO AppIndicatorCategory 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 indicator sets it's status to APP_INDICATOR_STATUS_ATTENTION then this textual description of the icon shown. appIndicatorAttentionIconDesc :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) appIndicatorAttentionIconDesc = newAttrFromMaybeStringProperty "attention-icon-desc" -- | If the indicator sets it's status to APP_INDICATOR_STATUS_ATTENTION then this icon is shown. appIndicatorAttentionIconName :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) appIndicatorAttentionIconName = newAttrFromMaybeStringProperty "attention-icon-name" -- | The type of indicator that this represents. Please don't use 'Other'. Defaults to 'ApplicationStatus'. appIndicatorCategory :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) appIndicatorCategory = newAttrFromMaybeStringProperty "category" -- | Pretty simple, TRUE if we have a reasonable expectation of being displayed through this object. You should hide your TrayIcon if so. appIndicatorConnected :: AppIndicatorClass self => ReadAttr self Bool appIndicatorConnected = readAttrFromBoolProperty "connected" -- | The description of the regular icon that is shown for the indicator. appIndicatorIconDesc :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) appIndicatorIconDesc = newAttrFromMaybeStringProperty "icon-desc" -- | The name of the regular icon that is shown for the indicator. appIndicatorIconName :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) 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) appIndicatorIconThemePath = newAttrFromMaybeStringProperty "icon-theme-path" -- | The ID for this indicator, which should be unique, but used consistently by this program and its indicator. appIndicatorId :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) appIndicatorId = newAttrFromMaybeStringProperty "id" -- | A label that can be shown next to the string in the application indicator. 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) appIndicatorLabel = newAttrFromMaybeStringProperty "label" -- | An optional string to provide guidance to the panel on how big the "label" string could get. If this is set correctly then the panel should never 'jiggle' as the string adjusts through out the range of options. For instance, if you were providing a percentage like "54% thrust" in "label" 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) 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 application indicator try to place the applications in a recreatable place taking into account which category they're in to try and group them. But, there are some cases where you'd want to ensure indicators 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 appIndicatorOrderingIndex = newAttrFromUIntProperty "ordering-index" -- | Whether the indicator is shown or requests attention. Defaults to 'Passive'. appIndicatorStatus :: (AppIndicatorClass self, GlibString str) => Attr self (Maybe str) appIndicatorStatus = newAttrFromMaybeStringProperty "status" -- -- * Signals -- | Emitted when "icon-name" is changed appIndicatorNewIcon :: AppIndicatorClass self => Signal self (IO ()) appIndicatorNewIcon = Signal (connect_NONE__NONE "new-icon") -- | Emitted when "attention-icon-name" is changed appIndicatorNewAttentionIcon :: AppIndicatorClass self => Signal self (IO ()) appIndicatorNewAttentionIcon = Signal (connect_NONE__NONE "new-attention-icon") -- | Emitted when "status" is changed appIndicatorNewStatus :: (AppIndicatorClass self, GlibString str) => Signal self (str -> IO ()) appIndicatorNewStatus = Signal (connect_GLIBSTRING__NONE "new-status") -- | Emitted when either "label" or "label-guide" 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 there is a new icon set for the object. 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")