Skip to content
This repository has been archived by the owner on Aug 7, 2019. It is now read-only.

lierdakil/xmonad-prime-monad

Folders and files

NameName
Last commit message
Last commit date

Latest commit

 

History

16 Commits
 
 
 
 
 
 
 
 
 
 
 
 
 
 

Repository files navigation

xmonad-prime-monad-0.1.0.0: True monadic config for XMonad Build Status

Copyright Nikolay Yakimov <[email protected]>
License BSD-style (see LICENSE)
Maintainer Nikolay Yakimov <[email protected]>
Stability unstable
Portability unportable
Safe Haskell None
Language Haskell2010

XMonad.Config.Prime.Monadic

Contents

  • Start here
  • Attributes you can set
  • Attributes you can add to
  • Attributes you can add to or remove from
  • Modifying the list of workspaces
  • Modifying the screen keybindings
  • Modifying the layoutHook
  • Updating the XConfig en masse
  • The rest of the world
  • Core
  • Example config
  • Troubleshooting

Description

This is a draft of a brand new config syntax for xmonad. It aims to be:

  • easier to copy/paste snippets from the docs
  • easier to get the gist for what's going on, for you imperative programmers

It's brand new, so it's pretty much guaranteed to break or change syntax. But what's the worst that could happen? Xmonad crashes and logs you out? It probably won't do that. Give it a try.

Synopsis

  • xmonad :: Prime -> IO ()
  • nothing :: Prime
  • normalBorderColor :: Settable String (XConfig l)
  • focusedBorderColor :: Settable String (XConfig l)
  • terminal :: Settable String (XConfig l)
  • modMask :: Settable KeyMask (XConfig l)
  • borderWidth :: Settable Dimension (XConfig l)
  • focusFollowsMouse :: Settable Bool (XConfig l)
  • clickJustFocuses :: Settable Bool (XConfig l)
  • class SettableClass s x y | s -> x y where
    • (=:) :: s c -> y -> Arr c
  • class UpdateableClass s x y | s -> x y where
    • (=.) :: s c -> (x -> y) -> Arr c
  • manageHook :: Summable ManageHook ManageHook (XConfig l)
  • handleEventHook :: Summable (Event -> X All) (Event -> X All) (XConfig l)
  • workspaces :: Summable [String] [String] (XConfig l)
  • logHook :: Summable (X ()) (X ()) (XConfig l)
  • startupHook :: Summable (X ()) (X ()) (XConfig l)
  • clientMask :: Summable EventMask EventMask (XConfig l)
  • rootMask :: Summable EventMask EventMask (XConfig l)
  • class SummableClass s y | s -> y where
    • (=+) :: s c -> y -> Arr c
  • keys :: Keys (XConfig l)
  • mouseBindings :: MouseBindings (XConfig l)
  • class RemovableClass r y | r -> y where
    • (=-) :: r c -> y -> Arr c
  • withWorkspaces :: Arr WorkspaceConfig -> Prime
  • wsNames :: Settable [String] WorkspaceConfig
  • wsKeys :: Summable [String] [String] WorkspaceConfig
  • wsActions :: Summable [(String, String -> X ())] [(String, String -> X ())] WorkspaceConfig
  • wsSetName :: Int -> String -> Arr WorkspaceConfig
  • withScreens :: IsLayout l Window => Arr ScreenConfig -> Prime
  • sKeys :: Summable [String] [String] ScreenConfig
  • sActions :: Summable [(String, ScreenId -> X ())] [(String, ScreenId -> X ())] ScreenConfig
  • onScreens :: Eq s => (i -> StackSet i l a s sd -> StackSet i l a s sd) -> s -> StackSet i l a s sd -> StackSet i l a s sd
  • addLayout :: IsLayout r Window => r Window -> Prime
  • resetLayout :: IsLayout r Window => r Window -> Prime
  • modifyLayout :: CC m Window => (forall l. LayoutClass l Window => l Window -> m l Window) -> Prime
  • squash :: S f t => (l a -> f a) -> l a -> t a
  • startWith :: IsLayout l Window => XConfig l -> Prime
  • apply :: (XConfig Layout -> XConfig Layout) -> Prime
  • apply' :: CC m Window => (forall l. LayoutClass l Window => XConfig l -> XConfig (m l)) -> Prime
  • squashXC :: S f t => (XConfig l -> XConfig f) -> XConfig l -> XConfig t
  • applyIO :: (XConfig Layout -> IO (XConfig Layout)) -> Prime
  • applyIO' :: CC m Window => (forall l. LayoutClass l Window => XConfig l -> IO (XConfig (m l))) -> Prime
  • squashIO :: S f t => (XConfig l -> IO (XConfig f)) -> XConfig l -> IO (XConfig t)
  • module XMonad
  • type Prime = Arr (XConfig Layout)
  • type Arr a = StateT a IO ()
  • class CC m a where
    • dict :: forall l. IsLayout l a => m l a -> Dict (IsLayout (m l) a)
  • data Dict :: Constraint -> * where
    • Dict :: a => Dict a

