aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAlex Tarkovsky <alextarkovsky@gmail.com>2007-09-05 22:01:28 +0200
committerAlex Tarkovsky <alextarkovsky@gmail.com>2007-09-05 22:01:28 +0200
commita2ceae3cf6f302de2420f072238a29c9fbe8d974 (patch)
treebdd6ec53b679432c8a88a1cb60e4bc437b86a3dd
parentbea7c7116f233a785e4c96a1d577ca2797fe70bf (diff)
downloadXMonadContrib-a2ceae3cf6f302de2420f072238a29c9fbe8d974.tar.gz
XMonadContrib-a2ceae3cf6f302de2420f072238a29c9fbe8d974.tar.xz
XMonadContrib-a2ceae3cf6f302de2420f072238a29c9fbe8d974.zip
Docstring parser for generating xmonad build configs with default settings for extensions
darcs-hash:20070905200128-bd4fb-ff90db3eb7ebce6ea75956f19ebc6c35d36c08d4.gz
-rw-r--r--Accordion.hs3
-rw-r--r--Anneal.hs2
-rw-r--r--Circle.hs2
-rw-r--r--Combo.hs6
-rw-r--r--Commands.hs7
-rw-r--r--CopyWindow.hs11
-rw-r--r--DeManage.hs3
-rw-r--r--Dmenu.hs2
-rw-r--r--DwmPromote.hs3
-rw-r--r--DynamicLog.hs4
-rw-r--r--FindEmptyWorkspace.hs4
-rw-r--r--FlexibleManipulate.hs3
-rw-r--r--FlexibleResize.hs3
-rw-r--r--FocusNth.hs6
-rw-r--r--LayoutHints.hs4
-rw-r--r--LayoutScreens.hs4
-rw-r--r--MagicFocus.hs4
-rw-r--r--Magnifier.hs4
-rw-r--r--Mosaic.hs10
-rw-r--r--NoBorders.hs4
-rw-r--r--Roledex.hs3
-rw-r--r--RotSlaves.hs3
-rw-r--r--RotView.hs4
-rw-r--r--ShellPrompt.hs5
-rw-r--r--SimpleDate.hs3
-rw-r--r--SinkAll.hs3
-rw-r--r--Spiral.hs9
-rw-r--r--Square.hs2
-rw-r--r--SshPrompt.hs4
-rw-r--r--Submap.hs8
-rw-r--r--Tabbed.hs3
-rw-r--r--ThreeColumns.hs5
-rw-r--r--TwoPane.hs5
-rw-r--r--Warp.hs7
-rw-r--r--WorkspaceDir.hs6
-rw-r--r--XMonadPrompt.hs4
-rwxr-xr-xscripts/generate-configs.sh206
37 files changed, 360 insertions, 9 deletions
diff --git a/Accordion.hs b/Accordion.hs
index 37dc972..74c53b5 100644
--- a/Accordion.hs
+++ b/Accordion.hs
@@ -28,6 +28,9 @@ import XMonadContrib.LayoutHelpers ( idModify )
-- > import XMonadContrib.Accordion
-- > defaultLayouts = [ accordion ]
+-- %import XMonadContrib.Accordion
+-- %layout , accordion
+
accordion :: Eq a => Layout a
accordion = Layout { doLayout = accordionLayout, modifyLayout = idModify }
diff --git a/Anneal.hs b/Anneal.hs
index 07094fc..184bea0 100644
--- a/Anneal.hs
+++ b/Anneal.hs
@@ -17,6 +17,8 @@ module XMonadContrib.Anneal ( Rated(Rated), the_value, the_rating
import System.Random ( StdGen, Random, mkStdGen, randomR )
import Control.Monad.State ( State, runState, put, get, gets, modify )
+-- %import XMonadContrib.Anneal
+
data Rated a b = Rated !a !b
deriving ( Show )
instance Functor (Rated a) where
diff --git a/Circle.hs b/Circle.hs
index 49de894..fde2351 100644
--- a/Circle.hs
+++ b/Circle.hs
@@ -30,6 +30,8 @@ import XMonadContrib.LayoutHelpers ( idModify )
--
-- > import XMonadContrib.Circle
+-- %import XMonadContrib.Circle
+
circle :: Layout Window
circle = Layout { doLayout = \r s -> do { layout <- raiseFocus $ circleLayout r $ integrate s
; return (layout, Nothing) }
diff --git a/Combo.hs b/Combo.hs
index da9070f..cbf330e 100644
--- a/Combo.hs
+++ b/Combo.hs
@@ -32,7 +32,7 @@ import StackSet ( integrate, differentiate )
--
-- and add something like
--
--- > simpleStacking $ combo (twoPane 0.03 0.5) [(full,1),(tabbed shrinkText,1)]
+-- > simpleStacking $ combo (twoPane 0.03 0.5) [(full,1),(tabbed shrinkText defaultTConf,1)]
--
-- to your defaultLayouts.
--
@@ -43,6 +43,10 @@ import StackSet ( integrate, differentiate )
-- windows this section should hold. This number is ignored for the last
-- layout, which will hold any excess windows.
+-- %import XMonadContrib.Combo
+-- %import XMonadContrib.SimpleStacking
+-- %layout , simpleStacking $ combo (twoPane 0.03 0.5) [(full,1),(tabbed shrinkText defaultTConf,1)]
+
combo :: Layout (Layout a, Int) -> [(Layout a, Int)] -> Layout a
combo super origls = Layout { doLayout = \r s -> arrange r (integrate s), modifyLayout = message }
where arrange _ [] = return ([], Nothing)
diff --git a/Commands.hs b/Commands.hs
index 216f1b2..1b7cac8 100644
--- a/Commands.hs
+++ b/Commands.hs
@@ -42,7 +42,7 @@ import Data.Maybe
--
-- and add a keybinding to the runCommand action:
--
--- > , ((modMask .|. controlMask, xK_y), runCommand)
+-- > , ((modMask .|. controlMask, xK_y), runCommand commands)
--
-- and define the list commands:
--
@@ -54,6 +54,11 @@ import Data.Maybe
-- 'commands'. (If you like it enough, you may even want to get rid
-- of many of your other key bindings!)
+-- %def commands :: [(String, X ())]
+-- %def commands = defaultCommands
+-- %import XMonadContrib.Commands
+-- %keybind , ((modMask .|. controlMask, xK_y), runCommand commands)
+
commandMap :: [(String, X ())] -> M.Map String (X ())
commandMap c = M.fromList c
diff --git a/CopyWindow.hs b/CopyWindow.hs
index fa96802..947b488 100644
--- a/CopyWindow.hs
+++ b/CopyWindow.hs
@@ -43,6 +43,17 @@ import StackSet
--
-- > , ((modMask .|. shiftMask, xK_c ), kill1) -- @@ Close the focused window
+-- %import XMonadContrib.CopyWindow
+-- %keybind -- comment out default close window binding above if you uncomment this:
+-- %keybind , ((modMask .|. shiftMask, xK_c ), kill1) -- @@ Close the focused window
+-- %keybindlist ++
+-- %keybindlist -- mod-[1..9] @@ Switch to workspace N
+-- %keybindlist -- mod-shift-[1..9] @@ Move client to workspace N
+-- %keybindlist -- mod-control-shift-[1..9] @@ Copy client to workspace N
+-- %keybindlist [((m .|. modMask, k), f i)
+-- %keybindlist | (i, k) <- zip workspaces [xK_1 ..]
+-- %keybindlist , (f, m) <- [(view, 0), (shift, shiftMask), (copy, shiftMask .|. controlMask)]]
+
-- | copy. Copy a window to a new workspace.
copy :: WorkspaceId -> X ()
copy n = windows (copy' n)
diff --git a/DeManage.hs b/DeManage.hs
index 8ff5e0b..8209653 100644
--- a/DeManage.hs
+++ b/DeManage.hs
@@ -48,6 +48,9 @@ import Graphics.X11 (Window)
-- > , ((modMask, xK_d ), withFocused demanage)
--
+-- %import XMonadContrib.DeManage
+-- %keybind , ((modMask, xK_d ), withFocused demanage)
+
-- | Stop managing the current focused window.
demanage :: Window -> X ()
demanage w = do
diff --git a/Dmenu.hs b/Dmenu.hs
index 9980c44..222d668 100644
--- a/Dmenu.hs
+++ b/Dmenu.hs
@@ -30,6 +30,8 @@ import Control.Monad.State
--
-- > import XMonadContrib.Dmenu
+-- %import XMonadContrib.Dmenu
+
runProcessWithInput :: FilePath -> [String] -> String -> IO String
runProcessWithInput cmd args input = do
(pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
diff --git a/DwmPromote.hs b/DwmPromote.hs
index 7ec8fd6..a4143c3 100644
--- a/DwmPromote.hs
+++ b/DwmPromote.hs
@@ -36,6 +36,9 @@ import StackSet
--
-- > , ((modMask, xK_Return), dwmpromote)
+-- %import XMonadContrib.DwmPromote
+-- %keybind , ((modMask, xK_Return), dwmpromote)
+
dwmpromote :: X ()
dwmpromote = windows swap
diff --git a/DynamicLog.hs b/DynamicLog.hs
index 44ea957..7447f43 100644
--- a/DynamicLog.hs
+++ b/DynamicLog.hs
@@ -40,6 +40,10 @@ import qualified StackSet as S
-- > import XMonadContrib.DynamicLog
-- > logHook = dynamicLog
+-- %import XMonadContrib.DynamicLog
+-- %def -- comment out default logHook definition above if you uncomment this:
+-- %def logHook = dynamicLog
+
-- |
-- Perform an arbitrary action on each state change.
diff --git a/FindEmptyWorkspace.hs b/FindEmptyWorkspace.hs
index 5cb3964..7ffe664 100644
--- a/FindEmptyWorkspace.hs
+++ b/FindEmptyWorkspace.hs
@@ -41,6 +41,10 @@ import qualified Operations as O
-- Now you can jump to an empty workspace with mod-m. Mod-shift-m will
-- tag the current window to an empty workspace and view it.
+-- %import XMonadContrib.FindEmptyWorkspace
+-- %keybind , ((modMask, xK_m ), viewEmptyWorkspace)
+-- %keybind , ((modMask .|. shiftMask, xK_m ), tagToEmptyWorkspace)
+
-- | Find the first hidden empty workspace in a StackSet. Returns
-- Nothing if all workspaces are in use. Function searches currently
diff --git a/FlexibleManipulate.hs b/FlexibleManipulate.hs
index 7daf5e0..1a2df1d 100644
--- a/FlexibleManipulate.hs
+++ b/FlexibleManipulate.hs
@@ -48,6 +48,9 @@ import Graphics.X11.Xlib.Extras
-- a value between 0 and 1 indicating position, and return a value indicating
-- the corresponding position if plain Flex.linear was used.
+-- %import qualified XMonadContrib.FlexibleManipulate as Flex
+-- %mousebind , ((modMask, button1), (\\w -> focus w >> Flex.mouseWindow Flex.linear w))
+
discrete, linear, resize, position :: Double -> Double
discrete x | x < 0.33 = 0
diff --git a/FlexibleResize.hs b/FlexibleResize.hs
index 360df53..d9ed6fb 100644
--- a/FlexibleResize.hs
+++ b/FlexibleResize.hs
@@ -32,6 +32,9 @@ import Foreign.C.Types
-- > [ ...
-- > , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w)) ]
+-- %import qualified XMonadContrib.FlexibleResize as Flex
+-- %mousebind , ((modMask, button3), (\\w -> focus w >> Flex.mouseResizeWindow w))
+
mouseResizeWindow :: Window -> X ()
mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
io $ raiseWindow d w
diff --git a/FocusNth.hs b/FocusNth.hs
index f697c75..1bcd66b 100644
--- a/FocusNth.hs
+++ b/FocusNth.hs
@@ -27,6 +27,12 @@ import XMonad
-- > ++ [((mod4Mask, k), focusNth i)
-- > | (i, k) <- zip [0 .. 8] [xK_1 ..]]
+-- %import XMonadContrib.FocusNth
+-- %keybdindextra ++
+-- %keybdindextra -- mod4-[1..9] @@ Switch to window N
+-- %keybdindextra [((mod4Mask, k), focusNth i)
+-- %keybdindextra | (i, k) <- zip [0 .. 8] [xK_1 ..]]
+
focusNth :: Int -> X ()
focusNth = windows . modify' . focusNth'
diff --git a/LayoutHints.hs b/LayoutHints.hs
index 5daece8..e171d16 100644
--- a/LayoutHints.hs
+++ b/LayoutHints.hs
@@ -27,6 +27,10 @@ import XMonadContrib.LayoutHelpers ( layoutModify, idModMod )
-- > import XMonadContrib.LayoutHints
-- > defaultLayouts = [ layoutHints tiled , layoutHints $ mirror tiled ]
+-- %import XMonadContrib.LayoutHints
+-- %layout , layoutHints tiled
+-- %layout , layoutHints $ mirror tiled
+
-- | Expand a size by the given multiple of the border width. The
-- multiple is most commonly 1 or -1.
adjBorders :: Dimension -> D -> D
diff --git a/LayoutScreens.hs b/LayoutScreens.hs
index 9d74189..a78a402 100644
--- a/LayoutScreens.hs
+++ b/LayoutScreens.hs
@@ -40,6 +40,10 @@ import Graphics.X11.Xlib.Extras
-- > , ((modMask .|. shiftMask, xK_space), layoutScreens 2 (twoPane 0.5 0.5))
-- > , ((controlMask .|. modMask .|. shiftMask, xK_space), rescreen)
+-- %import XMonadContrib.LayoutScreens
+-- %keybind , ((modMask .|. shiftMask, xK_space), layoutScreens 2 (twoPane 0.5 0.5))
+-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_space), rescreen)
+
layoutScreens :: Int -> Layout Int -> X ()
layoutScreens nscr _ | nscr < 1 = trace $ "Can't layoutScreens with only " ++ show nscr ++ " screens."
layoutScreens nscr l =
diff --git a/MagicFocus.hs b/MagicFocus.hs
index 2376cdd..7bce455 100644
--- a/MagicFocus.hs
+++ b/MagicFocus.hs
@@ -24,6 +24,10 @@ import StackSet
-- > import XMonadContrib.MagicFocus
-- > defaultLayouts = [ magicFocus tiled , magicFocus $ mirror tiled ]
+-- %import XMonadContrib.MagicFocus
+-- %layout , magicFocus tiled
+-- %layout , magicFocus $ mirror tiled
+
magicFocus :: Layout Window -> Layout Window
magicFocus l = l { doLayout = \r s -> withWindowSet (return . peek) >>= (doLayout l) r . swap s
, modifyLayout = \x -> fmap magicFocus `fmap` modifyLayout l x }
diff --git a/Magnifier.hs b/Magnifier.hs
index f29cf3f..6bd8306 100644
--- a/Magnifier.hs
+++ b/Magnifier.hs
@@ -30,6 +30,10 @@ import XMonadContrib.LayoutHelpers
-- > import XMonadContrib.Magnifier
-- > defaultLayouts = [ magnifier tiled , magnifier $ mirror tiled ]
+-- %import XMonadContrib.Magnifier
+-- %layout , magnifier tiled
+-- %layout , magnifier $ mirror tiled
+
-- | Increase the size of the window that has focus, unless it is the master window.
magnifier :: Layout Window -> Layout Window
magnifier = layoutModify (unlessMaster applyMagnifier) idModMod
diff --git a/Mosaic.hs b/Mosaic.hs
index 59a6a68..ae2fd5d 100644
--- a/Mosaic.hs
+++ b/Mosaic.hs
@@ -59,6 +59,16 @@ import XMonadContrib.Anneal
-- > , ((controlMask .|. modMask .|. shiftMask, xK_o ), withNamedWindow (sendMessage . flexibleWindow))
--
+-- %import XMonadContrib.Mosaic
+-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_h), withNamedWindow (sendMessage . tallWindow))
+-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_l), withNamedWindow (sendMessage . wideWindow))
+-- %keybind , ((modMask .|. shiftMask, xK_h ), withNamedWindow (sendMessage . shrinkWindow))
+-- %keybind , ((modMask .|. shiftMask, xK_l ), withNamedWindow (sendMessage . expandWindow))
+-- %keybind , ((modMask .|. shiftMask, xK_s ), withNamedWindow (sendMessage . squareWindow))
+-- %keybind , ((modMask .|. shiftMask, xK_o ), withNamedWindow (sendMessage . myclearWindow))
+-- %keybind , ((controlMask .|. modMask .|. shiftMask, xK_o ), withNamedWindow (sendMessage . flexibleWindow))
+-- %layout , mosaic 0.25 0.5 M.empty
+
data HandleWindow = ExpandWindow NamedWindow | ShrinkWindow NamedWindow
| SquareWindow NamedWindow | ClearWindow NamedWindow
| TallWindow NamedWindow | WideWindow NamedWindow
diff --git a/NoBorders.hs b/NoBorders.hs
index 96698eb..b2476b3 100644
--- a/NoBorders.hs
+++ b/NoBorders.hs
@@ -40,6 +40,10 @@ import {-# SOURCE #-} Config (borderWidth)
--
-- > defaultLayouts = [ noBorders full, ... ]
+-- %import XMonadContrib.NoBorders
+-- %layout -- prepend noBorders to default layouts above to remove their borders, like so:
+-- %layout , noBorders full
+
noBorders :: Layout a -> Layout a
noBorders = withBorder 0
diff --git a/Roledex.hs b/Roledex.hs
index f9584ee..81092d9 100644
--- a/Roledex.hs
+++ b/Roledex.hs
@@ -30,6 +30,9 @@ import XMonadContrib.LayoutHelpers ( idModify )
-- > import XMonadContrib.Roledex
-- > defaultLayouts = [ roledex ]
+-- %import XMonadContrib.Roledex
+-- %layout , roledex
+
roledex :: Eq a => Layout a
roledex = Layout { doLayout = roledexLayout, modifyLayout = idModify }
diff --git a/RotSlaves.hs b/RotSlaves.hs
index 3c65387..e53a185 100644
--- a/RotSlaves.hs
+++ b/RotSlaves.hs
@@ -34,6 +34,9 @@ import XMonad
-- This operation will rotate all windows except the master window, while the focus
-- stays where it is. It is usefull together with the TwoPane-Layout (see XMonadContrib.TwoPane).
+-- %import XMonadContrib.RotSlaves
+-- %keybind , ((modMask .|. shiftMask, xK_Tab ), rotSlavesUp)
+
rotSlavesUp,rotSlavesDown :: X ()
rotSlavesUp = windows $ modify' (rotSlaves' (\l -> (tail l)++[head l]))
rotSlavesDown = windows $ modify' (rotSlaves' (\l -> [last l]++(init l)))
diff --git a/RotView.hs b/RotView.hs
index 38c2cae..c7dc6c6 100644
--- a/RotView.hs
+++ b/RotView.hs
@@ -35,6 +35,10 @@ import qualified Operations as O
-- > , ((modMask .|. shiftMask, xK_Right), rotView True)
-- > , ((modMask .|. shiftMask, xK_Left), rotView False)
+-- %import XMonadContrib.RotView
+-- %keybind , ((modMask .|. shiftMask, xK_Right), rotView True)
+-- %keybind , ((modMask .|. shiftMask, xK_Left), rotView False)
+
rotView :: Bool -> X ()
rotView b = do
ws <- gets windowset
diff --git a/ShellPrompt.hs b/ShellPrompt.hs
index a2f6465..6b06df6 100644
--- a/ShellPrompt.hs
+++ b/ShellPrompt.hs
@@ -48,6 +48,11 @@ import System.Environment
-- > , ((modMask .|. controlMask, xK_x), shellPrompt defaultXPConfig)
--
+-- %cabalbuilddep readline>=1.0
+-- %import XMonadContrib.XPrompt
+-- %import XMonadContrib.ShellPrompt
+-- %keybind , ((modMask .|. controlMask, xK_x), shellPrompt defaultXPConfig)
+
data Shell = Shell
instance XPrompt Shell where
diff --git a/SimpleDate.hs b/SimpleDate.hs
index 17805ca..6712a5c 100644
--- a/SimpleDate.hs
+++ b/SimpleDate.hs
@@ -32,5 +32,8 @@ import XMonad
--
-- a popup date menu will now be bound to mod-d
+-- %import XMonadContrib.SimpleDate
+-- %keybind , ((modMask, xK_d ), date)
+
date :: X ()
date = spawn "(date; sleep 10) | dzen2"
diff --git a/SinkAll.hs b/SinkAll.hs
index 16d6637..b6caa1d 100644
--- a/SinkAll.hs
+++ b/SinkAll.hs
@@ -25,6 +25,9 @@ import Graphics.X11.Xlib
-- > import XMonadContrib.SinkAll
-- > keys = [ ((modMask .|. shiftMask, xK_t), sinkAll) ]
+-- %import XMonadContrib.SinkAll
+-- %keybind , ((modMask .|. shiftMask, xK_t), sinkAll)
+
sinkAll :: X ()
sinkAll = withAll sink
diff --git a/Spiral.hs b/Spiral.hs
index c0aad78..ae52428 100644
--- a/Spiral.hs
+++ b/Spiral.hs
@@ -33,11 +33,10 @@ import XMonadContrib.LayoutHelpers
--
-- > import XMonadContrib.Spiral
--
--- > defaultLayouts :: [Layout]
--- > defaultLayouts = [ full,
--- > tall defaultWindowsInMaster defaultDelta (1%2),
--- > wide defaultWindowsInMaster defaultDelta (1%2),
--- > spiral (1 % 1) ]
+-- > defaultLayouts = [ full, spiral (1 % 1), ... ]
+
+-- %import XMonadContrib.Spiral
+-- %layout , spiral (1 % 1)
fibs :: [Integer]
fibs = 1 : 1 : (zipWith (+) fibs (tail fibs))
diff --git a/Square.hs b/Square.hs
index 4ccb50e..02a5adb 100644
--- a/Square.hs
+++ b/Square.hs
@@ -38,6 +38,8 @@ import XMonadContrib.LayoutHelpers ( l2lModDo, idModify )
-- > [(twoPane 0.03 0.2,1),(combo [(twoPane 0.03 0.8,1),(square,1)]
-- > [(tabbed,3),(tabbed,30),(tabbed,1),(tabbed,1)]
+-- %import XMonadContrib.Square
+
square :: Layout a
square = Layout { doLayout = l2lModDo arrange, modifyLayout = idModify }
where arrange :: Rectangle -> [a] -> [(a, Rectangle)]
diff --git a/SshPrompt.hs b/SshPrompt.hs
index 638aedf..1188432 100644
--- a/SshPrompt.hs
+++ b/SshPrompt.hs
@@ -37,6 +37,10 @@ import System.Environment
-- > , ((modMask .|. controlMask, xK_x), xmonadPrompt defaultXPConfig)
--
+-- %import XMonadContrib.XPrompt
+-- %import XMonadContrib.SshPrompt
+-- %keybind , ((modMask .|. controlMask, xK_x), xmonadPrompt defaultXPConfig)
+
data Ssh = Ssh
instance XPrompt Ssh where
diff --git a/Submap.hs b/Submap.hs
index 0dee401..4d655ef 100644
--- a/Submap.hs
+++ b/Submap.hs
@@ -43,6 +43,14 @@ anyModifier will not work, because that is a special value passed to XGrabKey()
and not an actual modifier.
-}
+-- %import XMonadContrib.Submap
+-- %keybind , ((modMask, xK_a), submap . M.fromList $
+-- %keybind [ ((0, xK_n), spawn "mpc next")
+-- %keybind , ((0, xK_p), spawn "mpc prev")
+-- %keybind , ((0, xK_z), spawn "mpc random")
+-- %keybind , ((0, xK_space), spawn "mpc toggle")
+-- %keybind ])
+
submap :: M.Map (KeyMask, KeySym) (X ()) -> X ()
submap keys = do
XConf { theRoot = root, display = d } <- ask
diff --git a/Tabbed.hs b/Tabbed.hs
index 5f66d7b..c91ef12 100644
--- a/Tabbed.hs
+++ b/Tabbed.hs
@@ -51,6 +51,9 @@ import XMonadContrib.LayoutHelpers ( idModify )
-- > defaultLayouts = [ tabbed shrinkText myconfig
-- > , ... ]
+-- %import XMonadContrib.Tabbed
+-- %layout , tabbed shrinkText defaultTConf
+
data TConf =
TConf { activeColor :: String
, inactiveColor :: String
diff --git a/ThreeColumns.hs b/ThreeColumns.hs
index faa1dd9..76faf6e 100644
--- a/ThreeColumns.hs
+++ b/ThreeColumns.hs
@@ -37,7 +37,10 @@ import Graphics.X11.Xlib
--
-- and add, to the list of layouts:
--
--- > threeCol
+-- > threeCol nmaster delta ratio
+
+-- %import XMonadContrib.ThreeColumns
+-- %layout , threeCol nmaster delta ratio
threeCol :: Int -> Rational -> Rational -> Layout a
threeCol nmaster delta frac =
diff --git a/TwoPane.hs b/TwoPane.hs
index 1fdabc7..65d52de 100644
--- a/TwoPane.hs
+++ b/TwoPane.hs
@@ -32,7 +32,10 @@ import StackSet ( focus, up, down)
--
-- and add, to the list of layouts:
--
--- > twoPane defaultDelta (1%2)
+-- > twoPane delta (1%2)
+
+-- %import XMonadContrib.TwoPane
+-- %layout , twoPane delta (1%2)
twoPane :: Rational -> Rational -> Layout a
twoPane delta split = Layout { doLayout = \r s -> return (arrange r s,Nothing), modifyLayout = message }
diff --git a/Warp.hs b/Warp.hs
index df186e6..f18b96b 100644
--- a/Warp.hs
+++ b/Warp.hs
@@ -45,6 +45,13 @@ my Config.hs:
Note that warping to a particular screen may change the focus.
-}
+-- %import XMonadContrib.Warp
+-- %keybind , ((modMask, xK_z ), warpToWindow (1%2) (1%2)) -- @@ Move pointer to currently focused window
+-- %keybindlist ++
+-- %keybindlist -- mod-ctrl-{w,e,r} @@ Move mouse pointer to screen 1, 2, or 3
+-- %keybindlist [((modMask .|. controlMask, key), warpToScreen sc (1%2) (1%2))
+-- %keybindlist | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]]
+
fraction :: (Integral a, Integral b) => Rational -> a -> b
fraction f x = floor (f * fromIntegral x)
diff --git a/WorkspaceDir.hs b/WorkspaceDir.hs
index 290a675..9e3431c 100644
--- a/WorkspaceDir.hs
+++ b/WorkspaceDir.hs
@@ -46,6 +46,12 @@ import XMonadContrib.XPrompt ( defaultXPConfig )
--
-- > , ((modMask .|. shiftMask, xK_x ), changeDir defaultXPConfig)
+-- %import XMonadContrib.WorkspaceDir
+-- %keybind , ((modMask .|. shiftMask, xK_x ), changeDir defaultXPConfig)
+-- %layout -- prepend 'map (workspaceDir "~")' to defaultLayouts definition above,
+-- %layout -- just before the list, like the following (don't uncomment next line):
+-- %layout -- defaultLayouts = map (workspaceDir "~") [ tiled, ... ]
+
data Chdir = Chdir String deriving ( Typeable )
instance Message Chdir
diff --git a/XMonadPrompt.hs b/XMonadPrompt.hs
index 28be4ed..f2a7019 100644
--- a/XMonadPrompt.hs
+++ b/XMonadPrompt.hs
@@ -34,6 +34,10 @@ import XMonadContrib.Commands (defaultCommands, runCommand')
-- > , ((modMask .|. controlMask, xK_x), xmonadPrompt defaultXPConfig)
--
+-- %import XMonadContrib.XPrompt
+-- %import XMonadContrib.XMonadPrompt
+-- %keybind , ((modMask .|. controlMask, xK_x), xmonadPrompt defaultXPConfig)
+
data XMonad = XMonad
instance XPrompt XMonad where
diff --git a/scripts/generate-configs.sh b/scripts/generate-configs.sh
new file mode 100755
index 0000000..bfd9a78
--- /dev/null
+++ b/scripts/generate-configs.sh
@@ -0,0 +1,206 @@
+#!/bin/bash
+
+# generate-configs.sh - Docstring parser for generating xmonad build configs
+# with default settings for extensions
+# Author: Alex Tarkovsky <alextarkovsky@gmail.com>
+# Released into the public domain
+
+# This script parses custom docstrings specifying build-time configuration data
+# from xmonad extension source files, then inserts the data into copies of
+# xmonad's Config.hs and xmonad.cabal files accordingly.
+#
+# Usage: generate-configs.sh PATH_TO_CONTRIBS
+#
+# Run this script from the directory containing xmonad's main Config.hs and
+# xmonad.cabal files, otherwise you'll need to change the value of
+# $REPO_DIR_BASE below.
+#
+# The docstring markup can be extended as needed. Currently the following tags
+# are defined, shown with some examples:
+#
+# ~~~~~
+#
+# %cabalbuilddep
+#
+# Cabal build dependency. Value is appended to the "build-depends" line in
+# xmonad.cabal and automatically prefixed with ", ". NB: Don't embed
+# comments in this tag!
+#
+# -- %cabalbuilddep readline>=1.0
+#
+# %def
+#
+# General definition. Value is appended to the end of Config.sh.
+#
+# -- %def commands :: [(String, X ())]
+# -- %def commands = defaultCommands
+#
+# %import
+#
+# Module needed by Config.sh to build the extension. Value is appended to
+# the end of the default import list in Config.sh and automatically
+# prefixed with "import ".
+#
+# -- %import XMonadContrib.Accordion
+# -- %import qualified XMonadContrib.FlexibleManipulate as Flex
+#
+# %keybind
+#
+# Tuple defining a key binding. Must be prefixed with ", ". Value is
+# inserted at the end of the "keys" list in Config.sh.
+#
+# -- %keybind , ((modMask, xK_d), date)
+#
+# %keybindlist
+#
+# Same as %keybind, but instead of a key binding tuple the definition is a
+# list of key binding tuples (or a list comprehension producing them). This
+# list is concatenated to the "keys" list must begin with the "++" operator
+# rather than ", ".
+#
+# -- %keybindlist ++
+# -- %keybindlist -- mod-[1..9] @@ Switch to workspace N
+# -- %keybindlist -- mod-shift-[1..9] @@ Move client to workspace N
+# -- %keybindlist -- mod-control-shift-[1..9] @@ Copy client to workspace N
+# -- %keybindlist [((m .|. modMask, k), f i)
+# -- %keybindlist | (i, k) <- zip [0..fromIntegral (workspaces-1)] [xK_1 ..]
+# -- %keybindlist , (f, m) <- [(view, 0), (shift, shiftMask), (copy, shiftMask .|. controlMask)]]
+#
+# %layout
+#
+# A layout. Must be prefixed with ", ". Value is inserted at the end of the
+# "defaultLayouts" list in Config.sh.
+#
+# -- %layout , accordion
+#
+# %mousebind
+#
+# Tuple defining a mouse binding. Must be prefixed with ", ". Value is
+# inserted at the end of the "mouseBindings" list in Config.sh.
+#
+# -- %mousebind , ((modMask, button3), (\\w -> focus w >> Flex.mouseResizeWindow w))
+#
+# ~~~~~
+#
+# NB: '/' and '\' characters must be escaped with a '\' character!
+#
+# Tags may also contain comments, as illustrated in the %keybindlist examples
+# above. Comments are a good place for special user instructions:
+#
+# -- %def -- comment out default logHook definition above if you uncomment this:
+# -- %def logHook = dynamicLog
+
+if [[ -z "$1" || $# > 1 || ! -d "$1" ]] ; then
+ echo "Usage: generate-configs.sh PATH_TO_CONTRIB"
+ exit 1
+fi
+
+REPO_DIR_BASE="."
+
+CABAL_FILE_BASE="${REPO_DIR_BASE}/xmonad.cabal"
+CABAL_FILE_CONTRIB="${1}/xmonad.cabal"
+
+CONFIG_FILE_BASE="${REPO_DIR_BASE}/Config.hs"
+CONFIG_FILE_CONTRIB="${1}/Config.hs"
+
+# Markup tag to search for in source files.
+TAG_CABALBUILDDEP="%cabalbuilddep"
+TAG_DEF="%def"
+TAG_IMPORT="%import"
+TAG_KEYBIND="%keybind"
+TAG_KEYBINDLIST="%keybindlist"
+TAG_LAYOUT="%layout"
+TAG_MOUSEBIND="%mousebind"
+
+# Insert markers to search for in Config.sh and xmonad.cabal. Values are
+# extended sed regular expressions.
+INS_MARKER_CABALBUILDDEP='^build-depends:.*'
+INS_MARKER_DEF='-- Extension-provided definitions$'
+INS_MARKER_IMPORT='-- Extension-provided imports$'
+INS_MARKER_KEYBIND='-- Extension-provided key bindings$'
+INS_MARKER_KEYBINDLIST='-- Extension-provided key bindings lists$'
+INS_MARKER_LAYOUT='-- Extension-provided layouts$'
+INS_MARKER_MOUSEBIND='-- Extension-provided mouse bindings$'
+
+# Literal indentation strings. Values may contain escaped chars such as \t.
+INS_INDENT_CABALBUILDDEP=""
+INS_INDENT_DEF=""
+INS_INDENT_IMPORT=""
+INS_INDENT_KEYBIND=" "
+INS_INDENT_KEYBINDLIST=" "
+INS_INDENT_LAYOUT=" "
+INS_INDENT_MOUSEBIND=" "
+
+# Prefix applied to inserted values after indent strings have been applied.
+INS_PREFIX_CABALBUILDDEP=", "
+INS_PREFIX_DEF="-- "
+INS_PREFIX_IMPORT="--import "
+INS_PREFIX_KEYBIND="-- "
+INS_PREFIX_KEYBINDLIST="-- "
+INS_PREFIX_LAYOUT="-- "
+INS_PREFIX_MOUSEBIND="-- "
+
+cp -f "${CABAL_FILE_BASE}" "${CABAL_FILE_CONTRIB}"
+cp -f "${CONFIG_FILE_BASE}" "${CONFIG_FILE_CONTRIB}"
+
+for extension_srcfile in $(ls --color=never -1 "${1}"/*.hs | head -n -1 | sort -r) ; do
+ for tag in $TAG_CABALBUILDDEP \
+ $TAG_DEF \
+ $TAG_IMPORT \
+ $TAG_KEYBIND \
+ $TAG_KEYBINDLIST \
+ $TAG_LAYOUT \
+ $TAG_MOUSEBIND ; do
+
+ ifs="$IFS"
+ IFS=$'\n'
+ tags=( $(sed -n -r -e "s/^.*--\s*${tag}\s//p" "${extension_srcfile}") )
+ IFS="${ifs}"
+
+ case $tag in
+ $TAG_CABALBUILDDEP) ins_indent=$INS_INDENT_CABALBUILDDEP
+ ins_marker=$INS_MARKER_CABALBUILDDEP
+ ins_prefix=$INS_PREFIX_CABALBUILDDEP
+ ;;
+ $TAG_DEF) ins_indent=$INS_INDENT_DEF
+ ins_marker=$INS_MARKER_DEF
+ ins_prefix=$INS_PREFIX_DEF
+ ;;
+ $TAG_IMPORT) ins_indent=$INS_INDENT_IMPORT
+ ins_marker=$INS_MARKER_IMPORT
+ ins_prefix=$INS_PREFIX_IMPORT
+ ;;
+ $TAG_KEYBIND) ins_indent=$INS_INDENT_KEYBIND
+ ins_marker=$INS_MARKER_KEYBIND
+ ins_prefix=$INS_PREFIX_KEYBIND
+ ;;
+ $TAG_KEYBINDLIST) ins_indent=$INS_INDENT_KEYBINDLIST
+ ins_marker=$INS_MARKER_KEYBINDLIST
+ ins_prefix=$INS_PREFIX_KEYBINDLIST
+ ;;
+ $TAG_LAYOUT) ins_indent=$INS_INDENT_LAYOUT
+ ins_marker=$INS_MARKER_LAYOUT
+ ins_prefix=$INS_PREFIX_LAYOUT
+ ;;
+ $TAG_MOUSEBIND) ins_indent=$INS_INDENT_MOUSEBIND
+ ins_marker=$INS_MARKER_MOUSEBIND
+ ins_prefix=$INS_PREFIX_MOUSEBIND
+ ;;
+ esac
+
+ # Insert in reverse so values will ultimately appear in correct order.
+ for i in $( seq $(( ${#tags[*]} - 1 )) -1 0 ) ; do
+ [ -z "${tags[i]}" ] && continue
+ if [[ $tag == $TAG_CABALBUILDDEP ]] ; then
+ sed -i -r -e "s/${ins_marker}/\\0${ins_prefix}${tags[i]}/" "${CABAL_FILE_CONTRIB}"
+ else
+ sed -i -r -e "/${ins_marker}/{G;s/$/${ins_indent}${ins_prefix}${tags[i]}/;}" "${CONFIG_FILE_CONTRIB}"
+ fi
+ done
+
+ if [[ $tag != $TAG_CABALBUILDDEP && -n "${tags}" ]] ; then
+ ins_group_comment="${ins_indent}-- For extension $(basename $extension_srcfile .hs):"
+ sed -i -r -e "/${ins_marker}/{G;s/$/${ins_group_comment}/;}" "${CONFIG_FILE_CONTRIB}"
+ fi
+ done
+done