summaryrefslogtreecommitdiff
path: root/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2021-01-03 00:55:29 +0100
committerGregor Kleen <gkleen@yggdrasil.li>2021-01-03 16:21:34 +0100
commit4a3d2a8ddaf4e546df360656bc54b2947bdb890b (patch)
treef571511e0b74fbd7e78f7e10966a8d6d5d400241 /accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs
parent3b5ab82fa714a0d483a7b90d60f9f7c857646e33 (diff)
downloadnixos-4a3d2a8ddaf4e546df360656bc54b2947bdb890b.tar
nixos-4a3d2a8ddaf4e546df360656bc54b2947bdb890b.tar.gz
nixos-4a3d2a8ddaf4e546df360656bc54b2947bdb890b.tar.bz2
nixos-4a3d2a8ddaf4e546df360656bc54b2947bdb890b.tar.xz
nixos-4a3d2a8ddaf4e546df360656bc54b2947bdb890b.zip
gkleen@sif: import
Diffstat (limited to 'accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs')
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs243
1 files changed, 243 insertions, 0 deletions
diff --git a/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs
new file mode 100644
index 00000000..c85d0f92
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs
@@ -0,0 +1,243 @@
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
84 | null $ cCommand c = c { cCommand = "tmux new-session" }
85 | otherwise = c { cCommand = "tmux new-session \"" ++ (cCommand c) ++ "\"" }
86withEnv :: [(String, String)] -> Conn -> Conn
87withEnv envs c = c { cCommand = "env" ++ (concat $ map (\(n, v) -> ' ' : (n ++ "=" ++ v)) envs) ++ " " ++ (cCommand c) }
88
89data Conn = Conn
90 { cUser :: Maybe String
91 , cHost :: String
92 , cPort :: Maybe Int
93 , cCommand :: String
94 } deriving (Eq, Show, Read)
95
96data Ssh = Ssh
97
98instance XPrompt Ssh where
99 showXPrompt Ssh = "SSH to: "
100 commandToComplete _ c = c
101 nextCompletion _ = getNextCompletion
102
103toConn :: String -> Maybe Conn
104toConn = toConn' . parse connParser "(unknown)"
105toConn' :: Either ParseError Conn -> Maybe Conn
106toConn' (Left _) = Nothing
107toConn' (Right a) = Just a
108
109connParser :: Parser Conn
110connParser = do
111 spaces
112 user' <- optionMaybe $ try $ do
113 str <- many1 $ satisfy (\c -> (not $ isSpace c) && (c /= '@'))
114 char '@'
115 return str
116 host' <- many1 $ satisfy (not . isSpace)
117 port' <- optionMaybe $ try $ do
118 space
119 string "-p"
120 spaces
121 int <- many1 digit
122 (space >> return ()) <|> eof
123 return $ (read int :: Int)
124 spaces
125 command' <- many anyChar
126 eof
127 return $ Conn
128 { cHost = host'
129 , cUser = user'
130 , cPort = port'
131 , cCommand = command'
132 }
133
134sshPrompt :: [Override] -> XPConfig -> X ()
135sshPrompt o c = do
136 sc <- io sshComplList
137 mkXPrompt Ssh c (mkComplFunFromList sc) $ ssh o
138
139ssh :: [Override] -> String -> X ()
140ssh overrides str = do
141 let cmd = applyOverrides overrides str
142 liftIO $ putStr "SSH Command: "
143 liftIO $ putStrLn cmd
144 runInTerm "" cmd
145
146applyOverrides :: [Override] -> String -> String
147applyOverrides [] str = "ssh " ++ str
148applyOverrides (o:os) str = case (applyOverride o str) of
149 Just str -> str
150 Nothing -> applyOverrides os str
151
152applyOverride :: Override -> String -> Maybe String
153applyOverride o str = let
154 conn = toConn str
155 in
156 if isNothing conn then Nothing else
157 case (fromJust conn) `matches` o of
158 True -> Just $ (oCommand o) (fromJust conn)
159 False -> Nothing
160
161matches :: Conn -> Override -> Bool
162a `matches` b = and
163 [ justBool (cUser a) (oUser b) (==)
164 , (cHost a) == (oHost b)
165 , justBool (cPort a) (oPort b) (==)
166 ]
167
168justBool :: Eq a => Maybe a -> Maybe a -> (a -> a -> Bool) -> Bool
169justBool Nothing _ _ = True
170justBool _ Nothing _ = True
171justBool (Just a) (Just b) match = a `match` b
172
173sshComplList :: IO [String]
174sshComplList = uniqSort `fmap` liftM2 (++) sshComplListLocal sshComplListGlobal
175
176sshComplListLocal :: IO [String]
177sshComplListLocal = do
178 h <- getEnv "HOME"
179 s1 <- sshComplListFile $ h ++ "/.ssh/known_hosts"
180 s2 <- sshComplListConf $ h ++ "/.ssh/config"
181 return $ s1 ++ s2
182
183sshComplListGlobal :: IO [String]
184sshComplListGlobal = do
185 env <- getEnv "SSH_KNOWN_HOSTS" `E.catch` econst "/nonexistent"
186 fs <- mapM fileExists [ env
187 , "/usr/local/etc/ssh/ssh_known_hosts"
188 , "/usr/local/etc/ssh_known_hosts"
189 , "/etc/ssh/ssh_known_hosts"
190 , "/etc/ssh_known_hosts"
191 ]
192 case catMaybes fs of
193 [] -> return []
194 (f:_) -> sshComplListFile' f
195
196sshComplListFile :: String -> IO [String]
197sshComplListFile kh = do
198 f <- doesFileExist kh
199 if f then sshComplListFile' kh
200 else return []
201
202sshComplListFile' :: String -> IO [String]
203sshComplListFile' kh = do
204 l <- readFile kh
205 return $ map (getWithPort . takeWhile (/= ',') . concat . take 1 . words)
206 $ filter nonComment
207 $ lines l
208
209sshComplListConf :: String -> IO [String]
210sshComplListConf kh = do
211 f <- doesFileExist kh
212 if f then sshComplListConf' kh
213 else return []
214
215sshComplListConf' :: String -> IO [String]
216sshComplListConf' kh = do
217 l <- readFile kh
218 return $ map (!!1)
219 $ filter isHost
220 $ map words
221 $ lines l
222 where
223 isHost ws = take 1 ws == ["Host"] && length ws > 1
224
225fileExists :: String -> IO (Maybe String)
226fileExists kh = do
227 f <- doesFileExist kh
228 if f then return $ Just kh
229 else return Nothing
230
231nonComment :: String -> Bool
232nonComment [] = False
233nonComment ('#':_) = False
234nonComment ('|':_) = False -- hashed, undecodeable
235nonComment _ = True
236
237getWithPort :: String -> String
238getWithPort ('[':str) = host ++ " -p " ++ port
239 where (host,p) = break (==']') str
240 port = case p of
241 ']':':':x -> x
242 _ -> "22"
243getWithPort str = str