Start here

To start with, create a ~/.xmonad/xmonad.hs that looks like this:

import XMonad.Config.Prime.Monadic

-- Imports go here.

main = xmonad $ do
  nothing
  -- Configs go here.

This will give you a default xmonad install, with room to grow. The lines starting with double dashes are comments. You may delete them. Note that Haskell is a bit precise about indentation. Make sure all the statements in your do-block start at the same column, and make sure that any multi-line statements are formatted with a hanging indent. (For an example, see the 'keys =+' statement in the Example config section, below.)

After changing your config file, restart xmonad with mod-q (where, by default, "mod" == "alt").

xmonad :: Prime -> IO ()

This is the xmonad main function. It passes def (the default XConfig) into your do-block, takes the modified config out The do-block is a 'Prime. Advanced readers can skip right to that definition.

nothing :: Prime

This doesn't modify the config in any way. It's just here for your initial config because Haskell doesn't allow empty do-blocks. Feel free to delete it

Attributes you can set

These are a bunch of attributes that you can set. Syntax looks like this:

  terminal =: "urxvt"

Strings are double quoted, Dimensions are unquoted integers, booleans are True or False (case-sensitive), and modMask is usually mod1Mask or mod4Mask.

normalBorderColor :: Settable String (XConfig l)

Non-focused windows border color. Default: "#dddddd"

focusedBorderColor :: Settable String (XConfig l)

Focused windows border color. Default: "#ff0000"

terminal :: Settable String (XConfig l)

The preferred terminal application. Default: "xterm"

modMask :: Settable KeyMask (XConfig l)

The mod modifier, as used by key bindings. Default: mod1Mask (which is probably alt on your computer).

borderWidth :: Settable Dimension (XConfig l)

The border width (in pixels). Default: 1

focusFollowsMouse :: Settable Bool (XConfig l)

