[xmonad] XMonad.Config.Prime, a monadic config syntax
Brent Yorgey
byorgey at seas.upenn.edu
Mon Oct 1 20:31:43 CEST 2012
Just looking at the Haddocks, I like it very much!
Can you say a bit more about exactly why TH is required? I get that
fclabels depends on it, but why do you have to turn on the
TemplateHaskell flag in your xmonad config? (I haven't actually
looked at the code.)
I'm a bit wary of adding a TH dep, but for a different reason than
what others have said. TH versions are tied tightly to the changing
Haskell syntax supported by different releases of GHC, so in theory a
TH dep makes it harder to have a package that works under a wide range
of GHC (and hence TH) versions. I don't know how much of a problem
this is in practice.
-Brent
On Sun, Sep 23, 2012 at 11:36:58PM -0700, Devin Mullins wrote:
> Hello, folks. Loooong time no see. I had some free time and spare energy this
> weekend, and this one had always been curiousing me. A couple things:
>
> 1. I `darcs rec`d with --no-test, since Minimize was complaining about a
> shadowed identifier.
>
> 2. This adds new build deps on fclabels and template-haskell. I know y'all are
> generally fairly conservative on new deps. What do you think?
>
> 3. Here's a live copy of the haddock doc:
> http://twifkak.com/xmonad-junk/XMonad-Config-Prime.html
>
> Sun Sep 23 22:57:31 PDT 2012 Devin Mullins <me at twifkak.com>
> * XMonad.Config.Prime, a monadic config syntax
> This is an attempt at a cleaner and more modular config syntax, a follow up to
> http://thread.gmane.org/gmane.comp.lang.haskell.xmonad/5398. (Hello, everybody!
> How have the last four years been?)
>
> FAQ:
>
> Why fclabels instead of data-lens?
> Of the two, it was the one that successfully compiled on my ancient Ubuntu
> Lucid machine when I ran `cabal install`.
>
> Ick, template-haskell? Really?
> Yeah, I know. Unfortunately, it seems that GHC won't let me write:
> > data L = forall l. L l
> > g f (L l) = L (f l)
> so I can't really make a generic Layout transformer. I spent a few minutes
> heading down the path of parameterized monads and NoImplicitPrelude, but the
> type-system mind games and the juggling between (Prelude.>>) for IO and
> (Control.Monad.Parameterized.>>) for state were melting my brain.
>
> Sun Sep 23 23:20:20 PDT 2012 Devin Mullins <me at twifkak.com>
> * minor tweaks to X.C.Prime
>
>
> [XMonad.Config.Prime, a monadic config syntax
> Devin Mullins <me at twifkak.com>**20120924055731
> Ignore-this: e5d7c999a892d2eb8447de692edec708
> This is an attempt at a cleaner and more modular config syntax, a follow up to
> http://thread.gmane.org/gmane.comp.lang.haskell.xmonad/5398. (Hello, everybody!
> How have the last four years been?)
>
> FAQ:
>
> Why fclabels instead of data-lens?
> Of the two, it was the one that successfully compiled on my ancient Ubuntu
> Lucid machine when I ran `cabal install`.
>
> Ick, template-haskell? Really?
> Yeah, I know. Unfortunately, it seems that GHC won't let me write:
> > data L = forall l. L l
> > g f (L l) = L (f l)
> so I can't really make a generic Layout transformer. I spent a few minutes
> heading down the path of parameterized monads and NoImplicitPrelude, but the
> type-system mind games and the juggling between (Prelude.>>) for IO and
> (Control.Monad.Parameterized.>>) for state were melting my brain.
> ] {
> addfile ./XMonad/Config/Prime.hs
> hunk ./XMonad/Config/Prime.hs 1
> +{-# LANGUAGE ExistentialQuantification, FlexibleContexts, FlexibleInstances, FunctionalDependencies, MultiParamTypeClasses, TemplateHaskell, TypeOperators, TypeSynonymInstances #-}
> +
> +-----------------------------------------------------------------------------
> +-- |
> +-- Module : XMonad.Config.Prime
> +-- Copyright : Devin Mullins <me at twifkak.com>
> +-- License : BSD-style (see LICENSE)
> +--
> +-- Maintainer : Devin Mullins <me at twifkak.com>
> +-- Stability : unstable
> +-- Portability : unportable
> +--
> +-- 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?
> +-- Give it a try. Start at the /Start here/ section.
> +--
> +-----------------------------------------------------------------------------
> +
> +-- monads, lenses, dsls, oh my!
> +module XMonad.Config.Prime (
> +-- * Start here
> +-- $start_here
> +xmonad,
> +nothing,
> +
> +-- * Attributes you can set
> +-- $settables
> +normalBorderColor,
> +focusedBorderColor,
> +terminal,
> +modMask,
> +borderWidth,
> +focusFollowsMouse,
> +(=:),
> +-- | This lets you set an attribute.
> +(=.),
> +-- | This lets you apply a function to an attribute (i.e. read, modify, write).
> +
> +-- * Attributes you can add to
> +-- $summables
> +keys,
> +mouseBindings,
> +manageHook,
> +handleEventHook,
> +workspaces,
> +logHook,
> +startupHook,
> +(=+),
> +
> +-- * Modifying the layoutHook
> +-- $layout
> +addLayout,
> +modifyLayout,
> +resetLayout,
> +layoutHook,
> +
> +-- * Update entire XConfig
> +-- $update
> +modify,
> +update,
> +
> +-- * The rest of XMonad
> +-- | Everything you know and love from the core "XMonad" is available for use in
> +-- your config file, too.
> +module XMonad,
> +
> +-- * Example config
> +-- $example
> +
> +-- * Devel stuff
> +-- | People wanting to implement extensions to the config system, or just play
> +-- around, might want access to these. Regular people shouldn't need them.
> +Prime,
> +getConfig,
> +Summable,
> +) where
> +
> +import Control.Monad.State.Lazy (StateT, execStateT)
> +import qualified Data.Map as M
> +import Data.Label (lens, (:->))
> +import Data.Label.PureM ((=:), (=.), gets)
> +import Data.Monoid (All, Monoid, mappend)
> +import Language.Haskell.TH (Exp, Q)
> +
> +import XMonad hiding (xmonad, XConfig(..), gets)
> +import XMonad (XConfig(XConfig))
> +import qualified XMonad as X (xmonad, XConfig(..))
> +
> +import XMonad.Util.EZConfig (additionalKeysP, additionalMouseBindings)
> +
> +-- $start_here
> +-- To start with, have a @~\/.xmonad\/xmonad.hs@ that looks like this:
> +--
> +-- > {-# LANGUAGE TemplateHaskell #-}
> +-- >
> +-- > import XMonad.Config.Prime
> +-- >
> +-- > -- 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 indented further on the subsequent lines. (For an example,
> +-- see the 'keys' statement in the /Example config/ section, below.)
> +
> +--
> +-- The Prime Monad
> +--
> +
> +-- | As you can see, this is a 'StateT' 'IO'. You can weave IO into your config
> +-- modification. Note that it's an 'XConfig' 'Layout' -- you'll have to unwrap
> +-- the existential to do anything useful to the layout.
> +type Prime = StateT (XConfig Layout) IO ()
> +
> +wrapConf :: (LayoutClass l Window, Read (l Window)) => XConfig l -> XConfig Layout
> +wrapConf conf = conf { X.layoutHook = Layout $ X.layoutHook conf }
> +
> +defaultConf :: XConfig Layout
> +defaultConf = wrapConf defaultConfig
> +
> +-- | This is the xmonad main function. It passes defaultConfig to your
> +-- do-block, takes the modified config out of your do-block, and runs xmonad.
> +--
> +-- The do-block is a 'Prime' monad. Advanced readers can skip right to that
> +-- definition.
> +xmonad :: Prime -> IO ()
> +xmonad prime = do
> + conf at XConfig { X.layoutHook = Layout l } <- getConfig prime
> + X.xmonad conf { X.layoutHook = l }
> +
> +-- | 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
> +-- once you've added other stuff.
> +nothing :: Prime
> +nothing = return ()
> +
> +-- $settables
> +-- 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'.
> +
> +-- | Non-focused windows border color. Default: @\"#dddddd\"@
> +normalBorderColor :: XConfig Layout :-> String
> +normalBorderColor = lens X.normalBorderColor (\x c -> c { X.normalBorderColor = x })
> +
> +-- | Focused windows border color. Default: @\"#ff0000\"@
> +focusedBorderColor :: XConfig Layout :-> String
> +focusedBorderColor = lens X.focusedBorderColor (\x c -> c { X.focusedBorderColor = x })
> +
> +-- | The preferred terminal application. Default: @\"xterm\"@
> +terminal :: XConfig Layout :-> String
> +terminal = lens X.terminal (\x c -> c { X.terminal = x })
> +
> +-- | The mod modifier, as used by key bindings. Default: @mod1Mask@ (which is
> +-- probably alt on your computer).
> +modMask :: XConfig Layout :-> KeyMask
> +modMask = lens X.modMask (\x c -> c { X.modMask = x })
> +
> +-- | The border width (in pixels). Default: @1@
> +borderWidth :: XConfig Layout :-> Dimension
> +borderWidth = lens X.borderWidth (\x c -> c { X.borderWidth = x })
> +
> +-- | Whether window focus follows the mouse cursor on move, or requires a mouse
> +-- click. (Mouse? What's that?) Default: @True@
> +focusFollowsMouse :: XConfig Layout :-> Bool
> +focusFollowsMouse = lens X.focusFollowsMouse (\x c -> c { X.focusFollowsMouse = x })
> +
> +-- $summables
> +-- 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.
> +
> +-- | 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:
> +--
> +-- > manageHook =+ (className =? "Emacs" --> doF . kill =<< ask)
> +-- > manageHook =+ (className =? "Vim" --> doF . shiftMaster =<< ask)
> +--
> +-- Note that operator precedence mandates the parentheses here.
> +manageHook :: XConfig Layout :-> ManageHook
> +manageHook = lens X.manageHook (\x c -> c { X.manageHook = x })
> +
> +-- | 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
> +-- > ...
> +-- > manageHook =+ serverModeEventHook
> +handleEventHook :: XConfig Layout :-> (Event -> X All)
> +handleEventHook = lens X.handleEventHook (\x c -> c { X.handleEventHook = x })
> +
> +-- | 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.
> +workspaces :: XConfig Layout :-> [String]
> +workspaces = lens X.workspaces (\x c -> c { X.workspaces = x })
> +
> +-- TODO: Rework the workspaces thing to pair names with keybindings.
> +
> +-- | Map from key presses to actions. Default: see `man xmonad`. @keys +=@
> +-- takes a list of keybindings specified emacs-style, as documented in
> +-- 'XMonad.Util.EZConfig.mkKeyMap'. For example, to add a help button to
> +-- XMonad:
> +--
> +-- > keys += [("<F1>", spawn "echo RTFS | dzen2 -p 2")]
> +keys :: XConfig Layout :-> (XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
> +keys = lens X.keys (\x c -> c { X.keys = x })
> +
> +-- | Map from button presses to actions. Default: see `man xmonad`. To make
> +-- mod-<scrollwheel> switch workspaces:
> +--
> +-- > import XMonad.Actions.CycleWS (nextWS, prevWS)
> +-- > ...
> +-- > mouseBindings =+ [((mod4Mask, button4), prevWS),
> +-- > ((mod4Mask, button5), nextWS)]
> +--
> +-- Note that you need to specify the numbered mod-mask e.g. 'mod4Mask' instead
> +-- of just 'modMask'.
> +mouseBindings :: XConfig Layout :-> (XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ()))
> +mouseBindings = lens X.mouseBindings (\x c -> c { X.mouseBindings = x })
> +
> +-- TODO: Fix the need to specify mod4Mask instead of modMask? Does anybody care?
> +
> +-- | 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
> +logHook :: XConfig Layout :-> X ()
> +logHook = lens X.logHook (\x c -> c { X.logHook = x })
> +
> +-- | The action to perform on startup. @startupHook =+@ takes an @X ()@ and
> +-- appends it via '(>>)'. For instance:
> +--
> +-- > import XMonad.Hooks.SetWMName
> +-- > ...
> +-- > startupHook =+ setWMName "LG3D"
> +startupHook :: XConfig Layout :-> X ()
> +startupHook = lens X.startupHook (\x c -> c { X.startupHook = x })
> +
> +-- The Summable class and instance definitions are further down.
> +
> +-- $layout
> +-- Layouts are special. Theoretically, you can use the @=:@ and @=.@ syntax to
> +-- set them, but I'm not sure you want to. There's some cruft involved. The
> +-- following macros make it a little nicer:
> +
> +-- (Stupid existential quantification. Make me write ridiculous code like this.)
> +
> +-- | Add a layout to the list of layouts choosable with mod-space. For instance:
> +--
> +-- > import XMonad.Layout.Tabbed
> +-- > ...
> +-- > $(addLayout [| simpleTabbed |])
> +addLayout :: Q Exp -> Q Exp
> +addLayout qexp = [| layoutHook =. (\(Layout l) -> Layout (l ||| $qexp)) |]
> +
> +-- | Modify your 'layoutHook' with some wrapper function. You probably want to call
> +-- this after you're done calling 'addLayout'. Example:
> +--
> +-- > import XMonad.Layout.NoBorders
> +-- > ...
> +-- > $(modifyLayout [| smartBorders |])
> +modifyLayout :: Q Exp -> Q Exp
> +modifyLayout qexp = [| layoutHook =. (\(Layout l) -> Layout ($qexp l)) |]
> +
> +-- | Reset the layoutHook from scratch. For instance, to get rid of the wide
> +-- layout:
> +--
> +-- > $(resetLayout [| Tall 1 (3/100) (1/2) ||| Full |])
> +resetLayout :: Q Exp -> Q Exp
> +resetLayout qexp = [| layoutHook =: Layout $qexp |]
> +
> +layoutHook :: XConfig Layout :-> Layout Window
> +layoutHook = lens X.layoutHook (\x c -> c { X.layoutHook = x })
> +
> +-- $update
> +-- Finally, there are a few contrib modules that bundle multiple attribute
> +-- updates up into functions that update the entire configuration. You can use
> +-- 'modify' or 'update' to wire them into this config syntax. Which one
> +-- depends on whether or not the IO monad is involved.
> +--
> +-- For instance, 'XMonad.Hooks.UrgencyHook.withUrgencyHook' returns an @XConfig
> +-- l@, so we need to use 'modify':
> +--
> +-- > import XMonad.Hooks.UrgencyHook
> +-- > ...
> +-- > modify $ withUrgencyHook dzenUrgencyHook
> +--
> +-- On the other hand, 'XMonad.Hooks.DynamicLog.xmobar' returns an @IO (XConfig
> +-- l)@, so we need to use 'update':
> +--
> +-- > import XMonad.Actions.WindowNavigation
> +-- > ...
> +-- > update $ xmobar
> +--
> +-- (Haskellers will note that the dollar sign is not actually necessary in this
> +-- case, but it doesn't hurt. The dollar sign is like an auto-closing
> +-- parenthesis.)
> +
> +update :: (XConfig Layout -> IO (XConfig Layout)) -> Prime
> +update f = get >>= io . f >>= put
> +
> +-- | Returns the modified config file resulting from passing 'defaultConfig' to
> +-- the 'Prime'. Implementing a 'Show' instance for 'XConfig' 'Layout' is left
> +-- as an exercise for the reader.
> +getConfig :: Prime -> IO (XConfig Layout)
> +getConfig m = execStateT m defaultConf
> +
> +--
> +-- Summables
> +--
> +
> +-- | The class for summable things. If you want to invent new summable
> +-- attributes, here's what you use.
> +class Summable a b | a -> b where
> + -- | How you add to a summable.
> + (=+) :: a -> b -> Prime
> + infix 0 =+
> +
> +instance Summable (XConfig Layout :-> (XConfig Layout -> M.Map (ButtonMask,KeySym) (X ())))
> + [(String, X ())] where
> + _ =+ newKeys = modify (`additionalKeysP` newKeys)
> +
> +instance Summable (XConfig Layout :-> (XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())))
> + [((ButtonMask, Button), Window -> X ())] where
> + _ =+ newMouseBindings = modify (`additionalMouseBindings` newMouseBindings)
> +
> +instance Summable (XConfig Layout :-> ManageHook) ManageHook where
> + l =+ new = l =. (<+> new)
> +
> +instance Summable (XConfig Layout :-> (Event -> X All)) (Event -> X All) where
> + l =+ new = do
> + old <- gets l
> + l =: \evt -> old evt `mappend` new evt
> +
> +instance Summable (XConfig Layout :-> [String]) [String] where
> + l =+ new = l =. (++ new)
> +
> +instance Summable (XConfig Layout :-> X ()) (X ()) where
> + l =+ new = l =. (>> new)
> +
> +-- $example
> +-- 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.
> +--
> +-- > {-# LANGUAGE TemplateHaskell #-}
> +-- >
> +-- > import XMonad.Config.Prime
> +-- >
> +-- > import XMonad.Actions.CycleWS (nextWS, prevWS)
> +-- > import XMonad.Actions.WindowNavigation (withWindowNavigation)
> +-- > import XMonad.Hooks.ManageHelpers (doFullFloat, isFullscreen)
> +-- > import XMonad.Layout.NoBorders (smartBorders)
> +-- > import XMonad.Prompt (defaultXPConfig, XPConfig(position), XPPosition(Top))
> +-- > import XMonad.Prompt.Shell (shellPrompt)
> +-- >
> +-- > main = xmonad $ do
> +-- > modMask =: mod4Mask
> +-- > normalBorderColor =: "#222222"
> +-- > terminal =: "urxvt"
> +-- > manageHook =+ (isFullscreen --> doFullFloat)
> +-- > $(modifyLayout [| smartBorders |])
> +-- > focusFollowsMouse =: False
> +-- > update $ withWindowNavigation (xK_w, xK_a, xK_s, xK_d)
> +-- > keys =+ [
> +-- > ("M-.", sendMessage (IncMasterN 1)),
> +-- > ("M-,", sendMessage (IncMasterN (-1))),
> +-- > ("M-p", shellPrompt defaultXPConfig { position = Top }),
> +-- > ("M-i", prevWS),
> +-- > ("M-o", nextWS),
> +-- > ("C-S-q", return ()),
> +-- > ("<XF86AudioLowerVolume>", spawn "amixer set Master 5%-"),
> +-- > ("<XF86AudioRaiseVolume>", spawn "amixer set Master unmute 5%+"),
> +-- > ("XF86AudioMute", spawn "amixer set Master toggle") ]
> hunk ./xmonad-contrib.cabal 64
> extensions: ForeignFunctionInterface
> cpp-options: -DXFT
>
> - build-depends: mtl >= 1 && < 3, unix, X11>=1.6 && < 1.7, xmonad>=0.10.1 && < 0.11, utf8-string
> + build-depends: mtl >= 1 && < 3, unix, X11>=1.6 && < 1.7, xmonad>=0.10.1 && < 0.11, utf8-string,
> + fclabels, template-haskell
>
> if true
> ghc-options: -fwarn-tabs -Wall
> hunk ./xmonad-contrib.cabal 146
> XMonad.Config.Droundy
> XMonad.Config.Gnome
> XMonad.Config.Kde
> + XMonad.Config.Prime
> XMonad.Config.Sjanssen
> XMonad.Config.Xfce
> XMonad.Hooks.CurrentWorkspaceOnTop
> }
> [minor tweaks to X.C.Prime
> Devin Mullins <me at twifkak.com>**20120924062020
> Ignore-this: 367385e5c3612f3bcdb7e28acad42513
> ] {
> hunk ./XMonad/Config/Prime.hs 87
> import Control.Monad.State.Lazy (StateT, execStateT)
> import qualified Data.Map as M
> import Data.Label (lens, (:->))
> -import Data.Label.PureM ((=:), (=.), gets)
> -import Data.Monoid (All, Monoid, mappend)
> +import Data.Label.PureM ((=:), (=.))
> +import Data.Monoid (All)
> import Language.Haskell.TH (Exp, Q)
>
> hunk ./XMonad/Config/Prime.hs 91
> -import XMonad hiding (xmonad, XConfig(..), gets)
> +import XMonad hiding (xmonad, XConfig(..), gets, modify)
> import XMonad (XConfig(XConfig))
> hunk ./XMonad/Config/Prime.hs 93
> -import qualified XMonad as X (xmonad, XConfig(..))
> +import qualified XMonad as X
>
> import XMonad.Util.EZConfig (additionalKeysP, additionalMouseBindings)
>
> hunk ./XMonad/Config/Prime.hs 317
> -- On the other hand, 'XMonad.Hooks.DynamicLog.xmobar' returns an @IO (XConfig
> -- l)@, so we need to use 'update':
> --
> --- > import XMonad.Actions.WindowNavigation
> +-- > import XMonad.Hooks.DynamicLog
> -- > ...
> -- > update $ xmobar
> --
> hunk ./XMonad/Config/Prime.hs 325
> -- case, but it doesn't hurt. The dollar sign is like an auto-closing
> -- parenthesis.)
>
> +modify :: (MonadState s m) => (s -> s) -> m ()
> +modify = X.modify
> +
> update :: (XConfig Layout -> IO (XConfig Layout)) -> Prime
> update f = get >>= io . f >>= put
>
> hunk ./XMonad/Config/Prime.hs 360
> l =+ new = l =. (<+> new)
>
> instance Summable (XConfig Layout :-> (Event -> X All)) (Event -> X All) where
> - l =+ new = do
> - old <- gets l
> - l =: \evt -> old evt `mappend` new evt
> + l =+ new = l =. (<+> new)
>
> instance Summable (XConfig Layout :-> [String]) [String] where
> l =+ new = l =. (++ new)
> }
>
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad
More information about the xmonad
mailing list