[Haskell-cafe] About xmonad
zaxis
z_axis at 163.com
Mon Nov 16 06:09:18 EST 2009
I have subscribed to xmonad maillist but i never received any email !
Deniz Dogan-3 wrote:
>
> 2009/11/16 zaxis <z_axis at 163.com>:
>>
>> %uname -a
>> Linux myarch 2.6.31-ARCH #1 SMP PREEMPT Tue Nov 10 19:48:17 CET 2009 i686
>> AMD Athlon(tm) 64 X2 Dual Core Processor 3600+ AuthenticAMD GNU/Linux
>>
>> %xmonad --version
>> xmonad 0.9
>>
>> In firefox, the `save as` dialog doesnot appear when i want to choose
>> picture to save by right clicking the mouse.
>>
>> %cat ~/.xmonad/xmonad.hs
>> import XMonad
>>
>> import XMonad.Hooks.ManageDocks
>> import XMonad.Hooks.EwmhDesktops
>> import XMonad.Hooks.DynamicLog
>> import XMonad.Hooks.ManageHelpers
>>
>> import XMonad.Util.Run(spawnPipe)
>>
>> import XMonad.Layout.TwoPane
>> import XMonad.Layout.WindowNavigation
>>
>> import qualified XMonad.StackSet as W
>> import qualified Data.Map as M
>>
>> main = do
>> xmonad $ defaultConfig
>> { borderWidth = 1
>> , focusedBorderColor = "#ff6666"
>> , normalBorderColor = "#2222aa"
>> , manageHook = manageHook defaultConfig <+> myManageHook
>> , workspaces = map show [1 .. 10 :: Int]
>> , terminal = "roxterm"
>> , modMask = mod4Mask
>> , focusFollowsMouse = True
>> , startupHook = myStartupHook
>> , logHook = myLogHook
>> , layoutHook = windowNavigation $ avoidStruts $ (Mirror
>> tall ||| tall ||| Full)
>> --, layoutHook = ewmhDesktopsLayout $ windowNavigation $
>> avoidStruts $ (Mirror tall ||| tall ||| Full)
>> , keys = \c -> myKeys c `M.union` keys
>> defaultConfig
>> c
>> --, mouseBindings = \c -> myMouse c `M.union` mouseBindings
>> defaultConfig c
>> }
>> where
>> tall = Tall 1 (3/100) (1/2)
>>
>> myStartupHook :: X ()
>> myStartupHook = do {
>> spawn "fcitx";
>> spawn "roxterm";
>> spawn "lxpanel";
>> spawn "/home/sw2wolf/bin/kvm.sh";
>> }
>> myLogHook :: X ()
>> myLogHook = ewmhDesktopsLogHook
>>
>> myManageHook :: ManageHook
>> myManageHook = composeAll . concat $
>> [ [ className =? c --> doFloat | c <- myCFloats]
>> ,[ resource =? r --> doFloat | r <- myRFloats]
>> ,[ title =? t --> doFloat | t <- myTFloats]
>> ,[ className =? c --> doIgnore | c <- ignores]
>> ,[ className =? "Audacious" --> doShift "3" ]
>> ,[ className =? "Firefox" --> doF W.swapDown]
>> ,[(role =? "gimp-toolbox" <||> role =?
>> "gimp-image-window") --> (ask >>= doF . W.sink)]]
>> where myCFloats = ["Thunderbird-bin", "GQview",
>> "MPlayer", "Gimp","Vncviewer","Xmessage"]
>> myRFloats = ["Dialog", "Download", "Places"]
>> myTFloats = ["Firefox Preferences", "Element
>> Properties"]
>> ignores = ["trayer"]
>> role = stringProperty "WM_WINDOW_ROLE"
>>
>> myKeys (XConfig {modMask = modm}) = M.fromList $
>> -- Apps and tools
>> [ ((modm, xK_F2), spawn "gmrun")
>> , ((modm, xK_f), spawn "/home/firefox/firefox")
>> , ((modm, xK_t), spawn "thunderbird")
>> --, ((modm, xK_p), spawn "exe=`dmenu_path | dmenu -b` && eval
>> \"exec $exe\"")
>> , ((modm, xK_F11), spawn "sudo shutdown -r now")
>> , ((modm, xK_F12), spawn "sudo shutdown -h now")
>> , ((modm .|. controlMask, xK_Print), spawn "sleep 0.2; scrot
>> -s")
>> , ((modm, xK_Print), spawn "scrot
>> '/tmp/%Y-%m-%d_%H:%M:%S_$wx$h_scrot.png' -e 'mv $f ~'")
>> , ((modm, xK_c), kill)
>> -- Window Navigation
>> , ((modm, xK_Right), sendMessage $ Go R)
>> , ((modm, xK_Left ), sendMessage $ Go L)
>> , ((modm, xK_Up ), sendMessage $ Go U)
>> , ((modm, xK_Down ), sendMessage $ Go D)
>> -- swap...
>> , ((modm .|. controlMask, xK_Right), sendMessage $ Swap R)
>> , ((modm .|. controlMask, xK_Left ), sendMessage $ Swap L)
>> , ((modm .|. controlMask, xK_Up ), sendMessage $ Swap U)
>> , ((modm .|. controlMask, xK_Down ), sendMessage $ Swap D)
>> ]
>>
>> -----
>> fac n = foldr (*) 1 [1..n]
>> --
>> View this message in context:
>> http://old.nabble.com/About-xmonad-tp26367498p26367498.html
>> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
> You should try asking on the xmonad mailing list:
> http://www.haskell.org/mailman/listinfo/xmonad
>
> --
> Deniz Dogan
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-----
fac n = foldr (*) 1 [1..n]
--
View this message in context: http://old.nabble.com/About-xmonad-tp26367498p26370168.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
More information about the Haskell-Cafe
mailing list