Whether window focus follows the mouse cursor on move, or requires a mouse click. (Mouse? What's that?) Default: True

clickJustFocuses :: Settable Bool (XConfig l)

If True, a mouse click on an inactive window focuses it, but the click is not passed to the window. If False, the click is also passed to the window. Default True

class SettableClass s x y | s -> x y where

Methods

(=:) :: s c -> y -> Arr c

This lets you modify an attribute.

Instances

UpdateableClass s x y => SettableClass s x y

class UpdateableClass s x y | s -> x y where

Methods

(=.) :: s c -> (x -> y) -> Arr c

This lets you apply a function to an attribute (i.e. read, modify, write).

Attributes you can add to

In addition to being able to set these attributes, they have a special syntax for being able to add to them. The operator is =+ (the plus comes after the equals), but each attribute has a different syntax for what comes after the operator.

manageHook :: Summable ManageHook ManageHook (XConfig l)

The action to run when a new window is opened. Default:

  manageHook =: composeAll [className =? "MPlayer" --> doFloat, className =? "Gimp" --> doFloat]

To add more rules to this list, you can say, for instance:

import XMonad.StackSet
...
  manageHook =+ (className =? "Emacs" --> doF kill)
  manageHook =+ (className =? "Vim" --> doF shiftMaster)

Note that operator precedence mandates the parentheses here.

handleEventHook :: Summable (Event -> X All) (Event -> X All) (XConfig l)

Custom X event handler. Return All True if the default handler should also be run afterwards. Default does nothing. To add an event handler:

import XMonad.Hooks.ServerMode
...
  handleEventHook =+ serverModeEventHook

workspaces :: Summable [String] [String] (XConfig l)

List of workspaces' names. Default: map show [1 .. 9 :: Int]. Adding appends to the end:

  workspaces =+ ["0"]

This is useless unless you also create keybindings for this.

logHook :: Summable (X ()) (X ()) (XConfig l)

The action to perform when the windows set is changed. This happens whenever focus change, a window is moved, etc. logHook =+ takes an X () and appends it via '(>>)'. For instance:

import XMonad.Hooks.ICCCMFocus
...
  logHook =+ takeTopFocus

Note that if your expression is parametrically typed (e.g. of type MonadIO m => m ()), you'll need to explicitly annotate it, like so:

  logHook =+ (io $ putStrLn "Hello, world!" :: X ())

startupHook :: Summable (X ()) (X ()) (XConfig l)

The action to perform on startup. startupHook =+ takes an X () and appends it via '(>>)'. For instance:

import XMonad.Hooks.SetWMName
...
  startupHook =+ setWMName "LG3D"

Note that if your expression is parametrically typed (e.g. of type MonadIO m => m ()), you'll need to explicitly annotate it, as documented in logHook.

clientMask :: Summable EventMask EventMask (XConfig l)

The client events that xmonad is interested in. This is useful in combination with handleEventHook. Default: structureNotifyMask .|. enterWindowMask .|. propertyChangeMask

  clientMask =+ keyPressMask .|. keyReleaseMask

rootMask :: Summable EventMask EventMask (XConfig l)

The root events that xmonad is interested in. This is useful in combination with handleEventHook. Default: substructureRedirectMask .|. substructureNotifyMask .|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask .|. buttonPressMask

class SummableClass s y | s -> y where

Methods

(=+) :: s c -> y -> Arr c infix 0

This lets you add to an attribute.

Attributes you can add to or remove from

The following support the the =+ for adding items and the =- operator for removing items.

keys :: Keys (XConfig l)

Key bindings to X actions. Default: see `man xmonad`. keys takes a list of keybindings specified emacs-style, as documented in mkKeyMap. For example, to change the "kill window" key:

  keys =- ["M-S-c"]
  keys =+ [("M-M1-x", kill)]

mouseBindings :: MouseBindings (XConfig l)

Mouse button bindings to an X actions on a window. Default: see `man xmonad`. To make mod-scrollwheel switch workspaces:

import XMonad.Actions.CycleWS (nextWS, prevWS)
...
  mouseBindings =+ [((mod4Mask, button4), const prevWS),
                    ((mod4Mask, button5), const nextWS)]

Note that you need to specify the numbered mod-mask e.g. mod4Mask instead of just modMask.

class RemovableClass r y | r -> y where

Methods

(=-) :: r c -> y -> Arr c infix 0

This lets you remove from an attribute.

Modifying the list of workspaces

Workspaces can be configured through workspaces, but then the keys need to be set, and this can be a bit laborious. withWorkspaces provides a convenient mechanism for common workspace updates.

withWorkspaces :: Arr WorkspaceConfig -> Prime

Configure workspaces through a Prime-like interface. Example:

  withWorkspaces $ do
    wsKeys =+ ["0"]
    wsActions =+ [("M-M1-", windows . swapWithCurrent)]
    wsSetName 1 "mail"

This will set workspaces and add the necessary keybindings to keys. Note that it won't remove old keybindings; it's just not that clever.

wsNames :: Settable [String] WorkspaceConfig

The list of workspace names, like workspaces but with two differences:

  1. If any entry is the empty string, it'll be replaced with the corresponding entry in wsKeys.
  2. The list is truncated to the size of wsKeys.

The default value is repeat "".

If you'd like to create workspaces without associated keyspecs, you can do that afterwards, outside the withWorkspaces block, with workspaces =+.

wsKeys :: Summable [String] [String] WorkspaceConfig

The list of workspace keys. These are combined with the modifiers in wsActions to form the keybindings for navigating to workspaces. Default: ["1","2",...,"9"].

wsActions :: Summable [(String, String -> X ())] [(String, String -> X ())] WorkspaceConfig

Mapping from key prefix to command. Its type is [(String, String -> X())]. The key prefix may be a modifier such as "M-", or a submap prefix such as "M-a ", or both, as in "M-a M-". The command is a function that takes a workspace name and returns an X (). withWorkspaces creates keybindings for the cartesian product of wsKeys and wsActions.

Default:

[("M-", windows . W.greedyView),
 ("M-S-", windows . W.shift)]

wsSetName :: Int -> String -> Arr WorkspaceConfig

A convenience for just modifying one entry in wsNames, in case you only want a few named workspaces. Example:

    wsSetName 1 "mail"
    wsSetName 2 "web"

Modifying the screen keybindings

withScreens provides a convenient mechanism to set keybindings for moving between screens, much like withWorkspaces.

withScreens :: IsLayout l Window => Arr ScreenConfig -> Prime

Configure screen keys through a Prime-like interface:

  withScreens $ do
    sKeys =: ["e", "r"]

This will add the necessary keybindings to keys. Note that it won't remove old keybindings; it's just not that clever.

sKeys :: Summable [String] [String] ScreenConfig

The list of screen keys. These are combined with the modifiers in sActions to form the keybindings for navigating to workspaces. Default: ["w","e","r"].

sActions :: Summable [(String, ScreenId -> X ())] [(String, ScreenId -> X ())] ScreenConfig

Mapping from key prefix to command. Its type is [(String, ScreenId -> X())]. Works the same as wsActions except for a different function type.

Default:

[("M-", windows . onScreens W.view),
 ("M-S-", windows . onScreens W.shift)]

onScreens :: Eq s => (i -> StackSet i l a s sd -> StackSet i l a s sd) -> s -> StackSet i l a s sd -> StackSet i l a s sd

Converts a stackset transformer parameterized on the workspace type into one parameterized on the screen type. For example, you can use onScreens W.view 0 to navigate to the workspace on the 0th screen. If the screen id is not recognized, the returned transformer acts as an identity function.

Modifying the layoutHook

Layouts are special. You can't modify them using the =: or =. operator. You need to use the following functions.

addLayout :: IsLayout r Window => r Window -> Prime

Add a layout to the list of layouts choosable with mod-space. For instance:

import XMonad.Layout.Tabbed
...
  addLayout simpleTabbed

resetLayout :: IsLayout r Window => r Window -> Prime

Reset the layoutHook from scratch. For instance, to get rid of the wide layout:

  resetLayout $ Tall 1 (3/100) (1/2) ||| Full

(The dollar is like an auto-closing parenthesis, so all the stuff to the right of it is treated like an argument to resetLayout.)

modifyLayout :: CC m Window => (forall l. LayoutClass l Window => l Window -> m l Window) -> Prime

Modify your layoutHook with some wrapper function. You probably want to call this after you're done calling addLayout.

Note that because of existential type in the Prime monad, modifyLayout can only accept modifiers that are instances of CC. This also entails that something like this will not work:

modifyLayout $ smartBorders . avoidStruts

You can use squash to make it work though:

modifyLayout $ squash $ smartBorders . avoidStruts

TL;DR -- apply modifiers separately, if you can.

Example:

import XMonad.Layout.NoBorders
...
  modifyLayout smartBorders

squash :: S f t => (l a -> f a) -> l a -> t a

Squashes a type m1 (m2 l) a into m3 l a. Use with modifyLayout if you need to apply it to function that adds more than one modifier to layout

Example:

let myLayoutFunction = Mirror . Mirror . Mirror . Mirror

modifyLayout $ squash $ myLayoutFunction

Updating the XConfig en masse

Finally, there are a few contrib modules that bundle multiple attribute updates together. There are three types: 1) wholesale replacements for the default config, 2) pure functions on the config, and 3) IO actions on the config. Each of those can also modify layout. The syntax for each is different. Examples:

  1. To start with a gnomeConfig instead of the default, we use startWith:

    import XMonad.Config.Gnome ... startWith gnomeConfig

  2. withUrgencyHook is a pure function, so we need to use apply:

    import XMonad.Hooks.UrgencyHook ... apply $ withUrgencyHook dzenUrgencyHook

  3. fullscreenSupport is a pure function, but it also applies a modifier to layout. In this case we need to use apply':

    import XMonad.Layout.Fullscreen ... apply' fullscreenSupport

  4. xmobar returns an IO (XConfig (ModifiedLayout AvoidStruts l)), so we need to use applyIO':

    import XMonad.Hooks.DynamicLog ... applyIO' xmobar

