summaryrefslogtreecommitdiff
path: root/accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs
diff options
context:
space:
mode:
Diffstat (limited to 'accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs')
-rw-r--r--accounts/gkleen@sif/xmonad/lib/XMonad/Prompt/MyPass.hs94
1 files changed, 94 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