xmonad-windownames-0.1.0.1: A library to automatically put named windows into the DynamicLog.

Copyright(c) 2015 Phil Lindberg <plindbe2@gmail.com>
LicenseBSD3-style (see LICENSE)
MaintainerPhil Lindberg <plindbe2@gmail.com>
Stabilityexperimental
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

XMonad.Actions.WindowNames

Contents

Description

A library to automatically put named windows into the DynamicLog. It provides a modification of dynamicLogWithPP and some helper functions.

Synopsis

Usage

You can add this to your ~/.xmonad/xmonad.hs:

   import Data.List (isSuffixOf)
   import System.IO
   import WindowNames
   import XMonad
   import XMonad.Hooks.DynamicLog
   import XMonad.Util.Run(spawnPipe)

A simple example is a follows (the example uses xmobar but feel free to substitute dzen or anything else):

myShortNames :: [(String -> Bool, String -> String)]
myShortNames = [ (("Pentadactyl" `isSuffixOf`), const "ff"  )
               , ((=="Library"),                const "ffdl")
               , (const True,                   take 4      ) -- catch all
               ]

main = do
    h <- spawnPipe "xmobar -options -foo -bar"
    xmonad $ myXmonadConfig h

myXmonadConfig h = defaultConfig {
  ...
  logHook = dynamicLogWithPPMap (getWindowNames (foc . filt) filt filt) xmobarPP { ppOutput = hPutStrLn h }
  ...
}
 where foc  = wrap "<fn=1>" "</fn>" -- xmobar font 1 (additionalFonts!!0)
       filt = filterShortNames myShortNames

This works nicely with named tmux sessions or screens. You can use it in conjunction with other dynamicLog string modifiers.

Modified dynamic log functions

dynamicLogStringMap :: (WindowSet -> X (Map WorkspaceId String)) -> PP -> X String Source

Modifed dynamicLogString which takes an additional WindowSet to Map of WorkspaceId to String.

dynamicLogWithPPMap :: (WindowSet -> X (Map WorkspaceId String)) -> PP -> X () Source

Modified dynamicLogWithPP which takes an additional WindowSet to Map of WorkspaceId to String.

Helper functions

evalLookup :: MonadPlus m => a -> [(a -> Bool, a -> b)] -> m b Source

Helper function used by filterShortNames which run the first function in the tuple on the value. If it evalutes to true, the output of the second function if returned.

filterShortNames :: [(String -> Bool, String -> String)] -> String -> String Source

Example filter short name function.

Stack and StackSet functions

getTagStack :: StackSet t l a sid sd -> [(t, Maybe (Stack a))] Source

Get a list of tag and maybe Stack.

getWindowNames Source

Arguments

:: (String -> String)

Function to apply to the focused window's name.

-> (String -> String)

Function to apply to the up windows' names.

-> (String -> String)

Function to apply to the down windows' names.

-> StackSet WorkspaceId l Window sid sd

Stack set

-> X (Map WorkspaceId String) 

Get a Map of window tag to strings in the format "wsId:w1,w2,...,wN" where w1,...,wn represent the names of windows according to getName after being run through the respective focus, up, and down functions

integrateM Source

Arguments

:: Monad m 
=> (a -> m b)

Monadic function to run on focused components.

-> (a -> m b)

Monadic function to run on up components.

-> (a -> m b)

Monadic function to run on down components.

-> Stack a

Current StackSet

-> m [b] 

Run a monadic function on Stack components.

Pretty-printer functions

pprWindowSetMap Source

Arguments

:: (WindowSet -> X (Map WorkspaceId String))

Map of WorkspaceId to a string to be displayed.

-> WorkspaceSort

A workspace sorting function

-> [Window]

A list of urgent windows

-> PP

pretty-printer format

-> WindowSet

current WindowSet

-> X String 

Format the workspace information

To Do

  • Incorporate with TagWindows
  • Efficiency (ExtensionClass?)
  • Make sure it works with the newest XMonad