X.P.Pass: Clean up code

This commit is contained in:
Tony Zorman
2023-09-20 13:36:54 +02:00
parent a379850f50
commit 431ba22e3c

View File

@@ -1,3 +1,4 @@
{-# LANGUAGE LambdaCase #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Prompt.Pass
@@ -64,26 +65,29 @@ module XMonad.Prompt.Pass
, passGenerateAndCopyPrompt
, passGenerateAndCopyPrompt'
-- * Misc
-- * One-time-passwords
, passOTPPrompt
) where
import System.Directory (getHomeDirectory)
import System.FilePath (combine, dropExtension, takeExtension)
import System.FilePath (dropExtension, (</>))
import System.Posix.Env (getEnv)
import XMonad.Core
import XMonad.Prompt ( XPrompt
, showXPrompt
, commandToComplete
, nextCompletion
, getNextCompletion
, XPConfig
, mkXPrompt
, searchPredicate)
import XMonad
import XMonad.Prelude
import XMonad.Prompt
( XPConfig,
XPrompt,
commandToComplete,
getNextCompletion,
mkXPrompt,
nextCompletion,
searchPredicate,
showXPrompt,
)
import XMonad.Util.Run (runProcessWithInput)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Prompt.Pass
--
@@ -119,10 +123,8 @@ import XMonad.Util.Run (runProcessWithInput)
-- or @man 1 pass@.
--
type Predicate = String -> String -> Bool
getPassCompl :: [String] -> Predicate -> String -> IO [String]
getPassCompl compls p s = return $ filter (p s) compls
---------------------------------------------------------------------------------
-- Prompt
type PromptLabel = String
@@ -133,28 +135,6 @@ instance XPrompt Pass where
commandToComplete _ c = c
nextCompletion _ = getNextCompletion
-- | Default password store folder in @$HOME/.password-store@.
--
passwordStoreFolderDefault :: String -> String
passwordStoreFolderDefault home = combine home ".password-store"
-- | Compute the password store's location.
-- Use the @$PASSWORD_STORE_DIR@ environment variable to set the password store.
-- If empty, return the password store located in user's home.
--
passwordStoreFolder :: IO String
passwordStoreFolder =
getEnv "PASSWORD_STORE_DIR" >>= computePasswordStoreDir
where computePasswordStoreDir Nothing = fmap passwordStoreFolderDefault getHomeDirectory
computePasswordStoreDir (Just storeDir) = return storeDir
-- | A pass prompt factory.
--
mkPassPrompt :: PromptLabel -> (String -> X ()) -> XPConfig -> X ()
mkPassPrompt promptLabel passwordFunction xpconfig = do
passwords <- io (passwordStoreFolder >>= getPasswords)
mkXPrompt (Pass promptLabel) xpconfig (getPassCompl passwords $ searchPredicate xpconfig) passwordFunction
-- | A prompt to retrieve a password from a given entry.
--
passPrompt :: XPConfig -> X ()
@@ -219,63 +199,103 @@ passEditPrompt = passEditPrompt' "Edit password"
passEditPrompt' :: String -> XPConfig -> X ()
passEditPrompt' s = mkPassPrompt s editPassword
-- | A pass prompt factory.
--
mkPassPrompt :: PromptLabel -> (String -> X ()) -> XPConfig -> X ()
mkPassPrompt promptLabel passwordFunction xpconfig = do
passwords <- io (passwordStoreFolder >>= getPasswords)
mkXPrompt (Pass promptLabel)
xpconfig
(getPassCompl passwords $ searchPredicate xpconfig)
passwordFunction
where
getPassCompl :: [String] -> (String -> String -> Bool) -> String -> IO [String]
getPassCompl compls p s = return $ filter (p s) compls
-- Compute the password store's location. Use the @$PASSWORD_STORE_DIR@
-- environment variable to set the password store. If empty, return the
-- password store located in user's home.
passwordStoreFolder :: IO String
passwordStoreFolder =
getEnv "PASSWORD_STORE_DIR" >>= computePasswordStoreDir
where
-- Default password store folder in @$HOME/.password-store@.
computePasswordStoreDir :: Maybe String -> IO String
computePasswordStoreDir = \case
Nothing -> getHomeDirectory <&> (</> ".password-store")
Just storeDir -> return storeDir
-- Retrieve the list of passwords from the password store @passwordStoreDir@.
getPasswords :: FilePath -> IO [String]
getPasswords passwordStoreDir = do
files <- runProcessWithInput "find" [
"-L", -- Traverse symlinks
passwordStoreDir,
"-type", "f",
"-name", "*.gpg",
"-printf", "%P\n"] []
return . map dropExtension $ lines files
---------------------------------------------------------------------------------
-- Selecting a password
-- | Select a password.
--
selectPassword :: String -> X ()
selectPassword passLabel = spawn $ "pass --clip \"" ++ escapeQuote passLabel ++ "\""
selectPassword = spawn . pass "--clip"
-- | Select an OTP.
-- | Select a one-time-password and copy it to the clipboard.
--
selectOTP :: String -> X ()
selectOTP passLabel = spawn $ "pass otp --clip \"" ++ escapeQuote passLabel ++ "\""
selectOTP = spawn . pass "otp --clip"
-- | Select a one-time-password and type it out.
--
selectOTPType :: String -> X ()
selectOTPType = spawn . typeString . pass "otp"
-- | Generate a 30 characters password for a given entry.
-- If the entry already exists, it is updated with a new password.
--
generatePassword :: String -> X ()
generatePassword passLabel = spawn $ "pass generate --force \"" ++ escapeQuote passLabel ++ "\" 30"
generatePassword passLabel = spawn $ pass "generate --force" passLabel ++ " 30"
-- | Generate a 30 characters password for a given entry.
-- If the entry already exists, it is updated with a new password.
-- After generating the password, it is copied to the clipboard.
--
generateAndCopyPassword :: String -> X ()
generateAndCopyPassword passLabel = spawn $ "pass generate --force -c \"" ++ escapeQuote passLabel ++ "\" 30"
generateAndCopyPassword passLabel = spawn $ pass "generate --force -c" passLabel ++ " 30"
-- | Remove a password stored for a given entry.
--
removePassword :: String -> X ()
removePassword passLabel = spawn $ "pass rm --force \"" ++ escapeQuote passLabel ++ "\""
removePassword = spawn . pass "rm --force"
-- | Edit a password stored for a given entry.
--
editPassword :: String -> X ()
editPassword passLabel = spawn $ "pass edit \"" ++ escapeQuote passLabel ++ "\""
editPassword = spawn . pass "edit"
-- | Type a password stored for a given entry using xdotool.
--
typePassword :: String -> X ()
typePassword passLabel = spawn $ "pass \"" ++ escapeQuote passLabel
++ "\"|head -n1|tr -d '\n'|xdotool type --clearmodifiers --file -"
typePassword = spawn . typeString . pass ""
escapeQuote :: String -> String
escapeQuote = concatMap escape
where escape :: Char -> String
escape '"' = "\\\""
escape x = [x]
-- | Retrieve the list of passwords from the password store 'passwordStoreDir'
-- | Type the given string with @xdotool@.
--
getPasswords :: FilePath -> IO [String]
getPasswords passwordStoreDir = do
files <- runProcessWithInput "find" [
"-L", -- Traverse symlinks
passwordStoreDir,
"-type", "f",
"-name", "*.gpg",
"-printf", "%P\n"] []
return . map removeGpgExtension $ lines files
-- >>> typeString (pass "" "arXiv")
-- "pass \"arXiv\" | head -n1 | tr -d '\n' | xdotool type --clearmodifiers --file -"
typeString :: String -> String
typeString cmd = cmd ++ " | head -n1 | tr -d '\n' | xdotool type --clearmodifiers --file -"
removeGpgExtension :: String -> String
removeGpgExtension file | takeExtension file == ".gpg" = dropExtension file
| otherwise = file
-- | Generate a pass prompt.
--
-- >>> pass "otp" "git\"hub\""
-- "pass otp \"git\\\"hub\\\"\""
pass :: String -> String -> String
pass cmd label = concat ["pass ", cmd, " \"", concatMap escape label, "\""]
where
escape :: Char -> String
escape '"' = "\\\""
escape x = [x]