startWith :: IsLayout l Window => XConfig l -> Prime

Replace the current XConfig with the given one. If you use this, you probably want it to be the first line of your config.

apply :: (XConfig Layout -> XConfig Layout) -> Prime

Turns a pure function on XConfig into a 'Prime.

apply' :: CC m Window => (forall l. LayoutClass l Window => XConfig l -> XConfig (m l)) -> Prime

Turns a pure function on XConfig into a 'Prime. This version also accepts functions that change layout. Use squashXC for functions adding more than one layout modifier:

apply' $ squashXC myFunction

squashXC :: S f t => (XConfig l -> XConfig f) -> XConfig l -> XConfig t

Same as squash, but acts on XConfig. Use with apply'.

Example:

let myLayoutFunction x = mirror $ mirror $ mirror $ mirror $ x
    mirror xc = xc{X.layoutHook = Mirror $ X.layoutHook xc}

apply $ squashXC $ myLayoutFunction

applyIO :: (XConfig Layout -> IO (XConfig Layout)) -> Prime

Turns an IO function on XConfig into a 'Prime.

applyIO' :: CC m Window => (forall l. LayoutClass l Window => XConfig l -> IO (XConfig (m l))) -> Prime

Turns an IO function on XConfig into a 'Prime. This version also accepts functions that change layout. Use squashIO for functions adding more than one layout modifier:

