Difference between revisions of "Xmonad/Config archive/And1's xmonad.hs"

From HaskellWiki
Jump to navigation Jump to search
m
m
Line 14: Line 14:
 
import XMonad.Hooks.UrgencyHook
 
import XMonad.Hooks.UrgencyHook
 
import XMonad.Layout.HintedTile
 
import XMonad.Layout.HintedTile
  +
import XMonad.Layout.ResizableTile
 
import XMonad.Layout.LayoutHints
 
import XMonad.Layout.LayoutHints
 
import XMonad.Layout.PerWorkspace
 
import XMonad.Layout.PerWorkspace
Line 29: Line 30:
   
 
main = do
 
main = do
din <- spawnPipe myStatusBar
+
dzen <- spawnPipe myStatusBar
din2 <- spawnPipe myTopBar
+
dzentop <- spawnPipe myTopBar
din3 <- spawnPipe myBottomBar
+
dzenbottom <- spawnPipe myBottomBar
 
dynHooksRef <- initDynamicHooks
 
dynHooksRef <- initDynamicHooks
 
xmonad $ myUrgencyHook $ defaultConfig
 
xmonad $ myUrgencyHook $ defaultConfig
Line 45: Line 46:
 
, focusedBorderColor = "#0077cc"
 
, focusedBorderColor = "#0077cc"
 
, layoutHook = myLayout
 
, layoutHook = myLayout
, logHook = dynamicLogWithPP $ myDzenPP din
+
, logHook = dynamicLogWithPP $ myDzenPP dzen
 
, manageHook = myManageHook <+> manageDocks <+> dynamicMasterHook dynHooksRef
 
, manageHook = myManageHook <+> manageDocks <+> dynamicMasterHook dynHooksRef
 
, workspaces = ["1:irc", "2:www", "3:music", "4:nicotine", "5:misc"]
 
, workspaces = ["1:irc", "2:www", "3:music", "4:nicotine", "5:misc"]
Line 60: Line 61:
   
 
-- Layout options:
 
-- Layout options:
myLayout = avoidStruts $ layoutHints $ onWorkspace "1:irc" (hintedTile Wide ||| hintedTile Tall) $ (Full ||| hintedTile Wide ||| hintedTile Tall)
+
myLayout = avoidStruts $ layoutHints $ onWorkspace "1:irc" (Mirror resizableTile ||| resizableTile) $ (Full ||| hintedTile Wide ||| hintedTile Tall)
 
where
 
where
 
hintedTile = HintedTile nmaster delta ratio TopLeft
 
hintedTile = HintedTile nmaster delta ratio TopLeft
  +
resizableTile = ResizableTall nmaster delta ratio []
 
nmaster = 1
 
nmaster = 1
 
ratio = toRational (2/(1+sqrt(5)::Double))
 
ratio = toRational (2/(1+sqrt(5)::Double))
Line 83: Line 85:
 
-- Key bindings:
 
-- Key bindings:
 
myKeys dynHooksRef conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
 
