
Hi Andrea, Thanks for your reply. When emerging xmonad on gentoo, a default configuration file is installed to be edited. I added the file in the attachment. I tried to edit it, so that the "HintedTile" extension is available. Thanks! Nathan Andrea Rossato schrieb:
Hi Nathan,
On Thu, Nov 29, 2007 at 02:49:56PM +0100, Nathan Huesken wrote:
I tried uncommenting the following lines in /etc/portage/savedconfig/x11-wm/xmonad-0.4.1:
(Line 69) import qualified XMonadContrib.HintedTile (Line 248) , XMonadContrib.HintedTile.tall nmaster delta ratio
[...]
[5 of 7] Compiling XMonadContrib.HintedTile ( XMonadContrib/HintedTile.hs, dist/build/xmonad/xmonad-tmp/XMonadContrib/HintedTile.o )
XMonadContrib/HintedTile.hs:55:13: Not in scope: `modifyLayout'
I hope some gentoo guy will drop by soon and make my request useless, but in the meantime, since I'm not a gentoo user, I would need to have a copy of the file you modified, and also a brief description of what you were/are trying to achieve with your modifications. This way I can contextualize the error messages you get and provide some directions.
Cheers, Andrea
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
----------------------------------------------------------------------------- -- | -- Module : Config.hs -- Copyright : (c) Spencer Janssen 2007 -- License : BSD3-style (see LICENSE) -- -- Maintainer : dons@galois.com -- Stability : stable -- Portability : portable -- -- This module specifies configurable defaults for xmonad. If you change -- values here, be sure to recompile and restart (mod-q) xmonad, -- for the changes to take effect. -- ------------------------------------------------------------------------ module Config where -- -- Useful imports -- import XMonad import Operations import qualified StackSet as W import Data.Ratio import Data.Bits ((.|.)) import qualified Data.Map as M import System.Exit import Graphics.X11.Xlib -- % Extension-provided imports -- For extension Accordion: --import XMonadContrib.Accordion -- For extension Anneal: --import XMonadContrib.Anneal -- For extension Circle: --import XMonadContrib.Circle -- For extension Combo: --import XMonadContrib.Combo -- For extension Commands: --import XMonadContrib.Commands -- For extension CopyWindow: --import XMonadContrib.CopyWindow -- For extension CycleWS: --import XMonadContrib.CycleWS -- For extension DeManage: --import XMonadContrib.DeManage -- For extension Dishes: --import XMonadContrib.Dishes -- For extension Dmenu: --import XMonadContrib.Dmenu -- For extension DwmPromote: --import XMonadContrib.DwmPromote -- For extension DynamicLog: --import XMonadContrib.DynamicLog -- For extension EwmhDesktops: --import XMonadContrib.EwmhDesktops -- For extension FindEmptyWorkspace: --import XMonadContrib.FindEmptyWorkspace -- For extension FlexibleManipulate: --import qualified XMonadContrib.FlexibleManipulate as Flex -- For extension FlexibleResize: --import qualified XMonadContrib.FlexibleResize as Flex -- For extension FocusNth: --import XMonadContrib.FocusNth -- For extension Grid: --import XMonadContrib.Grid -- For extension HintedTile: -- import qualified XMonadContrib.HintedTile -- For extension LayoutHints: --import XMonadContrib.LayoutHints -- For extension LayoutScreens: --import XMonadContrib.LayoutScreens -- For extension MagicFocus: --import XMonadContrib.MagicFocus -- For extension Magnifier: --import XMonadContrib.Magnifier -- For extension ManageDocks: --import XMonadContrib.ManageDocks -- For extension Maximize: --import XMonadContrib.Maximize -- For extension Mosaic: --import XMonadContrib.Mosaic -- For extension MosaicAlt: --import XMonadContrib.MosaicAlt -- For extension NoBorders: --import XMonadContrib.NoBorders -- For extension Roledex: --import XMonadContrib.Roledex -- For extension RotSlaves: --import XMonadContrib.RotSlaves -- For extension RotView: --import XMonadContrib.RotView -- For extension ShellPrompt: --import XMonadContrib.XPrompt --import XMonadContrib.ShellPrompt -- For extension SimpleDate: --import XMonadContrib.SimpleDate -- For extension SinkAll: --import XMonadContrib.SinkAll -- For extension Spiral: --import XMonadContrib.Spiral -- For extension Square: --import XMonadContrib.Square -- For extension SshPrompt: --import XMonadContrib.XPrompt --import XMonadContrib.SshPrompt -- For extension Submap: --import XMonadContrib.Submap -- For extension SwapWorkspaces: --import XMonadContrib.SwapWorkspaces -- For extension Tabbed: --import XMonadContrib.Tabbed -- For extension TagWindows: --import XMonadContrib.TagWindows --import XMonadContrib.XPrompt -- to use tagPrompt -- For extension ThreeColumns: --import XMonadContrib.ThreeColumns -- For extension TwoPane: --import XMonadContrib.TwoPane -- For extension Warp: --import XMonadContrib.Warp -- For extension WindowBringer: --import XMonadContrib.WindowBringer -- For extension WindowNavigation: --import XMonadContrib.WindowNavigation -- For extension WindowPrompt: --import XMonadContrib.XPrompt --import XMonadContrib.WindowPrompt -- For extension WorkspaceDir: --import XMonadContrib.WorkspaceDir -- For extension XMonadPrompt: --import XMonadContrib.XPrompt --import XMonadContrib.XMonadPrompt -- | The default number of workspaces (virtual screens) and their names. -- By default we use numeric strings, but any string may be used as a -- workspace name. The number of workspaces is determined by the length -- of this list. -- -- A tagging example: -- -- > workspaces = ["web", "irc", "code" ] ++ map show [4..9] -- workspaces :: [WorkspaceId] workspaces = map show [1 .. 9 :: Int] -- | modMask lets you specify which modkey you want to use. The default -- is mod1Mask ("left alt"). You may also consider using mod3Mask -- ("right alt"), which does not conflict with emacs keybindings. The -- "windows key" is usually mod4Mask. -- modMask :: KeyMask modMask = mod1Mask -- | The mask for the numlock key. Numlock status is "masked" from the -- current modifier status, so the keybindings will work with numlock on or -- off. You may need to change this on some systems. -- -- You can find the numlock modifier by running "xmodmap" and looking for a -- modifier with Num_Lock bound to it: -- -- > $ xmodmap | grep Num -- > mod2 Num_Lock (0x4d) -- -- Set numlockMask = 0 if you don't have a numlock key, or want to treat -- numlock status separately. -- numlockMask :: KeyMask numlockMask = mod2Mask -- | Width of the window border in pixels. -- borderWidth :: Dimension borderWidth = 3 -- | Border colors for unfocused and focused windows, respectively. -- normalBorderColor, focusedBorderColor :: String normalBorderColor = "#0000ff" focusedBorderColor = "#ff0000" -- | Default offset of drawable screen boundaries from each physical -- screen. Anything non-zero here will leave a gap of that many pixels -- on the given edge, on the that screen. A useful gap at top of screen -- for a menu bar (e.g. 15) -- -- An example, to set a top gap on monitor 1, and a gap on the bottom of -- monitor 2, you'd use a list of geometries like so: -- -- > defaultGaps = [(18,0,0,0),(0,18,0,0)] -- 2 gaps on 2 monitors -- -- Fields are: top, bottom, left, right. -- defaultGaps :: [(Int,Int,Int,Int)] defaultGaps = [(0,18,130,0),(0,18,0,0)] -- 15 for default dzen font ------------------------------------------------------------------------ -- Window rules -- | Execute arbitrary actions and WindowSet manipulations when managing -- a new window. You can use this to, for example, always float a -- particular program, or have a client always appear on a particular -- workspace. -- manageHook :: Window -- ^ the new window to manage -> String -- ^ window title -> String -- ^ window resource name -> String -- ^ window resource class -> X (WindowSet -> WindowSet) -- Always float various programs: manageHook w _ _ c | c `elem` floats = fmap (W.float w . snd) (floatLocation w) where floats = ["MPlayer", "Gimp"] -- Desktop panels and dock apps should be ignored by xmonad: manageHook w _ n _ | n `elem` ignore = reveal w >> return (W.delete w) where ignore = ["gnome-panel", "desktop_window", "kicker", "kdesktop"] -- Automatically send Firefox windows to the "web" workspace: -- If a workspace named "web" doesn't exist, the window will appear on the -- current workspace. manageHook _ _ "Gecko" _ = return $ W.shift "web" -- The default rule: return the WindowSet unmodified. You typically do not -- want to modify this line. manageHook _ _ _ _ = return id ------------------------------------------------------------------------ -- Extensible layouts -- | The list of possible layouts. Add your custom layouts to this list. layouts :: [Layout Window] layouts = [ Layout tiled , Layout $ Mirror tiled , Layout Full -- Add extra layouts you want to use here: -- % Extension-provided layouts -- For extension Accordion: -- , Layout Accordion -- For extension Combo: -- , combo (twoPane 0.03 0.5) [(full,1),(tabbed shrinkText defaultTConf,1)] -- For extension Dishes: -- , Layout $ Dishes 2 (1%6) -- For extension Grid: -- , Layout Grid -- For extension HintedTile: -- , XMonadContrib.HintedTile.tall nmaster delta ratio -- For extension LayoutHints: -- , layoutHints $ tiled -- , layoutHints $ Mirror tiled -- For extension MagicFocus: -- , Layout $ MagicFocus tiled -- , Layout $ MagicFocus $ Mirror tiled -- For extension Magnifier: -- , magnifier tiled -- , magnifier $ mirror tiled -- For extension Maximize: -- , Layout $ maximize $ tiled -- For extension Mosaic: -- , mosaic 0.25 0.5 M.empty -- For extension MosaicAlt: -- , Layout $ MosaicAlt M.empty -- For extension NoBorders: -- -- prepend noBorders to default layouts above to remove their borders, like so: -- , noBorders Full -- For extension Roledex: -- , Layout Roledex -- For extension Spiral: -- , Layout $ spiral (1 % 1) -- For extension Tabbed: -- , tabbed shrinkText defaultTConf -- For extension ThreeColumns: -- , ThreeCol nmaster delta ratio -- For extension TwoPane: -- , (Layout $ TwoPane 0.03 0.5) -- For extension WindowNavigation: -- -- include 'windowNavigation' in layoutHook definition above. -- -- just before the list, like the following (don't uncomment next line): -- -- layoutHook = Layout $ windowNavigation defaultWNConfig $ ... -- For extension WorkspaceDir: -- -- prepend 'map (workspaceDir "~")' to layouts definition above, -- -- just before the list, like the following (don't uncomment next line): -- -- layouts = map (workspaceDir "~") [ tiled, ... ] ] where -- default tiling algorithm partitions the screen into two panes tiled = Tall nmaster delta ratio -- The default number of windows in the master pane nmaster = 1 -- Default proportion of screen occupied by master pane ratio = 1%2 -- Percent of screen to increment by when resizing panes delta = 3%100 -- | The top level layout switcher. Most users will not need to modify this binding. -- -- By default, we simply switch between the layouts listed in `layouts' -- above, but you may program your own selection behaviour here. Layout -- transformers, for example, would be hooked in here. -- layoutHook :: Layout Window layoutHook = Layout $ Select layouts -- | Register with xmonad a list of layouts whose state we can preserve over restarts. -- There is typically no need to modify this list, the defaults are fine. -- serialisedLayouts :: [Layout Window] serialisedLayouts = layoutHook : layouts ------------------------------------------------------------------------ -- Logging -- | Perform an arbitrary action on each internal state change or X event. -- Examples include: -- * do nothing -- * log the state to stdout -- -- See the 'DynamicLog' extension for examples. -- logHook :: X () logHook = return () ------------------------------------------------------------------------ -- Key bindings: -- | The xmonad key bindings. Add, modify or remove key bindings here. -- -- (The comment formatting character is used when generating the manpage) -- keys :: M.Map (KeyMask, KeySym) (X ()) keys = M.fromList $ -- launching and killing programs [ ((modMask .|. shiftMask, xK_Return), spawn "aterm -tr -fade 70 +sb") -- %! Launch an xterm , ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu , ((modMask .|. shiftMask, xK_p ), spawn "gmrun") -- %! Launch gmrun , ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window , ((modMask, xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms , ((modMask .|. shiftMask, xK_space ), setLayout layoutHook) -- %! Reset the layouts on the current workspace to default , ((modMask, xK_n ), refresh) -- %! Resize viewed windows to the correct size -- move focus up or down the window stack , ((modMask, xK_Tab ), windows W.focusDown) -- %! Move focus to the next window , ((modMask, xK_j ), windows W.focusDown) -- %! Move focus to the next window , ((modMask, xK_k ), windows W.focusUp ) -- %! Move focus to the previous window , ((modMask, xK_m ), windows W.focusMaster ) -- %! Move focus to the master window -- modifying the window order , ((modMask, xK_Return), windows W.swapMaster) -- %! Swap the focused window and the master window , ((modMask .|. shiftMask, xK_j ), windows W.swapDown ) -- %! Swap the focused window with the next window , ((modMask .|. shiftMask, xK_k ), windows W.swapUp ) -- %! Swap the focused window with the previous window -- resizing the master/slave ratio , ((modMask, xK_h ), sendMessage Shrink) -- %! Shrink the master area , ((modMask, xK_l ), sendMessage Expand) -- %! Expand the master area -- floating layer support , ((modMask, xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling -- increase or decrease number of windows in the master area , ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area , ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area -- toggle the status bar gap , ((modMask , xK_b ), modifyGap (\i n -> let x = (defaultGaps ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap -- quit, or restart , ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad , ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad -- % Extension-provided key bindings -- For extension Commands: -- , ((modMask .|. controlMask, xK_y), runCommand commands) -- For extension CopyWindow: -- -- comment out default close window binding above if you uncomment this: -- , ((modMask .|. shiftMask, xK_c ), kill1) -- @@ Close the focused window -- For extension CycleWS: -- , ((modMask, xK_Right), nextWS) -- , ((modMask, xK_Left), prevWS) -- , ((modMask .|. shiftMask, xK_Right), shiftToNext) -- , ((modMask .|. shiftMask, xK_Left), shiftToPrev) -- For extension DeManage: -- , ((modMask, xK_d ), withFocused demanage) -- For extension DwmPromote: -- , ((modMask, xK_Return), dwmpromote) -- For extension FindEmptyWorkspace: -- , ((modMask, xK_m ), viewEmptyWorkspace) -- , ((modMask .|. shiftMask, xK_m ), tagToEmptyWorkspace) -- For extension LayoutScreens: -- , ((modMask .|. shiftMask, xK_space), layoutScreens 2 (twoPane 0.5 0.5)) -- , ((controlMask .|. modMask .|. shiftMask, xK_space), rescreen) -- For extension Mosaic: -- , ((controlMask .|. modMask .|. shiftMask, xK_h), withNamedWindow (sendMessage . tallWindow)) -- , ((controlMask .|. modMask .|. shiftMask, xK_l), withNamedWindow (sendMessage . wideWindow)) -- , ((modMask .|. shiftMask, xK_h ), withNamedWindow (sendMessage . shrinkWindow)) -- , ((modMask .|. shiftMask, xK_l ), withNamedWindow (sendMessage . expandWindow)) -- , ((modMask .|. shiftMask, xK_s ), withNamedWindow (sendMessage . squareWindow)) -- , ((modMask .|. shiftMask, xK_o ), withNamedWindow (sendMessage . myclearWindow)) -- , ((controlMask .|. modMask .|. shiftMask, xK_o ), withNamedWindow (sendMessage . flexibleWindow)) -- For extension RotSlaves: -- , ((modMask .|. shiftMask, xK_Tab ), rotSlavesUp) -- For extension RotView: -- , ((modMask .|. shiftMask, xK_Right), rotView True) -- , ((modMask .|. shiftMask, xK_Left), rotView False) -- For extension ShellPrompt: -- , ((modMask .|. controlMask, xK_x), shellPrompt defaultXPConfig) -- For extension SimpleDate: -- , ((modMask, xK_d ), date) -- For extension SinkAll: -- , ((modMask .|. shiftMask, xK_t), sinkAll) -- For extension SshPrompt: -- , ((modMask .|. controlMask, xK_s), sshPrompt defaultXPConfig) -- For extension Submap: -- , ((modMask, xK_a), submap . M.fromList $ -- [ ((0, xK_n), spawn "mpc next") -- , ((0, xK_p), spawn "mpc prev") -- , ((0, xK_z), spawn "mpc random") -- , ((0, xK_space), spawn "mpc toggle") -- ]) -- For extension Warp: -- , ((modMask, xK_z ), warpToWindow (1%2) (1%2)) -- @@ Move pointer to currently focused window -- For extension WindowBringer: -- , ((modMask .|. shiftMask, xK_g ), gotoMenu) -- , ((modMask .|. shiftMask, xK_b ), bringMenu) -- For extension WindowNavigation: -- , ((modMask, xK_Right), sendMessage $ Go R) -- , ((modMask, xK_Left), sendMessage $ Go L) -- , ((modMask, xK_Up), sendMessage $ Go U) -- , ((modMask, xK_Down), sendMessage $ Go D) -- , ((modMask .|. controlMask, xK_Right), sendMessage $ Swap R) -- , ((modMask .|. controlMask, xK_Left), sendMessage $ Swap L) -- , ((modMask .|. controlMask, xK_Up), sendMessage $ Swap U) -- , ((modMask .|. controlMask, xK_Down), sendMessage $ Swap D) -- For extension WindowPrompt: -- , ((modMask .|. shiftMask, xK_g ), windowPromptGoto defaultXPConfig) -- , ((modMask .|. shiftMask, xK_b ), windowPromptBring defaultXPConfig) -- For extension WorkspaceDir: -- , ((modMask .|. shiftMask, xK_x ), changeDir defaultXPConfig) -- For extension XMonadPrompt: -- , ((modMask .|. controlMask, xK_x), xmonadPrompt defaultXPConfig) ] ++ -- mod-[1..9] %! Switch to workspace N -- mod-shift-[1..9] %! Move client to workspace N [((m .|. modMask, k), windows $ f i) | (i, k) <- zip workspaces [xK_1 .. xK_9] , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]] ++ -- mod-{w,e,r} %! Switch to physical/Xinerama screens 1, 2, or 3 -- mod-shift-{w,e,r} %! Move client to screen 1, 2, or 3 [((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f)) | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..] , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]] -- % Extension-provided key bindings lists -- For extension CopyWindow: -- ++ -- -- mod-[1..9] @@ Switch to workspace N -- -- mod-shift-[1..9] @@ Move client to workspace N -- -- mod-control-shift-[1..9] @@ Copy client to workspace N -- [((m .|. modMask, k), f i) -- | (i, k) <- zip workspaces [xK_1 ..] -- , (f, m) <- [(view, 0), (shift, shiftMask), (copy, shiftMask .|. controlMask)]] -- For extension SwapWorkspaces: -- ++ -- [((modMask .|. controlMask, k), windows $ swapWithCurrent i) -- | (i, k) <- zip workspaces [xK_1 ..]] -- For extension Warp: -- ++ -- -- mod-ctrl-{w,e,r} @@ Move mouse pointer to screen 1, 2, or 3 -- [((modMask .|. controlMask, key), warpToScreen sc (1%2) (1%2)) -- | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]] -- | Mouse bindings: default actions bound to mouse events -- mouseBindings :: M.Map (KeyMask, Button) (Window -> X ()) mouseBindings = M.fromList $ -- mod-button1 %! Set the window to floating mode and move by dragging [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w)) -- mod-button2 %! Raise the window to the top of the stack , ((modMask, button2), (\w -> focus w >> windows W.swapMaster)) -- mod-button3 %! Set the window to floating mode and resize by dragging , ((modMask, button3), (\w -> focus w >> mouseResizeWindow w)) -- you may also bind events to the mouse scroll wheel (button4 and button5) -- % Extension-provided mouse bindings -- For extension FlexibleManipulate: -- , ((modMask, button1), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) -- For extension FlexibleResize: -- , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w)) ] -- % Extension-provided definitions -- For extension Commands: -- commands :: [(String, X ())] -- commands = defaultCommands -- For extension DynamicLog: -- -- comment out default logHook definition above if you uncomment any of these: -- logHook = dynamicLog -- logHook = dynamicLogWithTitle -- logHook = dynamicLogWithTitleColored "white" -- For extension EwmhDesktops: -- -- comment out default logHook definition above if you uncomment this: -- logHook = ewmhDesktopsLogHook -- For extension ManageDocks: -- -- comment out default manageHook definition above if you uncomment this: -- manageHook w _ _ _ = manageDocksHook w