applyIO' $ squashIO myFunction

squashIO :: S f t => (XConfig l -> IO (XConfig f)) -> XConfig l -> IO (XConfig t)

Same as squashXC, but for IO functions. Use with applyIO'

Example:

let myLayoutFunction x = return $ mirror $ mirror $ mirror $ mirror $ x
    mirror xc = xc{X.layoutHook = Mirror $ X.layoutHook xc}

applyIO $ squashIO $ myLayoutFunction

The rest of the world

Everything you know and love from the core XMonad module is available for use in your config file, too.

module XMonad

Core

These are the building blocks on which the config language is built. Regular people shouldn't need to know about these.

type Prime = Arr (XConfig Layout)

A Prime is a state monad that incapsulates an XConfig. It wraps layouts into an existential type.

type Arr a = StateT a IO ()

An Arr is a generalization of Prime. Don't reference the type, if you can avoid it. It might go away in the future.

class CC m a where

Typeclass used to prove that there is actually a layout inside Layout.

All layout modifiers like Mirror must be instances of this class. Most instances should be already defined. If not, in most cases you can define one with

instance CC Mod a where dict _ = Dict

Where Mod is your modifier.

All modifiers that are instances of LayoutModifier are automatically instances of CC.

Methods

dict :: forall l. IsLayout l a => m l a -> Dict (IsLayout (m l) a)

