-- | -- = Notification server plugin for [XMobar](https://codeberg.org/xmobar/xmobar) -- -- This module only exposes the 'XNobar' data type, along with the homonym ctor -- to be used for instantiating a plugin for [XMobar](https://codeberg.org/xmobar/xmobar). -- -- That plugin will start a notification server, and show the notifications in a marquee -- as they come, with a default text if there's no notification to show. -- -- A single click on the marquee will dismiss the notification on which the click happened. -- {-# LANGUAGE LambdaCase #-} module XNobar (XNobar (..)) where import Control.Monad (when) import Xmobar (Exec (..)) import XNobar.Server (startServer) import XNobar.Scroller (scroller) -- |XNobar plugin ctor. You would use it like this in your @xmobar.hs@ -- (__note__: the non-library usage of -- [XMobar](https://codeberg.org/xmobar/xmobar) is not supported, or at least I -- haven't tried using xnobar in that context): -- -- @ -- main :: IO () -- main = xmobar defaultConfig { -- , commands = [ -- Run $ 'XNobar' "hello" 20 1 -- -- ... -- @ data XNobar = XNobar !String -- ^ Default string (to be shown steady) when no notification is left. !Int -- ^ Width (in number of characters) of the scrolling marquee (this is unrelated ot the length of the first argument). !Int -- ^ Scrolling rate (in tenths of seconds per character). deriving (Read, -- ^ For integration with [XMobar](https://codeberg.org/xmobar/xmobar). Show) -- ^ For integration with [XMobar](https://codeberg.org/xmobar/xmobar). -- |For integration with [XMobar](https://codeberg.org/xmobar/xmobar). instance Exec XNobar where alias (XNobar {}) = "XNobar" start (XNobar def len rate) cb = startServer >>= \case Just notifs -> do scroller def rate len cb notifs error "What? scroller returned. Has it been killed?!" Nothing -> cb "Server could not start"