myKeys dynHooksRef conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
[ ((mod4Mask, xK_q), spawn "urxvt -g 120x40+20+30 -e ssh and1@dg.net")
+
[ ((mod4Mask, xK_q), spawn "urxvt -g 120x40+20+30 -e ssh user@domain.net")
 
, ((mod4Mask, xK_w), spawn "nitrogen --sort=alpha /home/and1/wallpapers/")
 
, ((mod4Mask, xK_w), spawn "nitrogen --sort=alpha /home/and1/wallpapers/")
 
, ((mod4Mask, xK_e), spawn "iceweasel")
 
, ((mod4Mask, xK_e), spawn "iceweasel")
 
, ((mod4Mask, xK_r), oneShotHook dynHooksRef (className =? "URxvt") (doF $ (W.swapDown . W.shiftMaster)) >> spawn "urxvt -g 120x40+20+30")
 
, ((mod4Mask, xK_r), oneShotHook dynHooksRef (className =? "URxvt") (doF $ (W.swapDown . W.shiftMaster)) >> spawn "urxvt -g 120x40+20+30")
 
, ((mod4Mask .|. shiftMask, xK_r), oneShotHook dynHooksRef (className =? "URxvt") (doF $ (W.swapUp . W.shiftMaster)) >> spawn "urxvt -g 120x40+20+30")
 
, ((mod4Mask .|. shiftMask, xK_r), oneShotHook dynHooksRef (className =? "URxvt") (doF $ (W.swapUp . W.shiftMaster)) >> spawn "urxvt -g 120x40+20+30")
, ((mod4Mask, xK_t), spawn "icedove")
 
 
, ((mod4Mask, xK_o), spawn "openoffice")
 
, ((mod4Mask, xK_o), spawn "openoffice")
 
, ((mod4Mask, xK_p), shellPrompt myXPConfig)
 
, ((mod4Mask, xK_p), shellPrompt myXPConfig)
  +
, ((mod4Mask, xK_d), spawn "date +'%Y-%m-%d %H:%M' | osd_cat -p bottom -A center -s 2 -c '#a10a30' -f '-xos4-terminus-medium-r-normal-*-140-*-*-*-c-*-iso10646-1'")
  +
, ((mod4Mask .|. shiftMask, xK_d), spawn "date +'%H:%M' | osd_cat -p middle -A center -s 2 -c '#a10a30' -f '-xos4-terminus-medium-r-normal-*-140-*-*-*-c-*-iso10646-1'")
 
, ((mod4Mask, xK_l), spawn "slock")
 
, ((mod4Mask, xK_l), spawn "slock")
 
, ((mod4Mask, xK_x), spawn "schroot -p gmpc")
 
, ((mod4Mask, xK_x), spawn "schroot -p gmpc")
Line 108: Line 111:
 
, ((modMask, xK_period), sendMessage (IncMasterN (-1))) -- deincrement the number of windows in the master area
 
, ((modMask, xK_period), sendMessage (IncMasterN (-1))) -- deincrement the number of windows in the master area
 
, ((modMask, xK_Return), windows W.focusMaster) -- move focus to the master window
 
, ((modMask, xK_Return), windows W.focusMaster) -- move focus to the master window
-- , ((modMask, xK_Up), windows W.focusUp) -- move focus to the previous window
 
-- , ((modMask, xK_Down), windows W.focusDown) -- move focus to the next window
 
 
, ((modMask .|. shiftMask, xK_Tab), windows W.focusUp) -- move focus to the previous window
 
, ((modMask .|. shiftMask, xK_Tab), windows W.focusUp) -- move focus to the previous window
 
, ((modMask .|. shiftMask, xK_h), sendMessage Shrink) -- shrink the master area
 
, ((modMask .|. shiftMask, xK_h), sendMessage Shrink) -- shrink the master area
Line 115: Line 116:
 
, ((modMask .|. shiftMask, xK_k), windows W.swapDown) -- swap the focused window with the next window
 
, ((modMask .|. shiftMask, xK_k), windows W.swapDown) -- swap the focused window with the next window
 
, ((modMask .|. shiftMask, xK_l), sendMessage Expand) -- expand the master area
 
, ((modMask .|. shiftMask, xK_l), sendMessage Expand) -- expand the master area
-- , ((modMask .|. shiftMask, xK_Up), sendMessage Shrink) -- shrink the master area
 
-- , ((modMask .|. shiftMask, xK_Down), sendMessage Expand) -- expand the master area
 
 
, ((modMask .|. controlMask, xK_q), io (exitWith ExitSuccess)) -- quit xmonad
 
, ((modMask .|. controlMask, xK_q), io (exitWith ExitSuccess)) -- quit xmonad
 
, ((modMask .|. controlMask, xK_r), spawn "killall conky dzen2" >> restart "xmonad" True) -- restart xmonad
 
, ((modMask .|. controlMask, xK_r), spawn "killall conky dzen2" >> restart "xmonad" True) -- restart xmonad
 
, ((modMask .|. controlMask, xK_d), withFocused $ windows . W.sink) -- push window back into tiling
 
, ((modMask .|. controlMask, xK_d), withFocused $ windows . W.sink) -- push window back into tiling
 
, ((modMask .|. controlMask, xK_f), setLayout $ XMonad.layoutHook conf) -- reset the layouts on the current workspace to default
 
, ((modMask .|. controlMask, xK_f), setLayout $ XMonad.layoutHook conf) -- reset the layouts on the current workspace to default
 
, ((modMask .|. controlMask, xK_h), sendMessage MirrorExpand) -- expand the height/wide
 
, ((modMask .|. controlMask, xK_l), sendMessage MirrorShrink) -- shrink the height/wide
 
, ((modMask .|. controlMask, xK_x), kill) -- close focused window
 
, ((modMask .|. controlMask, xK_x), kill) -- close focused window
-- , ((modMask .|. controlMask, xK_Left), windows W.swapUp) -- swap the focused window with the previous window
 
-- , ((modMask .|. controlMask, xK_Right), windows W.swapDown) -- swap the focused window with the next window
 
-- , ((modMask .|. controlMask, xK_Up), sendMessage (IncMasterN 1)) -- increment the number of windows in the master area
 
-- , ((modMask .|. controlMask, xK_Down), sendMessage (IncMasterN (-1))) -- deincrement the number of windows in the master area
 
 
]
 
]
 
