xmonad/xmonad.hs
author Fabien Ninoles <fabien@tzone.org>
Sun, 13 Sep 2015 14:47:26 -0400
changeset 14 6348b9f842b2
parent 0 df7496e40bee
permissions -rw-r--r--
Move back to non-shifty awesomeness.
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
0
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     1
-- Import statements
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     2
import XMonad
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     3
-- import XMonad.Config.Gnome
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     4
import XMonad.Hooks.DynamicLog
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     5
import XMonad.Hooks.ManageDocks
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     6
import XMonad.Hooks.EwmhDesktops
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     7
import XMonad.Hooks.Place
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     8
import XMonad.Hooks.FadeInactive
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
     9
import XMonad.Hooks.UrgencyHook
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    10
import XMonad.Config.Gnome
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    11
import XMonad.Util.Run
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    12
import XMonad.Util.EZConfig
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    13
import XMonad.Actions.CycleWS
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    14
import XMonad.Actions.Promote
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    15
import XMonad.Actions.RotSlaves
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    16
import qualified XMonad.StackSet as S
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    17
import System.IO
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    18
import XMonad.Layout.NoBorders
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    19
import XMonad.Layout.Tabbed
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    20
import XMonad.Layout.Spiral
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    21
import XMonad.Layout.MosaicAlt
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    22
import XMonad.Layout.ThreeColumns
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    23
import qualified Data.Map as M
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    24
import System.Exit
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    25
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    26
-- defines
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    27
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    28
myModMask = mod4Mask -- Windows key
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    29
myTerminal = "x-terminal-emulator"
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    30
myWorkspaces = ["1", "2", "3", "4", "5", "6", "7", "8", "9", "0"]
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    31
upperRowKeys = [ xK_quotedbl, 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    32
                 xK_guillemotleft, 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    33
                 xK_guillemotright,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    34
                 xK_parenleft,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    35
                 xK_parenright,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    36
                 xK_at,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    37
                 xK_plus,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    38
                 xK_minus,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    39
                 xK_slash,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    40
                 xK_asterisk ]
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    41
numberOfWS = 4
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    42
               
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    43
myWSKeys = [ ((m .|. myModMask, k), windows $ f i)
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    44
           | (i, k) <- take numberOfWS (zip myWorkspaces upperRowKeys),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    45
             (f, m) <- [(S.greedyView, 0), (S.shift, shiftMask)]]
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    46
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    47
-- X Y W H
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    48
myDefaultDialogSize = S.RationalRect (1/4) (1/4) (1/2) (1/2)
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    49
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    50
myKeys = [ 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    51
    ((myModMask .|. shiftMask, xK_Return        ), spawn $ myTerminal),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    52
    ((myModMask,               xK_m             ), windows S.focusMaster ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    53
    ((myModMask .|. shiftMask, xK_m             ), promote ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    54
    ((myModMask .|. shiftMask, xK_Tab           ), rotAllUp ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    55
    ((myModMask              , xK_space         ), sendMessage NextLayout),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    56
    ((myModMask,               xK_q             ), kill),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    57
    ((myModMask .|. shiftMask, xK_q             ), io (exitWith ExitSuccess)),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    58
    ((myModMask .|. shiftMask, xK_r             ), spawn "xmonad --recompile && xmonad --restart"),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    59
    (( 0,                      xK_Print         ), spawn "gnome-screenshot -i"),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    60
    ((myModMask,               xK_b             ), sendMessage ToggleStruts),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    61
    -- S.
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    62
    ((myModMask,               xK_d             ), withFocused $ windows . (`S.float` myDefaultDialogSize)),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    63
    ((myModMask .|. shiftMask, xK_d             ), withFocused $ windows . S.sink),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    64
    -- ((myModMask .|. shiftMask, xK_b             ), sendMessage (SetStruts [D] [])),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    65
    
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    66
    -- Vi-like bindings for modifying layout
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    67
    ((myModMask,                 xK_t             ), windows S.focusDown ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    68
    ((myModMask,                 xK_s             ), windows S.focusUp ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    69
    ((myModMask .|. shiftMask  , xK_t             ), windows S.swapDown ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    70
    ((myModMask .|. shiftMask  , xK_s             ), windows S.swapUp ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    71
    ((myModMask .|. controlMask, xK_t             ), sendMessage Shrink ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    72
    ((myModMask .|. controlMask, xK_s             ), sendMessage Expand ),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    73
    ((myModMask .|. shiftMask  , xK_n             ), sendMessage (IncMasterN (1))),
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    74
    ((myModMask                , xK_n             ), sendMessage (IncMasterN (-1)))
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    75
    ] ++ myWSKeys
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    76
         
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    77
         
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    78
fib :: Int -> Int
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    79
fib 0 = 0
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    80
fib 1 = 1
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    81
fib n = fib (n-1) + fib (n-2)
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    82
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    83
golden :: Int -> Rational
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    84
golden n = toRational (fib n) / toRational (fib (n-1))
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    85
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    86
myLayouts = tall ||| threeCol ||| Mirror tall ||| threeCol ||| mosaic ||| simpleTabbed ||| Full
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    87
  where 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    88
    mosaic = MosaicAlt M.empty
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    89
    mySpiral = spiral ratio
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    90
    tall = Tall nmaster delta ratio
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    91
    threeCol = ThreeCol nmaster delta ratio
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    92
    nmaster = 2
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    93
    delta = 3/100
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    94
    ratio = 2/3
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    95
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    96
fadingHook = fadeInactiveLogHook fadeAmount
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    97
  where fadeAmount = 0.7
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    98
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
    99
-- Run
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   100
main = do
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   101
  xmproc <- spawnPipe "xmobar"  
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   102
  xmonad 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   103
    $ withUrgencyHook dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] }
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   104
    $ ewmh 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   105
    $ gnomeConfig { 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   106
    terminal = myTerminal,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   107
    borderWidth = 0,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   108
    focusFollowsMouse = False,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   109
    workspaces = take numberOfWS myWorkspaces,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   110
    manageHook = manageDocks <+> 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   111
                 placeHook (smart (0.5, 0.5)) <+> 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   112
                 manageHook defaultConfig,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   113
    layoutHook = avoidStruts $ myLayouts,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   114
    logHook = fadingHook >> dynamicLogWithPP xmobarPP {
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   115
      ppOutput = hPutStrLn xmproc,
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   116
      ppTitle = xmobarColor "green" "" . shorten 50 
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   117
      },
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   118
    modMask = myModMask -- windows key
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   119
    } `removeKeys` [
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   120
      (myModMask, xK_Return)
df7496e40bee Initial configuration files.
Fabien Ninoles <fabien@tzone.org>
parents:
diff changeset
   121
    ] `additionalKeys` myKeys