xmobar-0.29: A Minimalistic Text Based Status Bar

Copyright(c) 2011 2012 2013 2014 2015 2017 2018 Jose Antonio Ortega Ruiz
(c) 2007 Andrea Rossato
LicenseBSD-style (see LICENSE)
MaintainerJose A. Ortega Ruiz <jao@gnu.org>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell98

Xmobar

Contents

Description

A status bar for the Xmonad Window Manager

Synopsis

Documentation

defaultConfig :: Config Source #

The default configuration values

data Runnable Source #

Constructors

(Exec r, Read r, Show r) => Run r 
Instances
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

Methods

alias :: Runnable -> String Source #

rate :: Runnable -> Int Source #

run :: Runnable -> IO String Source #

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

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

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
Exec Runnable Source # 
Instance details

Defined in Xmobar.Run.Runnable

Methods

alias :: Runnable -> String Source #

rate :: Runnable -> Int Source #

run :: Runnable -> IO String Source #

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

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

Exec Monitors Source # 
Instance details

Defined in Xmobar.Plugins.Monitors

Methods

alias :: Monitors -> String Source #

rate :: Monitors -> Int Source #

run :: Monitors -> IO String Source #

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

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

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 PipeReader Source # 
Instance details

Defined in Xmobar.Plugins.PipeReader

Methods

alias :: PipeReader -> String Source #

rate :: PipeReader -> Int Source #

run :: PipeReader -> IO String Source #

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

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

Exec CommandReader Source # 
Instance details

Defined in Xmobar.Plugins.CommandReader

Exec BufferedPipeReader Source # 
Instance details

Defined in Xmobar.Plugins.BufferedPipeReader

Exec StdinReader Source # 
Instance details

Defined in Xmobar.Plugins.StdinReader

Methods

alias :: StdinReader -> String Source #

rate :: StdinReader -> Int Source #

run :: StdinReader -> IO String Source #

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

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

Exec XMonadLog Source # 
Instance details

Defined in Xmobar.Plugins.XMonadLog

Methods

alias :: XMonadLog -> String Source #

rate :: XMonadLog -> Int Source #

run :: XMonadLog -> IO String Source #

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

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

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 #

Configuration

Configuration data type

data Config Source #

The configuration data type

Constructors

Config 

Fields

data Align Source #

Constructors

L 
R 
C 
Instances
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

data Border Source #

Instances
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

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
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
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 #

newtype Kbd Source #

Constructors

Kbd [(String, String)] 
Instances
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
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 #

type Args = [String] Source #

type Rate = Int Source #