Instances

CC Mirror a
CC WithID a
IsLayout l a => CC (Choose l) a
IsLayout l a => CC (NewSelect l) a
(IsLayout l a, Show a) => CC (OnHost l) a
Message m => CC (Ignore m) a
LayoutModifier m a => CC (ModifiedLayout m) a
IsLayout l a => CC (ToggleLayouts l) a
IsLayout l a => CC (IfMax l) a
(Eq a, Read a, Show a, Typeable * a, IsLayout l a) => CC (LayoutN l) a
(Read b, Show b, Typeable * a, HList b a) => CC (MultiToggle b) a
(IsLayout l a, Show a) => CC (PerScreen l) a
(IsLayout l a, Show a) => CC (PerWorkspace l) a
(IsLayout l (), IsLayout l1 Window, IsLayout l2 Window) => CC (CombineTwoP (l ()) l1) Window
(IsLayout l (), IsLayout l1 a, Read a, Show a, Eq a, Typeable * a) => CC (CombineTwo (l ()) l1) a
(IsLayout l a, Show a, Eq a, Read b, Read a, Show b, Typeable * a, Predicate b a) => CC (LayoutP b l) a

data Dict :: Constraint -> * where

Constructors

Dict :: a => Dict a

Example config

As an example, I've included below a subset of my current config. Note that my import statements specify individual identifiers in parentheticals. That's optional. The default is to import the entire module. I just find it helpful to remind me where things came from.

import XMonad.Config.Prime

import XMonad.Actions.CycleWS (prevWS, nextWS)
import XMonad.Actions.SwapWorkspaces (swapWithCurrent)
import XMonad.Actions.WindowNavigation (withWindowNavigation)
import XMonad.Layout.Fullscreen (fullscreenSupport)
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Layout.Tabbed (simpleTabbed)

main = xmonad $ do
  modMask =: mod4Mask
  normalBorderColor =: "#222222"
  terminal =: "urxvt"
  focusFollowsMouse =: False
  resetLayout $ Tall 1 (3/100) (1/2) ||| simpleTabbed
  modifyLayout smartBorders
  apply fullscreenSupport
  applyIO' $ withWindowNavigation (xK_w, xK_a, xK_s, xK_d)
  withWorkspaces $ do
    wsKeys =+ ["0"]
    wsActions =+ [("M-M1-", windows . swapWithCurrent)]
  keys =+ [
      ("M-,",                      sendMessage $ IncMasterN (-1)),
      ("M-.",                      sendMessage $ IncMasterN 1),
      ("M-M1-d",                   spawn "date | dzen2 -fg '#eeeeee' -p 2"),
      ("C-S-q",                    return ()),
      ("<XF86AudioLowerVolume>",   spawn "amixer set Master 5%-"),
      ("<XF86AudioRaiseVolume>",   spawn "amixer set Master 5%+"),
      ("M-M1-x",                   kill),
      ("M-i",                      prevWS),
      ("M-o",                      nextWS)
    ]

Troubleshooting

How do I use the old keyboard syntax?

You can use apply and supply your own Haskell function. For instance:

apply $ flip additionalKeys $ [((mod1Mask, xK_z), spawn "date | dzen2 -fg '#eeeeee' -p 2")]

How do I run a command before xmonad starts (like spawnPipe)?

If you're using it for a status bar, see if dzen or xmobar does what you want. If so, you can apply it with applyIO.

If not, you can write your own XConfig l -> IO (XConfig l) and apply it with applyIO.

Alternatively, you could do something like this this:

import qualified Prelude as P (>>)

main =
  openFile ".xmonad.log" AppendMode >>= \log ->
  hSetBuffering log LineBuffering P.>>
  (xmonad $ do
     nothing -- Prime config here.
  )

Produced by Haddock version 2.16.1

About

Monadic XMonad config

Resources

License

Stars

Watchers

Forks

Releases

No releases published

Packages

No packages published