summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2015-07-03 22:49:07 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2015-07-03 22:49:07 +0200
commit920df251756c5de589f3a012778b714c32aac76b (patch)
tree77bfa0a72d8b637afeadba5218bb63b3aa6019d7
parent4f5b56901294354152d90b52721e8b165a40d307 (diff)
downloaddotfiles-920df251756c5de589f3a012778b714c32aac76b.tar
dotfiles-920df251756c5de589f3a012778b714c32aac76b.tar.gz
dotfiles-920df251756c5de589f3a012778b714c32aac76b.tar.bz2
dotfiles-920df251756c5de589f3a012778b714c32aac76b.tar.xz
dotfiles-920df251756c5de589f3a012778b714c32aac76b.zip
Additional xmonad libs
-rw-r--r--.xmonad/lib/XMonad/Prompt/MyShell.hs105
-rw-r--r--.xmonad/lib/XMonad/Prompt/MySsh.hs241
-rw-r--r--.xmonad/xmonad.hs24
3 files changed, 367 insertions, 3 deletions
diff --git a/.xmonad/lib/XMonad/Prompt/MyShell.hs b/.xmonad/lib/XMonad/Prompt/MyShell.hs
new file mode 100644
index 0000000..c268f87
--- /dev/null
+++ b/.xmonad/lib/XMonad/Prompt/MyShell.hs
@@ -0,0 +1,105 @@
1module XMonad.Prompt.MyShell
2 ( Shell (..)
3 , shellPrompt
4 , prompt
5 , safePrompt
6 , unsafePrompt
7 , getCommands
8 , getShellCompl
9 , split
10 ) where
11
12import Codec.Binary.UTF8.String (encodeString)
13import Control.Exception as E
14import Control.Monad (forM)
15import Data.List (isPrefixOf)
16import System.Directory (doesDirectoryExist, getDirectoryContents)
17import System.Environment (getEnv)
18import System.Posix.Files (getFileStatus, isDirectory)
19
20import XMonad hiding (config)
21import XMonad.Prompt
22import XMonad.Util.Run
23
24econst :: Monad m => a -> IOException -> m a
25econst = const . return
26
27data Shell = Shell String
28
29instance XPrompt Shell where
30 showXPrompt (Shell q) = q
31 completionToCommand _ = escape
32
33shellPrompt :: String -> XPConfig -> X ()
34shellPrompt q c = do
35 cmds <- io getCommands
36 mkXPrompt (Shell q) c (getShellCompl cmds) spawn
37
38{- $spawns
39 See safe and unsafeSpawn in "XMonad.Util.Run".
40 prompt is an alias for safePrompt;
41 safePrompt and unsafePrompt work on the same principles, but will use
42 XPrompt to interactively query the user for input; the appearance is
43 set by passing an XPConfig as the second argument. The first argument
44 is the program to be run with the interactive input.
45 You would use these like this:
46
47 > , ((modm, xK_b), safePrompt "firefox" greenXPConfig)
48 > , ((modm .|. shiftMask, xK_c), prompt ("xterm" ++ " -e") greenXPConfig)
49
50 Note that you want to use safePrompt for Firefox input, as Firefox
51 wants URLs, and unsafePrompt for the XTerm example because this allows
52 you to easily start a terminal executing an arbitrary command, like
53 'top'. -}
54
55prompt, unsafePrompt, safePrompt :: String -> FilePath -> XPConfig -> X ()
56prompt = unsafePrompt
57safePrompt q c config = mkXPrompt (Shell q) config (getShellCompl [c]) run
58 where run = safeSpawn c . return
59unsafePrompt q c config = mkXPrompt (Shell q) config (getShellCompl [c]) run
60 where run a = unsafeSpawn $ c ++ " " ++ a
61
62getShellCompl :: [String] -> String -> IO [String]
63getShellCompl cmds s | s == "" || last s == ' ' = return []
64 | otherwise = do
65 f <- fmap lines $ runProcessWithInput "bash" [] ("compgen -A file -- "
66 ++ s ++ "\n")
67 files <- case f of
68 [x] -> do fs <- getFileStatus (encodeString x)
69 if isDirectory fs then return [x ++ "/"]
70 else return [x]
71 _ -> return f
72 return . uniqSort $ files ++ commandCompletionFunction cmds s
73
74commandCompletionFunction :: [String] -> String -> [String]
75commandCompletionFunction cmds str | '/' `elem` str = []
76 | otherwise = filter (isPrefixOf str) cmds
77
78getCommands :: IO [String]
79getCommands = do
80 p <- getEnv "PATH" `E.catch` econst []
81 let ds = filter (/= "") $ split ':' p
82 es <- forM ds $ \d -> do
83 exists <- doesDirectoryExist d
84 if exists
85 then getDirectoryContents d
86 else return []
87 return . uniqSort . filter ((/= '.') . head) . concat $ es
88
89split :: Eq a => a -> [a] -> [[a]]
90split _ [] = []
91split e l =
92 f : split e (rest ls)
93 where
94 (f,ls) = span (/=e) l
95 rest s | s == [] = []
96 | otherwise = tail s
97
98escape :: String -> String
99escape [] = ""
100escape (x:xs)
101 | isSpecialChar x = '\\' : x : escape xs
102 | otherwise = x : escape xs
103
104isSpecialChar :: Char -> Bool
105isSpecialChar = flip elem " &\\@\"'#?$*()[]{};"
diff --git a/.xmonad/lib/XMonad/Prompt/MySsh.hs b/.xmonad/lib/XMonad/Prompt/MySsh.hs
new file mode 100644
index 0000000..e6ea042
--- /dev/null
+++ b/.xmonad/lib/XMonad/Prompt/MySsh.hs
@@ -0,0 +1,241 @@
1module XMonad.Prompt.MySsh
2 ( -- * Usage
3 -- $usage
4 sshPrompt,
5 Ssh,
6 Override (..),
7 mkOverride,
8 Conn (..),
9 moshCmd,
10 moshCmd',
11 sshCmd,
12 inTmux,
13 withEnv
14 ) where
15
16import XMonad
17import XMonad.Util.Run
18import XMonad.Prompt
19
20import System.Directory
21import System.Environment
22import qualified Control.Exception as E
23
24import Control.Monad
25import Data.Maybe
26
27import Text.Parsec.String
28import Text.Parsec
29import Data.Char (isSpace)
30
31econst :: Monad m => a -> E.IOException -> m a
32econst = const . return
33
34-- $usage
35-- 1. In your @~\/.xmonad\/xmonad.hs@:
36--
37-- > import XMonad.Prompt
38-- > import XMonad.Prompt.Ssh
39--
40-- 2. In your keybindings add something like:
41--
42-- > , ((modm .|. controlMask, xK_s), sshPrompt defaultXPConfig)
43--
44-- Keep in mind, that if you want to use the completion you have to
45-- disable the "HashKnownHosts" option in your ssh_config
46--
47-- For detailed instruction on editing the key binding see
48-- "XMonad.Doc.Extending#Editing_key_bindings".
49
50data Override = Override
51 { oUser :: Maybe String
52 , oHost :: String
53 , oPort :: Maybe Int
54 , oCommand :: Conn -> String
55 }
56
57mkOverride = Override { oUser = Nothing, oHost = "", oPort = Nothing, oCommand = sshCmd }
58sshCmd c = concat
59 [ "ssh -t "
60 , if isJust $ cUser c then (fromJust $ cUser c) ++ "@" else ""
61 , cHost c
62 , if isJust $ cPort c then " -p " ++ (show $ fromJust $ cPort c) else ""
63 , " -- "
64 , cCommand c
65 ]
66moshCmd c = concat
67 [ "mosh "
68 , if isJust $ cUser c then (fromJust $ cUser c) ++ "@" else ""
69 , cHost c
70 , if isJust $ cPort c then " --ssh=\"ssh -p " ++ (show $ fromJust $ cPort c) ++ "\"" else ""
71 , " -- "
72 , cCommand c
73 ]
74moshCmd' p c = concat
75 [ "mosh "
76 , "--server=" ++ p ++ " "
77 , if isJust $ cUser c then (fromJust $ cUser c) ++ "@" else ""
78 , cHost c
79 , if isJust $ cPort c then " --ssh=\"ssh -p " ++ (show $ fromJust $ cPort c) ++ "\"" else ""
80 , " -- "
81 , cCommand c
82 ]
83inTmux c = c { cCommand = "tmux new-session \"" ++ (cCommand c) ++ "\"" }
84withEnv :: [(String, String)] -> Conn -> Conn
85withEnv envs c = c { cCommand = "env" ++ (concat $ map (\(n, v) -> ' ' : (n ++ "=" ++ v)) envs) ++ " " ++ (cCommand c) }
86
87data Conn = Conn
88 { cUser :: Maybe String
89 , cHost :: String
90 , cPort :: Maybe Int
91 , cCommand :: String
92 } deriving (Eq, Show, Read)
93
94data Ssh = Ssh
95
96instance XPrompt Ssh where
97 showXPrompt Ssh = "SSH to: "
98 commandToComplete _ c = c
99 nextCompletion _ = getNextCompletion
100
101toConn :: String -> Maybe Conn
102toConn = toConn' . parse connParser "(unknown)"
103toConn' :: Either ParseError Conn -> Maybe Conn
104toConn' (Left _) = Nothing
105toConn' (Right a) = Just a
106
107connParser :: Parser Conn
108connParser = do
109 spaces
110 user' <- optionMaybe $ try $ do
111 str <- many1 $ satisfy (\c -> (not $ isSpace c) && (c /= '@'))
112 char '@'
113 return str
114 host' <- many1 $ satisfy (not . isSpace)
115 port' <- optionMaybe $ try $ do
116 space
117 string "-p"
118 spaces
119 int <- many1 digit
120 (space >> return ()) <|> eof
121 return $ (read int :: Int)
122 spaces
123 command' <- many anyChar
124 eof
125 return $ Conn
126 { cHost = host'
127 , cUser = user'
128 , cPort = port'
129 , cCommand = command'
130 }
131
132sshPrompt :: [Override] -> XPConfig -> X ()
133sshPrompt o c = do
134 sc <- io sshComplList
135 mkXPrompt Ssh c (mkComplFunFromList sc) $ ssh o
136
137ssh :: [Override] -> String -> X ()
138ssh overrides str = do
139 let cmd = applyOverrides overrides str
140 --liftIO $ putStr "SSH Command: "
141 --liftIO $ putStrLn cmd
142 runInTerm "" cmd
143
144applyOverrides :: [Override] -> String -> String
145applyOverrides [] str = "ssh " ++ str
146applyOverrides (o:os) str = case (applyOverride o str) of
147 Just str -> str
148 Nothing -> applyOverrides os str
149
150applyOverride :: Override -> String -> Maybe String
151applyOverride o str = let
152 conn = toConn str
153 in
154 if isNothing conn then Nothing else
155 case (fromJust conn) `matches` o of
156 True -> Just $ (oCommand o) (fromJust conn)
157 False -> Nothing
158
159matches :: Conn -> Override -> Bool
160a `matches` b = and
161 [ justBool (cUser a) (oUser b) (==)
162 , (cHost a) == (oHost b)
163 , justBool (cPort a) (oPort b) (==)
164 ]
165
166justBool :: Eq a => Maybe a -> Maybe a -> (a -> a -> Bool) -> Bool
167justBool Nothing _ _ = True
168justBool _ Nothing _ = True
169justBool (Just a) (Just b) match = a `match` b
170
171sshComplList :: IO [String]
172sshComplList = uniqSort `fmap` liftM2 (++) sshComplListLocal sshComplListGlobal
173
174sshComplListLocal :: IO [String]
175sshComplListLocal = do
176 h <- getEnv "HOME"
177 s1 <- sshComplListFile $ h ++ "/.ssh/known_hosts"
178 s2 <- sshComplListConf $ h ++ "/.ssh/config"
179 return $ s1 ++ s2
180
181sshComplListGlobal :: IO [String]
182sshComplListGlobal = do
183 env <- getEnv "SSH_KNOWN_HOSTS" `E.catch` econst "/nonexistent"
184 fs <- mapM fileExists [ env
185 , "/usr/local/etc/ssh/ssh_known_hosts"
186 , "/usr/local/etc/ssh_known_hosts"
187 , "/etc/ssh/ssh_known_hosts"
188 , "/etc/ssh_known_hosts"
189 ]
190 case catMaybes fs of
191 [] -> return []
192 (f:_) -> sshComplListFile' f
193
194sshComplListFile :: String -> IO [String]
195sshComplListFile kh = do
196 f <- doesFileExist kh
197 if f then sshComplListFile' kh
198 else return []
199
200sshComplListFile' :: String -> IO [String]
201sshComplListFile' kh = do
202 l <- readFile kh
203 return $ map (getWithPort . takeWhile (/= ',') . concat . take 1 . words)
204 $ filter nonComment
205 $ lines l
206
207sshComplListConf :: String -> IO [String]
208sshComplListConf kh = do
209 f <- doesFileExist kh
210 if f then sshComplListConf' kh
211 else return []
212
213sshComplListConf' :: String -> IO [String]
214sshComplListConf' kh = do
215 l <- readFile kh
216 return $ map (!!1)
217 $ filter isHost
218 $ map words
219 $ lines l
220 where
221 isHost ws = take 1 ws == ["Host"] && length ws > 1
222
223fileExists :: String -> IO (Maybe String)
224fileExists kh = do
225 f <- doesFileExist kh
226 if f then return $ Just kh
227 else return Nothing
228
229nonComment :: String -> Bool
230nonComment [] = False
231nonComment ('#':_) = False
232nonComment ('|':_) = False -- hashed, undecodeable
233nonComment _ = True
234
235getWithPort :: String -> String
236getWithPort ('[':str) = host ++ " -p " ++ port
237 where (host,p) = break (==']') str
238 port = case p of
239 ']':':':x -> x
240 _ -> "22"
241getWithPort str = str
diff --git a/.xmonad/xmonad.hs b/.xmonad/xmonad.hs
index cca4df1..f0e443f 100644
--- a/.xmonad/xmonad.hs
+++ b/.xmonad/xmonad.hs
@@ -40,7 +40,8 @@ import XMonad.Actions.Warp
40 40
41import XMonad.Layout.IM 41import XMonad.Layout.IM
42 42
43import XMonad.Prompt.Shell 43import XMonad.Prompt.MyShell
44import XMonad.Prompt.MySsh
44 45
45wsp :: Int -> WorkspaceId 46wsp :: Int -> WorkspaceId
46wsp i = case Map.lookup i workspaceNames of 47wsp i = case Map.lookup i workspaceNames of
@@ -135,6 +136,22 @@ xPConfig = defaultXPConfig { bgColor = "black"
135 , borderColor = "white" 136 , borderColor = "white"
136 } 137 }
137 138
139sshOverrides = map (\h -> mkOverride { oHost = h, oCommand = moshCmd . inTmux } )
140 [
141 "odin", "odin.asgard.yggdrasil"
142 , "surtr", "yggdrasil.li", "surtr.yggdrasil.li", "praseodym.org", "surtr.praseodym.org", "surtr.141.li", "141.li"
143 , "vindler", "vindler.alfheim.yggdrasil"
144 , "ullr"
145 ]
146 ++
147 map (\h -> mkOverride { oHost = h, oCommand = moshCmd' "/run/current-system/sw/bin/mosh-server" . withEnv [("TERM", "xterm")] . inTmux} )
148 [ "bragi", "bragi.asgard.yggdrasil"
149 ]
150 ++
151 map (\h -> mkOverride { oHost = h, oCommand = sshCmd . withEnv [("TERM", "xterm")] . inTmux } )
152 [ "galois", "galois.praseodym.org"
153 ]
154
138myKeys' conf = Map.fromList $ 155myKeys' conf = Map.fromList $
139 -- launch a terminal 156 -- launch a terminal
140 [ ((modm, xK_Return), spawn $ (XMonad.terminal conf) ++ " -e tmux") 157 [ ((modm, xK_Return), spawn $ (XMonad.terminal conf) ++ " -e tmux")
@@ -142,8 +159,9 @@ myKeys' conf = Map.fromList $
142 159
143 -- launch dmenu 160 -- launch dmenu
144 --, ((modm, xK_d ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") 161 --, ((modm, xK_d ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
145 , ((modm, xK_d ), shellPrompt xPConfig) 162 , ((modm, xK_d ), shellPrompt "Run: " xPConfig)
146 , ((modm .|. shiftMask, xK_d ), prompt ("urxvtc" ++ " -e") xPConfig) 163 , ((modm .|. shiftMask, xK_d ), prompt "Run in Terminal: " ("urxvtc" ++ " -e") xPConfig)
164 , ((modm, xK_at ), sshPrompt sshOverrides xPConfig)
147 165
148 -- close focused window 166 -- close focused window
149 , ((modm .|. shiftMask, xK_q ), kill) 167 , ((modm .|. shiftMask, xK_q ), kill)