xmobar-0.42: A Minimalistic Text Based Status Bar
Copyright(c) 2011 2012 2013 2014 2015 2017 2018 2019 2022 Jose Antonio Ortega Ruiz
(c) 2007 Andrea Rossato
LicenseBSD-style (see LICENSE)
MaintainerJose A. Ortega Ruiz <jao@gnu.org>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

Xmobar

Description

Public interface of the xmobar library

Synopsis

Documentation

defaultConfig :: Config Source #

The default configuration values

tenthSeconds :: Int -> IO () Source #

Sleep for a given amount of tenths of a second.

(Work around the Int max bound: since threadDelay takes an Int, it is not possible to set a thread delay grater than about 45 minutes. With a little recursion we solve the problem.)

data Runnable Source #

Constructors

forall r.(Exec r, Read r, Show r) => Run r 

Instances

Instances details
Read Runnable Source # 
Instance details

Defined in Xmobar.Run.Runnable

Show Runnable Source # 
Instance details

Defined in Xmobar.Run.Runnable

Exec Runnable Source # 
Instance details

Defined in Xmobar.Run.Runnable

class Show e => Exec e where Source #

Minimal complete definition

Nothing

Methods

alias :: e -> String Source #

rate :: e -> Int Source #

run :: e -> IO String Source #

start :: e -> (String -> IO ()) -> IO () Source #

trigger :: e -> (Maybe SignalType -> IO ()) -> IO () Source #

Instances

Instances details
Exec Runnable Source # 
Instance details

Defined in Xmobar.Run.Runnable

Exec StdinReader Source # 
Instance details

Defined in Xmobar.Plugins.StdinReader

Exec PipeReader Source # 
Instance details

Defined in Xmobar.Plugins.PipeReader

Exec NotmuchMail Source #

How to execute this plugin.

Instance details

Defined in Xmobar.Plugins.NotmuchMail

Exec MarqueePipeReader Source # 
Instance details

Defined in Xmobar.Plugins.MarqueePipeReader

Exec HandleReader Source #

Asynchronously read from the Handle.

Instance details

Defined in Xmobar.Plugins.HandleReader

Exec Date Source # 
Instance details

Defined in Xmobar.Plugins.Date

Methods

alias :: Date -> String Source #

rate :: Date -> Int Source #

run :: Date -> IO String Source #

start :: Date -> (String -> IO ()) -> IO () Source #

trigger :: Date -> (Maybe SignalType -> IO ()) -> IO () Source #

Exec CommandReader Source # 
Instance details

Defined in Xmobar.Plugins.CommandReader

Exec Command Source # 
Instance details

Defined in Xmobar.Plugins.Command

Exec BufferedPipeReader Source # 
Instance details

Defined in Xmobar.Plugins.BufferedPipeReader

Exec Monitors Source # 
Instance details

Defined in Xmobar.Plugins.Monitors

Exec XMonadLog Source # 
Instance details

Defined in Xmobar.Plugins.XMonadLog

Exec Locks Source # 
Instance details

Defined in Xmobar.Plugins.Locks

Methods

alias :: Locks -> String Source #

rate :: Locks -> Int Source #

run :: Locks -> IO String Source #

start :: Locks -> (String -> IO ()) -> IO () Source #

trigger :: Locks -> (Maybe SignalType -> IO ()) -> IO () Source #

Exec Kbd Source # 
Instance details

Defined in Xmobar.Plugins.Kbd

Methods

alias :: Kbd -> String Source #

rate :: Kbd -> Int Source #

run :: Kbd -> IO String Source #

start :: Kbd -> (String -> IO ()) -> IO () Source #

trigger :: Kbd -> (Maybe SignalType -> IO ()) -> IO () Source #

Exec EWMH Source # 
Instance details

Defined in Xmobar.Plugins.EWMH

Methods

alias :: EWMH -> String Source #

rate :: EWMH -> Int Source #

run :: EWMH -> IO String Source #