++
 
++
Line 176: Line 173:
 
"Hinted Wide" -> "^fg(#777777)^i(/home/and1/.dzen/layout-mirror-bottom.xbm)"
 
"Hinted Wide" -> "^fg(#777777)^i(/home/and1/.dzen/layout-mirror-bottom.xbm)"
 
"Hinted Full" -> "^fg(#777777)^i(/home/and1/.dzen/layout-full.xbm)"
 
"Hinted Full" -> "^fg(#777777)^i(/home/and1/.dzen/layout-full.xbm)"
  +
"Hinted ResizableTall" -> "^fg(#777777)^i(/home/and1/.dzen/layout-tall-right.xbm)"
  +
"Hinted Mirror ResizableTall" -> "^fg(#777777)^i(/home/and1/.dzen/layout-mirror-bottom.xbm)"
  +
_ -> x
 
)
 
)
 
, ppOutput = hPutStrLn h
 
, ppOutput = hPutStrLn h
Line 195: Line 195:
 
"Hinted Wide" -> "[-]"
 
"Hinted Wide" -> "[-]"
 
"Hinted Full" -> "[ ]"
 
"Hinted Full" -> "[ ]"
  +
"Hinted ResizableTall" -> "[|]"
  +
"Hinted Mirror ResizableTall" -> "[-]"
  +
_ -> x
 
)
 
)
 
, ppOutput = hPutStrLn h
 
, ppOutput = hPutStrLn h
 
}
 
}
 
 
</haskell>
 
</haskell>
   

Revision as of 14:59, 3 January 2009

xmonad.hs

------------------------------------------------------------------------
-- ~/.xmonad/xmonad.hs
-- validate syntax: xmonad --recompile
------------------------------------------------------------------------

import XMonad hiding (Tall)
import XMonad.Actions.CycleWS
import XMonad.Hooks.DynamicHooks
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.UrgencyHook
import XMonad.Layout.HintedTile
import XMonad.Layout.ResizableTile
import XMonad.Layout.LayoutHints
import XMonad.Layout.PerWorkspace
import XMonad.ManageHook
import XMonad.Prompt
import XMonad.Prompt.Shell
import XMonad.Util.Run
import Graphics.X11
import System.Exit
import System.IO

import qualified Data.Map as M
import qualified XMonad.Actions.FlexibleResize as Flex
import qualified XMonad.StackSet as W

