summaryrefslogtreecommitdiff
path: root/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt
diff options
context:
space:
mode:
Diffstat (limited to 'accounts/gkleen@sif/xmonad/lib/XMonad/Prompt')
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs94
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyShell.hs105
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs246
3 files changed, 445 insertions, 0 deletions
diff --git a/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs
new file mode 100644
index 00000000..1caefae5
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs
@@ -0,0 +1,94 @@
1module XMonad.Prompt.MyPass
2 (
3 -- * Usages
4 -- $usages
5 mkPassPrompt
6 ) where
7
8import Control.Monad (liftM)
9import XMonad.Core
10import XMonad.Prompt ( XPrompt
11 , showXPrompt
12 , commandToComplete
13 , nextCompletion
14 , getNextCompletion
15 , XPConfig
16 , mkXPrompt
17 , searchPredicate)
18import System.Directory (getHomeDirectory)
19import System.FilePath (takeExtension, dropExtension, combine)
20import System.Posix.Env (getEnv)
21import XMonad.Util.Run (runProcessWithInput)
22
23-- $usages
24-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
25--
26-- > import XMonad.Prompt.Pass
27--
28-- Then add a keybinding for 'passPrompt', 'passGeneratePrompt' or 'passRemovePrompt':
29--
30-- > , ((modMask x , xK_p) , passPrompt xpconfig)
31-- > , ((modMask x .|. controlMask, xK_p) , passGeneratePrompt xpconfig)
32-- > , ((modMask x .|. controlMask .|. shiftMask, xK_p), passRemovePrompt xpconfig)
33--
34-- For detailed instructions on:
35--
36-- - editing your key bindings, see "XMonad.Doc.Extending#Editing_key_bindings".
37--
38-- - how to setup the password storage, see <http://git.zx2c4.com/password-store/about/>
39--
40
41type Predicate = String -> String -> Bool
42
43getPassCompl :: [String] -> Predicate -> String -> IO [String]
44getPassCompl compls p s
45 | length s <= minL
46 , all ((> minL) . length) compls = return []
47 | otherwise = do return $ filter (p s) compls
48 where
49 minL = 3
50
51type PromptLabel = String
52
53data Pass = Pass PromptLabel
54
55instance XPrompt Pass where
56 showXPrompt (Pass prompt) = prompt ++ ": "
57 commandToComplete _ c = c
58 nextCompletion _ = getNextCompletion
59
60-- | Default password store folder in $HOME/.password-store
61--
62passwordStoreFolderDefault :: String -> String
63passwordStoreFolderDefault home = combine home ".password-store"
64
65-- | Compute the password store's location.
66-- Use the PASSWORD_STORE_DIR environment variable to set the password store.
67-- If empty, return the password store located in user's home.
68--
69passwordStoreFolder :: IO String
70passwordStoreFolder =
71 getEnv "PASSWORD_STORE_DIR" >>= computePasswordStoreDir
72 where computePasswordStoreDir Nothing = liftM passwordStoreFolderDefault getHomeDirectory
73 computePasswordStoreDir (Just storeDir) = return storeDir
74
75-- | A pass prompt factory
76--
77mkPassPrompt :: PromptLabel -> (String -> X ()) -> XPConfig -> X ()
78mkPassPrompt promptLabel passwordFunction xpconfig = do
79 passwords <- io (passwordStoreFolder >>= getPasswords)
80 mkXPrompt (Pass promptLabel) xpconfig (getPassCompl passwords $ searchPredicate xpconfig) passwordFunction
81
82-- | Retrieve the list of passwords from the password storage 'passwordStoreDir
83getPasswords :: FilePath -> IO [String]
84getPasswords passwordStoreDir = do
85 files <- runProcessWithInput "find" [
86 passwordStoreDir,
87 "-type", "f",
88 "-name", "*.gpg",
89 "-printf", "%P\n"] []
90 return $ map removeGpgExtension $ lines files
91
92removeGpgExtension :: String -> String
93removeGpgExtension file | takeExtension file == ".gpg" = dropExtension file
94 | otherwise = file
diff --git a/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyShell.hs b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyShell.hs
new file mode 100644
index 00000000..c268f87d
--- /dev/null
+++ b/accounts/gkleen@sif/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/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..729941aa
--- /dev/null
+++ b/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MySsh.hs
@@ -0,0 +1,246 @@
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 Nothing c
84 | null $ cCommand c = c { cCommand = "tmux new-session" }
85 | otherwise = c { cCommand = "tmux new-session \"" ++ (cCommand c) ++ "\"" }
86inTmux (Just h) c
87 | null $ cCommand c = c { cCommand = "tmux new-session -As " <> h }
88 | otherwise = c { cCommand = "tmux new-session \"" ++ (cCommand c) ++ "\"" }
89withEnv :: [(String, String)] -> Conn -> Conn
90withEnv envs c = c { cCommand = "env" ++ (concat $ map (\(n, v) -> ' ' : (n ++ "=" ++ v)) envs) ++ " " ++ (cCommand c) }
91
92data Conn = Conn
93 { cUser :: Maybe String
94 , cHost :: String
95 , cPort :: Maybe Int
96 , cCommand :: String
97 } deriving (Eq, Show, Read)
98
99data Ssh = Ssh
100
101instance XPrompt Ssh where
102 showXPrompt Ssh = "SSH to: "
103 commandToComplete _ c = c
104 nextCompletion _ = getNextCompletion
105
106toConn :: String -> Maybe Conn
107toConn = toConn' . parse connParser "(unknown)"
108toConn' :: Either ParseError Conn -> Maybe Conn
109toConn' (Left _) = Nothing
110toConn' (Right a) = Just a
111
112connParser :: Parser Conn
113connParser = do
114 spaces
115 user' <- optionMaybe $ try $ do
116 str <- many1 $ satisfy (\c -> (not $ isSpace c) && (c /= '@'))
117 char '@'
118 return str
119 host' <- many1 $ satisfy (not . isSpace)
120 port' <- optionMaybe $ try $ do
121 space
122 string "-p"
123 spaces
124 int <- many1 digit
125 (space >> return ()) <|> eof
126 return $ (read int :: Int)
127 spaces
128 command' <- many anyChar
129 eof
130 return $ Conn
131 { cHost = host'
132 , cUser = user'
133 , cPort = port'
134 , cCommand = command'
135 }
136
137sshPrompt :: [Override] -> XPConfig -> X ()
138sshPrompt o c = do
139 sc <- io sshComplList
140 mkXPrompt Ssh c (mkComplFunFromList sc) $ ssh o
141
142ssh :: [Override] -> String -> X ()
143ssh overrides str = do
144 let cmd = applyOverrides overrides str
145 liftIO $ putStr "SSH Command: "
146 liftIO $ putStrLn cmd
147 runInTerm "" cmd
148
149applyOverrides :: [Override] -> String -> String
150applyOverrides [] str = "ssh " ++ str
151applyOverrides (o:os) str = case (applyOverride o str) of
152 Just str -> str
153 Nothing -> applyOverrides os str
154
155applyOverride :: Override -> String -> Maybe String
156applyOverride o str = let
157 conn = toConn str
158 in
159 if isNothing conn then Nothing else
160 case (fromJust conn) `matches` o of
161 True -> Just $ (oCommand o) (fromJust conn)
162 False -> Nothing
163
164matches :: Conn -> Override -> Bool
165a `matches` b = and
166 [ justBool (cUser a) (oUser b) (==)
167 , (cHost a) == (oHost b)
168 , justBool (cPort a) (oPort b) (==)
169 ]
170
171justBool :: Eq a => Maybe a -> Maybe a -> (a -> a -> Bool) -> Bool
172justBool Nothing _ _ = True
173justBool _ Nothing _ = True
174justBool (Just a) (Just b) match = a `match` b
175
176sshComplList :: IO [String]
177sshComplList = uniqSort `fmap` liftM2 (++) sshComplListLocal sshComplListGlobal
178
179sshComplListLocal :: IO [String]
180sshComplListLocal = do
181 h <- getEnv "HOME"
182 s1 <- sshComplListFile $ h ++ "/.ssh/known_hosts"
183 s2 <- sshComplListConf $ h ++ "/.ssh/config"
184 return $ s1 ++ s2
185
186sshComplListGlobal :: IO [String]
187sshComplListGlobal = do
188 env <- getEnv "SSH_KNOWN_HOSTS" `E.catch` econst "/nonexistent"
189 fs <- mapM fileExists [ env
190 , "/usr/local/etc/ssh/ssh_known_hosts"
191 , "/usr/local/etc/ssh_known_hosts"
192 , "/etc/ssh/ssh_known_hosts"
193 , "/etc/ssh_known_hosts"
194 ]
195 case catMaybes fs of
196 [] -> return []
197 (f:_) -> sshComplListFile' f
198
199sshComplListFile :: String -> IO [String]
200sshComplListFile kh = do
201 f <- doesFileExist kh
202 if f then sshComplListFile' kh
203 else return []
204
205sshComplListFile' :: String -> IO [String]
206sshComplListFile' kh = do
207 l <- readFile kh
208 return $ map (getWithPort . takeWhile (/= ',') . concat . take 1 . words)
209 $ filter nonComment
210 $ lines l
211
212sshComplListConf :: String -> IO [String]
213sshComplListConf kh = do
214 f <- doesFileExist kh
215 if f then sshComplListConf' kh
216 else return []
217
218sshComplListConf' :: String -> IO [String]
219sshComplListConf' kh = do
220 l <- readFile kh
221 return $ map (!!1)
222 $ filter isHost
223 $ map words
224 $ lines l
225 where
226 isHost ws = take 1 ws == ["Host"] && length ws > 1
227
228fileExists :: String -> IO (Maybe String)
229fileExists kh = do
230 f <- doesFileExist kh
231 if f then return $ Just kh
232 else return Nothing
233
234nonComment :: String -> Bool
235nonComment [] = False
236nonComment ('#':_) = False
237nonComment ('|':_) = False -- hashed, undecodeable
238nonComment _ = True
239
240getWithPort :: String -> String
241getWithPort ('[':str) = host ++ " -p " ++ port
242 where (host,p) = break (==']') str
243 port = case p of
244 ']':':':x -> x
245 _ -> "22"
246getWithPort str = str