start :: EWMH -> (String -> IO ()) -> IO () Source #

trigger :: EWMH -> (Maybe SignalType -> IO ()) -> IO () Source #

Exec (QueueReader a) Source #

Async queue/channel reading.

Instance details

Defined in Xmobar.Plugins.QueueReader

data Command Source #

Constructors

Com Program Args Alias Rate 
ComX Program Args String Alias Rate 

Instances

Instances details
Eq Command Source # 
Instance details

Defined in Xmobar.Plugins.Command

Methods

(==) :: Command -> Command -> Bool #

(/=) :: Command -> Command -> Bool #

Read Command Source # 
Instance details

Defined in Xmobar.Plugins.Command

Show Command Source # 
Instance details

Defined in Xmobar.Plugins.Command

Exec Command Source # 
Instance details

Defined in Xmobar.Plugins.Command

Configuration

Configuration data type

data Config Source #

The configuration data type

Constructors

Config 

Fields

Instances

Instances details
Read Config Source # 
Instance details

Defined in Xmobar.Config.Types

Show Config Source # 
Instance details

Defined in Xmobar.Config.Types

data Align Source #

Constructors

L 
R 
C 

Instances

Instances details
Eq Align Source # 
Instance details

Defined in Xmobar.Config.Types

Methods

(==) :: Align -> Align -> Bool #

(/=) :: Align -> Align -> Bool #

Read Align Source # 
Instance details

Defined in Xmobar.Config.Types

Show Align Source # 
Instance details

Defined in Xmobar.Config.Types

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

data Border Source #

Instances

Instances details
Eq Border Source # 
Instance details

Defined in Xmobar.Config.Types

Methods

(==) :: Border -> Border -> Bool #

(/=) :: Border -> Border -> Bool #

Read Border Source # 
Instance details

Defined in Xmobar.Config.Types

Show Border Source # 
Instance details

Defined in Xmobar.Config.Types

readConfig :: Config -> FilePath -> IO (Either ParseError (Config, [String])) Source #

Reads the configuration from a file or an error if it cannot be parsed.

parseConfig :: Config -> String -> Either ParseError (Config, [String]) Source #

Parse the config, logging a list of fields that were missing and replaced by the default definition.

data Date Source #

Constructors

Date String String Int 

Instances

Instances details
Read Date Source # 
Instance details

Defined in Xmobar.Plugins.Date

Show Date Source # 
Instance details

Defined in Xmobar.Plugins.Date

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

Exec Date Source # 
Instance details

Defined in Xmobar.Plugins.Date

Methods

alias :: Date -> String Source #

rate :: Date -> Int Source #

run :: Date -> IO String Source #

start :: Date -> (String -> IO ()) -> IO () Source #

trigger :: Date -> (Maybe SignalType -> IO ()) -> IO () Source #

data EWMH Source #

Constructors

EWMH 
EWMHFMT Component 

Instances

Instances details
Read EWMH Source # 
Instance details

Defined in Xmobar.Plugins.EWMH

Show EWMH Source # 
Instance details

Defined in Xmobar.Plugins.EWMH

Methods

showsPrec :: Int -> EWMH -> ShowS #

show :: EWMH -> String #

showList :: [EWMH] -> ShowS #

Exec EWMH Source # 
Instance details

Defined in Xmobar.Plugins.EWMH

Methods

alias :: EWMH -> String Source #

rate :: EWMH -> Int Source #

run :: EWMH -> IO String Source #

start :: EWMH -> (String -> IO ()) -> IO () Source #

trigger :: EWMH -> (Maybe SignalType -> IO ()) -> IO () Source #

data HandleReader Source #

A HandleReader displays any text received from a Handle.

This is only useful if you are running xmobar from other Haskell code. You can create a pair of (read, write) Handles using createPipe. Pass the read Handle to HandleReader and write your desired output to the write Handle.

 (readHandle, writeHandle) <- createPipe
 xmobarProcess <- forkProcess $ xmobar myConfig
         { commands =
             Run (HandleReader readHandle "handle") : commands myConfig
         }
 hPutStr writeHandle "Hello World"