main = do
    dzen <- spawnPipe myStatusBar
    dzentop <- spawnPipe myTopBar
    dzenbottom <- spawnPipe myBottomBar
    dynHooksRef <- initDynamicHooks
    xmonad $ myUrgencyHook $ defaultConfig

       { terminal = "urxvt"
       , borderWidth = 1
       , keys = myKeys dynHooksRef
       , modMask = mod1Mask
       , numlockMask = mod2Mask
       , focusFollowsMouse = True
       , mouseBindings = myMouseBindings
       , normalBorderColor = "#0f0f0f"
       , focusedBorderColor = "#0077cc"
       , layoutHook = myLayout
       , logHook = dynamicLogWithPP $ myDzenPP dzen
       , manageHook = myManageHook <+> manageDocks <+> dynamicMasterHook dynHooksRef
       , workspaces = ["1:irc", "2:www", "3:music", "4:nicotine", "5:misc"]
       }

-- Statusbar options:
myStatusBar = "dzen2 -x '0' -y '0' -h '16' -w '1320' -ta 'l' -fg '#f0f0f0' -bg '#0f0f0f' -fn '-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1'"
myTopBar = "conky -c .conkytoprc | dzen2 -x '1320' -y '0' -h '16' -w '600' -ta 'r' -fg '#555555' -bg '#0f0f0f' -fn '-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1'"
myBottomBar = "conky -c .conkybottomrc | dzen2 -x '0' -y '1184' -h '16' -w '1920' -ta 'l' -fg '#555555' -bg '#0f0f0f' -fn '-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1'"

-- Urgency hint options:
myUrgencyHook = withUrgencyHook dzenUrgencyHook
    { args = ["-x", "0", "-y", "1184", "-h", "16", "-w", "1920", "-ta", "r", "-expand", "l", "-fg", "#0099ff", "-bg", "#0f0f0f", "-fn", "-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1"] }

-- Layout options:
myLayout = avoidStruts $ layoutHints $ onWorkspace "1:irc" (Mirror resizableTile ||| resizableTile) $ (Full ||| hintedTile Wide ||| hintedTile Tall)
    where
    hintedTile = HintedTile nmaster delta ratio TopLeft
    resizableTile = ResizableTall nmaster delta ratio []
    nmaster = 1
    ratio = toRational (2/(1+sqrt(5)::Double))
    delta = 3/100

-- XPConfig options:
myXPConfig = defaultXPConfig
    { font = "-xos4-terminus-medium-r-normal-*-14-*-*-*-c-*-iso10646-1"
    , bgColor = "#222222"
    , fgColor = "#ffffff"
    , fgHLight = "#ffffff"
    , bgHLight = "#0066ff"
    , borderColor = "#ffffff"
    , promptBorderWidth = 1
    , position = Bottom
    , height = 16
    , historySize = 100
    }

