[xmonad] Quite difficult hack
Andrea Spada
andreaspada.mail at gmail.com
Thu May 22 18:19:02 EDT 2008
Hi, folks! I'm trying to set to functions in my xmonad.hs, without
success.
I need to change my workspace with functions keys, not as normal with
numbers. I had try the Droundy.hs method, but it not work on my config.
Also, I want to have my opacity change on focus in and out. Anyone
knows how can I achive this with transet-df?
Belowe, some of my config:
--- start here
import XMonad
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.EwmhDesktops
import qualified XMonad.StackSet as W
import Data.Bits ((.|.))
import System.Exit
import System.IO
import qualified Data.Map as M
import XMonad.Layout.TwoPane
import XMonad.Layout.ResizableTile
import XMonad.Layout.Tabbed
import XMonad.Layout.Combo
import XMonad.Layout.WindowNavigation
import XMonad.Layout.ShowWName
-- Actions
import XMonad.Actions.CycleWS
import XMonad.Actions.SwapWorkspaces
import XMonad.Actions.Submap
import XMonad.Actions.DwmPromote
import XMonad.Actions.UpdatePointer
--Utils
import XMonad.Util.EZConfig
main = xmonad $ defaultConfig
{ borderWidth = 2
, focusedBorderColor = "#ffa434"
, normalBorderColor = "#2e3436"
, manageHook = myManageHook <+> manageDocks
, workspaces = map show [1 .. 12 :: Int]
, terminal = "Terminal"
, modMask = mod4Mask
, logHook = myLogHook
, layoutHook = showWName $ windowNavigation $ (avoidStruts
(tall ||| Mirror tall ||| myT , keys = myKeys
}
where
etc, etc, etc...
myLogHook :: X ()
myLogHook = do ewmhDesktopsLogHook
return () >> updatePointer (Relative 1 1)
etc, etc, etc...
myKeys = \conf -> mkKeymap conf $
etc, etc, etc...
--Shift workspaces
++
[ (m ++ i, windows $ f j)
| (i, j) <- zip (map show [1..12])
, (m, f) <- [("M-", W.greedyView),
]
etc, etc, etc...
]
thank's a lot,
Andrea
More information about the xmonad
mailing list