summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2015-07-03 22:08:18 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2015-07-03 22:08:18 +0200
commit7be34a8395dd7174e2dfb6b8b544a3ded6ffe66e (patch)
treec7721dfcc58f1bb75a752bcfc0408570043b2e57
parent211b05fc7a43d871134ba7c726e3b80872a94092 (diff)
downloaddotfiles-7be34a8395dd7174e2dfb6b8b544a3ded6ffe66e.tar
dotfiles-7be34a8395dd7174e2dfb6b8b544a3ded6ffe66e.tar.gz
dotfiles-7be34a8395dd7174e2dfb6b8b544a3ded6ffe66e.tar.bz2
dotfiles-7be34a8395dd7174e2dfb6b8b544a3ded6ffe66e.tar.xz
dotfiles-7be34a8395dd7174e2dfb6b8b544a3ded6ffe66e.zip
First work on xmonad.hs
-rw-r--r--.xmonad/xmonad.hs232
1 files changed, 232 insertions, 0 deletions
diff --git a/.xmonad/xmonad.hs b/.xmonad/xmonad.hs
new file mode 100644
index 0000000..c7402a6
--- /dev/null
+++ b/.xmonad/xmonad.hs
@@ -0,0 +1,232 @@
1import XMonad
2import XMonad.Hooks.DynamicLog
3import XMonad.Hooks.ManageDocks
4import XMonad.Util.Run
5import XMonad.Util.Loggers
6import XMonad.Util.EZConfig(additionalKeys)
7import System.IO
8import System.Environment
9import qualified Data.Map as Map
10import qualified XMonad.StackSet as W
11import System.Exit
12import Control.Monad.State (get)
13import XMonad.Layout.Spiral
14import Data.Ratio
15import Data.List
16import Data.Maybe (fromMaybe, listToMaybe)
17import XMonad.Layout.Tabbed
18import XMonad.Prompt
19import XMonad.Util.Scratchpad
20import Control.Monad (sequence, liftM, liftM2, join)
21import XMonad.Util.WorkspaceCompare
22import XMonad.Layout.NoBorders
23import XMonad.Layout.PerWorkspace
24import XMonad.Layout.SimplestFloat
25import XMonad.Layout.Renamed
26import XMonad.Layout.Reflect
27import System.Process
28import System.Directory (removeFile)
29import System.Posix.Files
30import System.FilePath ((</>))
31import Control.Concurrent
32import System.Posix.Process (getProcessID)
33import System.IO.Error
34import XMonad.Hooks.ManageHelpers hiding (CW)
35import XMonad.StackSet (RationalRect (..))
36import Control.Monad (when)
37import Graphics.X11.ExtraTypes.XF86
38import XMonad.Util.Cursor
39import XMonad.Actions.Warp
40
41import XMonad.Layout.IM
42
43wsp :: Int -> WorkspaceId
44wsp i = case Map.lookup i workspaceNames of
45 Just str -> (show i) ++ " " ++ str
46 Nothing -> (show i)
47wsps = map wsp
48
49main = do
50 xmobarProc <- spawnPipe "xmobar"
51 let myConfig = defaultConfig {
52 manageHook = manageDocks <+> manageHook'
53 , terminal = "urxvtc"
54 , layoutHook = smartBorders $ avoidStruts layout'
55 , logHook = dynamicLogWithPP xmobarPP'
56 , modMask = mod4Mask
57 , keys = myKeys'
58 , workspaces = take (length numKeys) workspaces'
59 , startupHook = assimilateKeychain >> (sequence autostart) >> (setDefaultCursor xC_left_ptr) >> banishScreen LowerRight >> return ()
60 , normalBorderColor = "#202020"
61 , focusedBorderColor = "white"
62 }
63 layout' = defaultLayouts
64 defaultLayouts = spiralWithDir East CW (1 % 2) ||| tabbedLayout tabbedBottom ||| noBorders Full ||| simplestFloat
65 tabbedLayout t = renamed [Replace "Tabbed"] $ reflectHoriz $ t CustomShrink $ tabbedTheme
66 tabbedTheme = defaultTheme { activeColor = "black"
67 , inactiveColor = "black"
68 , urgentColor = "black"
69 , activeBorderColor = "white"
70 , inactiveBorderColor = "#202020"
71 , urgentBorderColor = "#bb0000"
72 , activeTextColor = "white"
73 , inactiveTextColor = "white"
74 , urgentTextColor = "white"
75 , decoHeight = 16
76 }
77 xmobarPP' = xmobarPP { ppOutput = hPutStrLn xmobarProc
78 , ppTitle = shorten 50
79 , ppSort = (liftM2 (.)) getSortByIndex $ return scratchpadFilterOutWorkspace
80 , ppUrgent = wrap "(" ")" . xmobarColor "red" ""
81 , ppHiddenNoWindows = xmobarColor "#202020" "" . wrap "(" ")"
82 , ppVisible = wrap "(" ")" . xmobarColor "yellow" ""
83 , ppCurrent = wrap "(" ")" . xmobarColor "green" ""
84 , ppHidden = wrap "(" ")"
85 , ppWsSep = " "
86 , ppSep = " | "
87 }
88 xmonad $ myConfig
89
90autostart = [ spawnKeychain
91 ]
92
93spawnKeychain = runInTerm "" "keychain ~/.ssh/id_ecdsa ~/.ssh/id_rsa"
94
95assimilateKeychain :: X ()
96assimilateKeychain = liftIO $ assimilateKeychain' >> return ()
97assimilateKeychain' = tryIOError $ do
98 -- pid <- getProcessID
99 -- tmpDir <- lookupEnv "TMPDIR"
100 -- let tmpDir' = fromMaybe "/tmp" tmpDir
101 -- tmpFile = tmpDir' </> "xmonad-keychain" ++ (show pid) ++ ".env"
102 env <- runProcessWithInput "sh" ["-c", "eval $(keychain --eval --noask); env"] "" -- > " ++ tmpFile] ""
103 -- env <- readFile tmpFile
104 let envVars = Map.fromList $ map (\(k, v) -> (k, tail' v)) $ map (span (/= '=')) $ envLines
105 envVars' = Map.filterWithKey (\k _ -> k `elem` transfer) envVars
106 transfer = ["SSH_AUTH_SOCK", "SSH_AGENT_PID", "GPG_AGENT_INFO"]
107 envLines = filter (elem '=') $ lines env :: [String]
108 sequence $ map (\(k, c) -> setEnv k c) $ Map.toList envVars'
109 -- removeFile tmpFile
110 where
111 tail' [] = []
112 tail' (x:xs) = xs
113
114
115numKeys = [xK_parenleft, xK_parenright, xK_braceright, xK_plus, xK_braceleft, xK_bracketright, xK_bracketleft, xK_exclam, xK_equal, xK_asterisk]
116
117workspaces' = wsps [1..]
118workspaceNames = Map.fromList
119 []
120
121manageHook' = composeOne
122 []
123
124instance Shrinker CustomShrink where
125 shrinkIt _ "" = [""]
126 shrinkIt s cs = cs : shrinkIt s ((reverse . drop 4 . reverse $ cs) ++ "...")
127
128xPConfig = defaultXPConfig { bgColor = "black"
129 , fgColor = "white"
130 , fgHLight = "green"
131 , bgHLight = "black"
132 , borderColor = "white"
133 }
134
135myKeys' conf = Map.fromList $
136 -- launch a terminal
137 [ ((modm, xK_Return), spawn $ (XMonad.terminal conf) ++ " -e tmux")
138 , ((modm .|. controlMask, xK_Return), scratchpadSpawnActionCustom $ (XMonad.terminal conf) ++ " -name scratchpad -title scratchpad -e tmux")
139
140 -- launch dmenu
141 --, ((modm, xK_d ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
142 , ((modm, xK_d ), shellPrompt "Run: " xPConfig)
143 , ((modm .|. shiftMask, xK_d ), prompt "Run in Terminal: " ("urxvtc" ++ " -e") xPConfig)
144
145 -- close focused window
146 , ((modm .|. shiftMask, xK_q ), kill)
147
148 -- Rotate through the available layout algorithms
149 , ((modm, xK_space ), sendMessage NextLayout)
150
151 -- Reset the layouts on the current workspace to default
152 , ((modm , xK_r ), (setLayout $ XMonad.layoutHook conf) >> refresh)
153
154 -- Resize viewed windows to the correct size
155 -- , ((modm, xK_r ), refresh)
156
157 , ((modm, xK_BackSpace ), focusUrgent)
158
159 -- Move focus to the next window
160 , ((modm, xK_t ), windows W.focusDown)
161
162 -- Move focus to the previous window
163 , ((modm, xK_n ), windows W.focusUp )
164
165 -- Move focus to the master window
166 , ((modm, xK_m ), windows W.focusMaster )
167
168 -- Swap the focused window and the master window
169 , ((modm .|. shiftMask, xK_m ), windows W.swapMaster)
170
171 -- Swap the focused window with the next window
172 , ((modm .|. shiftMask, xK_t ), windows W.swapDown )
173
174 -- Swap the focused window with the previous window
175 , ((modm .|. shiftMask, xK_n ), windows W.swapUp )
176
177 -- Shrink the master area
178 , ((modm, xK_h ), sendMessage Shrink)
179
180 -- Expand the master area
181 , ((modm, xK_s ), sendMessage Expand)
182
183 -- Push window back into tiling
184 , ((modm .|. shiftMask, xK_space ), withFocused $ windows . W.sink)
185
186 -- Increment the number of windows in the master area
187 , ((modm , xK_comma ), sendMessage (IncMasterN 1))
188
189 -- Deincrement the number of windows in the master area
190 , ((modm , xK_period), sendMessage (IncMasterN (-1)))
191
192 , ((0, xF86XK_AudioRaiseVolume), safeSpawn "amixer" ["sset", "Master", "Playback", "5+"])
193 , ((0, xF86XK_AudioLowerVolume), safeSpawn "amixer" ["sset", "Master", "Playback", "5-"])
194
195 -- Toggle the status bar gap
196 -- Use this binding with avoidStruts from Hooks.ManageDocks.
197 -- See also the statusBar function from Hooks.DynamicLog.
198 --
199 , ((modm , xK_b ), sendMessage ToggleStruts)
200
201 -- Quit xmonad
202 , ((modm .|. shiftMask, xK_e ), io (exitWith ExitSuccess))
203
204 -- Restart xmonad
205 , ((modm .|. shiftMask, xK_r ), whenX (recompile False) $ safeSpawn "xmonad" ["--restart"])
206 , ((modm .|. shiftMask, xK_l ), safeSpawn "slock" [])
207 ]
208 ++
209 (join $ map spawnBindings [])
210 ++
211
212 --
213 -- mod-[1..9], Switch to workspace N
214 --
215 -- mod-[1..9], Switch to workspace N
216 -- mod-shift-[1..9], Move client to workspace N
217 --
218 [((m .|. modm, k), windows $ f i)
219 | (i, k) <- zip (XMonad.workspaces conf) $ numKeys
220 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
221 ]
222 ++
223 [((m .|. modm .|. controlMask, k), screenWorkspace i >>= (flip whenJust) (windows . f))
224 | (i, k) <- zip [0..] [xK_g, xK_c, xK_r, xK_l]
225 , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]
226 ]
227 where
228 modm = XMonad.modMask conf
229 spawnModifiers = [0, controlMask, shiftMask .|. controlMask]
230 spawnBindings (k, cmds) = zipWith (\m cmd -> ((modm .|. mod1Mask .|. m, k), spawn cmd)) spawnModifiers cmds
231
232