-- Key bindings:
myKeys dynHooksRef conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
    [ ((mod4Mask, xK_q), spawn "urxvt -g 120x40+20+30 -e ssh user@domain.net")
    , ((mod4Mask, xK_w), spawn "nitrogen --sort=alpha /home/and1/wallpapers/")
    , ((mod4Mask, xK_e), spawn "iceweasel")
    , ((mod4Mask, xK_r), oneShotHook dynHooksRef (className =? "URxvt") (doF $ (W.swapDown . W.shiftMaster)) >> spawn "urxvt -g 120x40+20+30")
    , ((mod4Mask .|. shiftMask, xK_r), oneShotHook dynHooksRef (className =? "URxvt") (doF $ (W.swapUp . W.shiftMaster)) >> spawn "urxvt -g 120x40+20+30")
    , ((mod4Mask, xK_o), spawn "openoffice")
    , ((mod4Mask, xK_p), shellPrompt myXPConfig)
    , ((mod4Mask, xK_d), spawn "date +'%Y-%m-%d %H:%M' | osd_cat -p bottom -A center -s 2 -c '#a10a30' -f '-xos4-terminus-medium-r-normal-*-140-*-*-*-c-*-iso10646-1'")
    , ((mod4Mask .|. shiftMask, xK_d), spawn "date +'%H:%M' | osd_cat -p middle -A center -s 2 -c '#a10a30' -f '-xos4-terminus-medium-r-normal-*-140-*-*-*-c-*-iso10646-1'")
    , ((mod4Mask, xK_l), spawn "slock")
    , ((mod4Mask, xK_x), spawn "schroot -p gmpc")
    , ((mod4Mask, xK_n), spawn "nicotine")
    , ((mod4Mask, xK_Print), spawn "scrot screen_%Y-%m-%d.png -d 1") -- take screenshot
    , ((modMask .|. controlMask, xK_Home), spawn "mpc toggle") -- play/pause song
    , ((modMask .|. controlMask, xK_End), spawn "mpc stop") -- stop playback
    , ((modMask .|. controlMask, xK_Prior), spawn "mpc prev") -- previous song
    , ((modMask .|. controlMask, xK_Next), spawn "mpc next") -- next song
    , ((modMask, xK_Tab), windows W.focusDown) -- move focus to the next window
    , ((modMask, xK_f), sendMessage NextLayout) -- rotate through the available layout algorithms
    , ((modMask, xK_j), windows W.focusUp) -- move focus to the previous window
    , ((modMask, xK_k), windows W.focusDown) -- move focus to the next window
    , ((modMask, xK_n), refresh) -- resize viewed windows to the correct size
    , ((modMask, xK_m), windows W.swapMaster) -- swap the focused window and the master window
    , ((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
    , ((modMask, xK_Return), windows W.focusMaster) -- move focus to the master window
    , ((modMask .|. shiftMask, xK_Tab), windows W.focusUp) -- move focus to the previous window
    , ((modMask .|. shiftMask, xK_h), sendMessage Shrink) -- shrink the master area
    , ((modMask .|. shiftMask, xK_j), windows W.swapUp)  -- swap the focused window with the previous window
    , ((modMask .|. shiftMask, xK_k), windows W.swapDown) -- swap the focused window with the next window
    , ((modMask .|. shiftMask, xK_l), sendMessage Expand) -- expand the master area
    , ((modMask .|. controlMask, xK_q), io (exitWith ExitSuccess)) -- quit xmonad
    , ((modMask .|. controlMask, xK_r), spawn "killall conky dzen2" >> restart "xmonad" True) -- restart xmonad
    , ((modMask .|. controlMask, xK_d), withFocused $ windows . W.sink) -- push window back into tiling
    , ((modMask .|. controlMask, xK_f), setLayout $ XMonad.layoutHook conf) -- reset the layouts on the current workspace to default
    , ((modMask .|. controlMask, xK_h), sendMessage MirrorExpand) -- expand the height/wide
    , ((modMask .|. controlMask, xK_l), sendMessage MirrorShrink) -- shrink the height/wide
    , ((modMask .|. controlMask, xK_x), kill) -- close focused window
    ]
    ++
    [ ((m .|. modMask, k), windows $ f i)
    | (i, k) <- zip (XMonad.workspaces conf) [xK_F1 .. xK_F9] -- mod-[F1..F9], switch to workspace n
    , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)] -- mod-shift-[F1..F9], move window to workspace n
    ]
    ++
    [ ((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
    | (key, sc) <- zip [xK_F10, xK_F11, xK_F12] [0..] -- mod-{F10,F11,F12}, switch to physical/Xinerama screens 1, 2, or 3
    , (f, m) <- [(W.view, 0), (W.shift, shiftMask)] -- mod-shift-{F10,F11,F12}, move window to screen 1, 2, or 3
    ]
	
-- Mouse bindings:
myMouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
    [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w)) -- set the window to floating mode and move by dragging
    , ((modMask, button2), (\w -> focus w >> windows W.swapMaster)) -- raise the window to the top of the stack
    , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w)) -- set the window to floating mode and resize by dragging
    , ((modMask, button4), (\_ -> prevWS)) -- switch to previous workspace
    , ((modMask, button5), (\_ -> nextWS)) -- switch to next workspace
    ]