Constructors

HandleReader 

Fields

  • Handle

    The Handle to read from.

  • String

    Alias for the HandleReader

Instances

Instances details
Read HandleReader Source #

WARNING: This Read instance will throw an exception if used! It is only implemented because it is required to use HandleReader with Run in commands.

Instance details

Defined in Xmobar.Plugins.HandleReader

Show HandleReader Source # 
Instance details

Defined in Xmobar.Plugins.HandleReader

Exec HandleReader Source #

Asynchronously read from the Handle.

Instance details

Defined in Xmobar.Plugins.HandleReader

data QueueReader a Source #

A QueueReader displays data from an 'TQueue a' where the data items a are rendered by a user supplied function.

Like the HandleReader plugin this is only useful if you are running xmobar from other Haskell code. You should create a new TQueue a and pass it to this plugin.

main :: IO
main = do
  q <- STM.newQueueIO @String
  bar <- forkIO $ xmobar conf
    { commands = Run (QueueReader q id Queue) : commands conf }
  STM.atomically $ STM.writeTQueue q "Some Message"

Constructors

QueueReader 

Fields

Instances

Instances details
Read (QueueReader a) Source #

WARNING: This read instance will throw an exception if used! It is only implemented, because it is required by Run in commands.

Instance details

Defined in Xmobar.Plugins.QueueReader

Show (QueueReader a) Source #

This cannot be read back.

Instance details

Defined in Xmobar.Plugins.QueueReader

Exec (QueueReader a) Source #

Async queue/channel reading.

Instance details

Defined in Xmobar.Plugins.QueueReader

newtype Kbd Source #

Constructors

Kbd [(String, String)] 

Instances

Instances details
Read Kbd Source # 
Instance details

Defined in Xmobar.Plugins.Kbd

Show Kbd Source # 
Instance details

Defined in Xmobar.Plugins.Kbd

Methods

showsPrec :: Int -> Kbd -> ShowS #

show :: Kbd -> String #

showList :: [Kbd] -> ShowS #

Exec Kbd Source # 
Instance details

Defined in Xmobar.Plugins.Kbd

Methods

alias :: Kbd -> String Source #

rate :: Kbd -> Int Source #

run :: Kbd -> IO String Source #

start :: Kbd -> (String -> IO ()) -> IO () Source #

trigger :: Kbd -> (Maybe SignalType -> IO ()) -> IO () Source #

data Locks Source #

Constructors

Locks 

Instances

Instances details
Read Locks Source # 
Instance details

Defined in Xmobar.Plugins.Locks

Show Locks Source # 
Instance details

Defined in Xmobar.Plugins.Locks

Methods

showsPrec :: Int -> Locks -> ShowS #

show :: Locks -> String #

showList :: [Locks] -> ShowS #

Exec Locks Source # 
Instance details

Defined in Xmobar.Plugins.Locks

Methods

alias :: Locks -> String Source #

rate :: Locks -> Int Source #

run :: Locks -> IO String Source #

start :: Locks -> (String -> IO ()) -> IO () Source #

trigger :: Locks -> (Maybe SignalType -> IO ()) -> IO () Source #

Types

data MailItem Source #

A MailItem is a name, an address, and a query to give to notmuch.

Constructors

MailItem 

Fields

  • name :: String

    Display name for the item in the bar

  • address :: String

    Only check for mail sent to this address; may be the empty string to query all indexed mail instead

  • query :: String

    Query to give to notmuch search

Instances

Instances details
Read MailItem Source # 
Instance details

Defined in Xmobar.Plugins.NotmuchMail

Show MailItem Source # 
Instance details

Defined in Xmobar.Plugins.NotmuchMail

data NotmuchMail Source #

A full mail configuration.

Constructors

NotmuchMail 

Fields

type Args = [String] Source #

type Rate = Int Source #