-- Window rules:
myManageHook = composeAll . concat $
    [ [className =? c --> doFloat | c <- myFloats]
    , [title =? t --> doFloat | t <- myOtherFloats]
    , [resource =? r --> doFloat | r <- myIgnores]
    , [className =? "Iceweasel" --> doF (W.shift "2:www")]
    , [className =? "Gmpc" --> doF (W.shift "3:music")]
    , [className =? "Nicotine" --> doF (W.shift "4:nicotine")]
    ]
    where
    myFloats = ["Ekiga", "Gimp", "gimp", "MPlayer", "Nitrogen", "Nvidia-settings", "Xmessage", "xmms"]
    myOtherFloats = ["Downloads", "Iceweasel Preferences", "Save As..."]
    myIgnores = []

-- dynamicLog pretty printer for dzen:
myDzenPP h = defaultPP
    { ppCurrent = wrap "^fg(#0099ff)^bg(#333333)^p()^i(/home/and1/.dzen/corner.xbm)^fg(#ffffff)" "^fg()^bg()^p()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppVisible = wrap "^fg(#ffffff)^bg(#333333)^p()^i(/home/and1/.dzen/corner.xbm)^fg(#ffffff)" "^fg()^bg()^p()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppHidden = wrap "^i(/home/and1/.dzen/corner.xbm)" "^fg()^bg()^p()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId -- don't use ^fg() here!!
    , ppHiddenNoWindows = wrap "^fg(#777777)^bg()^p()^i(/home/and1/.dzen/corner.xbm)" "^fg()^bg()^p()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppUrgent = wrap "^fg(#0099ff)^bg()^p()" "^fg()^bg()^p()" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppSep = " "
    , ppWsSep = " "
    , ppTitle = dzenColor "#ffffff" "" . wrap "< " " >"
    , ppLayout = dzenColor "#ffffff" "" .
        (\x -> case x of
        "Hinted Tall" -> "^fg(#777777)^i(/home/and1/.dzen/layout-tall-right.xbm)"
        "Hinted Wide" -> "^fg(#777777)^i(/home/and1/.dzen/layout-mirror-bottom.xbm)"
        "Hinted Full" -> "^fg(#777777)^i(/home/and1/.dzen/layout-full.xbm)"
        "Hinted ResizableTall" -> "^fg(#777777)^i(/home/and1/.dzen/layout-tall-right.xbm)"
        "Hinted Mirror ResizableTall" -> "^fg(#777777)^i(/home/and1/.dzen/layout-mirror-bottom.xbm)"
        _ -> x
        )
    , ppOutput = hPutStrLn h
    }

-- dynamicLog pretty printer for xmobar:
myXmobarPP h = defaultPP
    { ppCurrent = wrap "[<fc=#0099ff>" "</fc>]" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppVisible = wrap "[<fc=#ffffff>" "</fc>]" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppHidden = wrap "" "" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId -- don't use <fc> here!!
    , ppHiddenNoWindows = wrap "<fc=#555555>" "</fc>" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppUrgent = wrap "<fc=#0099ff>" "</fc>" . \wsId -> if (':' `elem` wsId) then drop 2 wsId else wsId
    , ppSep = " "
    , ppWsSep = " "
    , ppTitle = xmobarColor "#ffffff" "" . wrap "< " " >"
    , ppLayout = xmobarColor "#ffffff" "" .
        (\x -> case x of
        "Hinted Tall" -> "[|]"
        "Hinted Wide" -> "[-]"
        "Hinted Full" -> "[ ]"
        "Hinted ResizableTall" -> "[|]"
        "Hinted Mirror ResizableTall" -> "[-]"
        _ -> x
        )
    , ppOutput = hPutStrLn h
    }


.xinitrc

xcompmgr &
xset -b b off
xmodmap -e "keysym Super_R = SunCompose"
xsetroot -cursor_name left_ptr
nitrogen --restore
nvidia-settings -a GlyphCache=1
nvidia-settings -a InitialPixmapPlacement=2
export OOO_FORCE_DESKTOP=gnome
exec /home/and1/bin/xmonad