rofi-extras/app/rofi-bw.hs

315 lines
9.6 KiB
Haskell
Raw Normal View History

2020-04-23 23:32:29 -04:00
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
2020-05-01 23:44:36 -04:00
--------------------------------------------------------------------------------
-- | rofi-bw - a rofi prompt for a bitwarden vault
--
-- This is basically a wrapper around the 'bw' command, which is assumed to be
-- properly configured before running this command. This shows a system of
-- menus that allows easy lookup of data associated with a vault entry. For now
-- only lookups (no edits or creation) are supported, and only logins can be
-- searched. Any searched entry can be copied to the clipboard
--
-- In order to manage the session keys, this utility is split into a daemon and
-- client (the former holds the session keys between calls with the latter).
-- They communicate via dbus.
2020-04-23 23:32:29 -04:00
module Main (main) where
import Control.Concurrent
import Control.Monad
import Data.Aeson
import Data.Maybe
import Data.String
import Data.UnixTime
import DBus
import DBus.Client
import GHC.Generics
import Rofi.Command
import Text.Read
import System.Clipboard
import System.Directory
import System.Environment
import System.Exit
import System.Process
main :: IO ()
main = runChecks >> getArgs >>= parse
2020-05-02 00:13:45 -04:00
-- TODO check if daemon is running when running client
2020-04-23 23:32:29 -04:00
parse :: [String] -> IO ()
parse ["-d", t] = case readMaybe t of { Just t' -> runDaemon t'; _ -> usage }
parse ("-c":args) = runClient args
parse _ = usage
usage :: IO ()
usage = putStrLn $ joinNewline
[ "daemon mode: rofi-bw -d TIMEOUT"
, "client mode: rofi-bw -c [ROFI-ARGS]"
]
runChecks :: IO ()
runChecks = checkExe "bw" >> checkExe "rofi"
checkExe :: String -> IO ()
checkExe cmd = do
res <- findExecutable cmd
unless (isJust res) $ do
putStrLn $ "Could not find executable: " ++ cmd
exitWith $ ExitFailure 1
--------------------------------------------------------------------------------
-- | Daemon
--
-- Daemon will export an interface on DBus with two methods:
-- * get current session id - if no session is active, launch Rofi to prompt
-- for a password; return session id or null if password is invalid
-- * lock session - destroy the current session id if active
--
-- The session ID will be valid only as long as TIMEOUT
2020-05-01 21:29:54 -04:00
newtype BWServerConf = BWServerConf
2020-04-23 23:32:29 -04:00
{ timeout :: UnixDiffTime
}
2020-05-02 00:13:45 -04:00
-- TODO add a cache so the browse list will load faster
2020-04-23 23:32:29 -04:00
data CurrentSession = CurrentSession
{ timestamp :: UnixTime
, hash :: String
}
type Session = MVar (Maybe CurrentSession)
runDaemon :: Int -> IO ()
runDaemon t = do
ses <- newMVar Nothing
2020-05-01 21:29:54 -04:00
let c = BWServerConf { timeout = UnixDiffTime (fromIntegral t) 0 }
2020-04-23 23:32:29 -04:00
startService c ses
forever $ threadDelay 1000000
lockSession :: Session -> IO ()
lockSession ses = void $ swapMVar ses Nothing
2020-05-11 22:45:26 -04:00
syncSession :: BWServerConf -> Session -> IO ()
syncSession conf ses = notify =<< fmap join . mapM cmd =<< getSession' conf ses
where
cmd h = readCmdSuccess "bw" ["sync", "--session", h] ""
notify res = let j = isJust res
in notifyStatus j $ if j then "sync succeeded" else "sync failed"
getSession' :: BWServerConf -> Session -> IO (Maybe String)
getSession' BWServerConf { timeout = t } ses = do
2020-04-23 23:32:29 -04:00
ut <- getUnixTime
modifyMVar ses $ \s -> case s of
Just CurrentSession { timestamp = ts, hash = h } ->
2020-05-11 22:45:26 -04:00
if diffUnixTime ut ts > t then getNewSession else return (s, Just h)
2020-04-23 23:32:29 -04:00
Nothing -> getNewSession
where
getNewSession = do
pwd <- readPassword
newHash <- join <$> mapM readSession pwd
2020-05-11 22:45:26 -04:00
(, newHash) <$> mapM newSession newHash
2020-04-23 23:32:29 -04:00
newSession h = do
ut <- getUnixTime
return CurrentSession { timestamp = ut, hash = h }
2020-05-11 22:45:26 -04:00
getSession :: BWServerConf -> Session -> IO String
getSession conf ses = fromMaybe "" <$> getSession' conf ses
2020-04-23 23:32:29 -04:00
readSession :: String -> IO (Maybe String)
readSession pwd = readCmdSuccess "bw" ["unlock", pwd, "--raw"] ""
2020-05-11 22:45:26 -04:00
notifyStatus :: Bool -> String -> IO ()
notifyStatus succeeded msg =
void $ spawnProcess "notify-send" ["-i", i, msg]
where
i = if succeeded
then "dialog-information-symbolic"
else "dialog-error-symbolic"
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | Client
--
-- The client will get the current session from the daemon (if it can) and then
-- go through a decision-tree like selection process to retrieve information as
-- needed. This will be in the form of the following menus:
--
-- Main menus
-- - Lock Session -> lock the session
-- - Browse logins -> show new menu of all logins
-- - select an entry -> show new menu with entry contents
-- - All -> copy all to clipboard
-- - username (if applicable) -> copy to clipboard
-- - password (if applicable) -> copy to clipboard
-- - anything else (notes and such) -> copy to clipboard
2020-05-01 21:29:54 -04:00
newtype BWClientConf = BWClientConf [String]
instance RofiConf BWClientConf where
defArgs (BWClientConf a) = a
2020-04-23 23:32:29 -04:00
runClient :: [String] -> IO ()
runClient a = do
2020-05-01 21:29:54 -04:00
let c = BWClientConf a
runRofiIO c $ selectAction $ emptyMenu
2020-04-23 23:32:29 -04:00
{ groups = [untitledGroup $ toRofiActions ras]
, prompt = Just "Action"
}
where
ras = [ ("Browse Logins", browseLogins)
2020-05-11 22:45:26 -04:00
, ("Sync Session", io callSyncSession)
2020-04-23 23:32:29 -04:00
, ("Lock Session", io callLockSession)
]
2020-05-01 21:29:54 -04:00
browseLogins :: RofiConf c => RofiIO c ()
2020-04-23 23:32:29 -04:00
browseLogins = do
session <- io callGetSession
forM_ session $ (io . getItems) >=> selectItem
2020-04-23 23:32:29 -04:00
-- TODO use this in rofi-dev to mount thing using BW passwords
getItems :: String -> IO [Item]
2020-04-23 23:32:29 -04:00
getItems session = do
items <- io $ readProcess "bw" ["list", "items", "--session", session] ""
return $ filter notEmpty $ fromMaybe [] $ decode $ fromString items
where
notEmpty Item { login = Login { username = Nothing, password = Nothing } }
= False
notEmpty _ = True
data Item = Item
{ name :: String
, login :: Login
}
deriving (Show)
instance FromJSON Item where
parseJSON (Object o) = Item
<$> o .: "name"
<*> o .:? "login" .!= Login { username = Nothing, password = Nothing }
parseJSON _ = mzero
data Login = Login
{ username :: Maybe String
, password :: Maybe String
}
deriving (Show, Generic)
instance FromJSON Login
-- TODO make menu buttons here to go back and to copy without leaving
-- the current menu
2020-05-01 21:29:54 -04:00
selectItem :: RofiConf c => [Item] -> RofiIO c ()
2020-04-23 23:32:29 -04:00
selectItem items = selectAction $ emptyMenu
{ groups = [untitledGroup $ itemsToRofiActions items]
, prompt = Just "Login"
}
2020-05-01 21:29:54 -04:00
itemsToRofiActions :: RofiConf c => [Item] -> RofiActions c
2020-04-23 23:32:29 -04:00
itemsToRofiActions = toRofiActions . fmap (\i -> (name i, selectCopy $ login i))
2020-05-01 21:29:54 -04:00
selectCopy :: RofiConf c => Login -> RofiIO c ()
2020-04-23 23:32:29 -04:00
selectCopy l = selectAction $ emptyMenu
{ groups = [untitledGroup $ loginToRofiActions l copy]
, prompt = Just "Copy"
, hotkeys = [copyHotkey, backHotkey]
}
where
copy = io . setClipboardString
copyRepeat s = copy s >> selectCopy l
copyHotkey = Hotkey
{ keyCombo = "Alt+c"
, keyIndex = 1
, keyDescription = "Copy One"
, keyActions = loginToRofiActions l copyRepeat
}
backHotkey = Hotkey
{ keyCombo = "Alt+q"
, keyIndex = 2
, keyDescription = "Back"
-- TODO this is overly complicated, all entries do the same thing
-- TODO this is slow, we can cache the logins somehow...
, keyActions = loginToRofiActions l (const browseLogins)
}
2020-05-01 21:29:54 -04:00
loginToRofiActions :: RofiConf c => Login -> (String -> RofiIO c ()) -> RofiActions c
2020-04-23 23:32:29 -04:00
loginToRofiActions Login { username = u, password = p } a =
toRofiActions $ catMaybes [user, pwd]
where
copyIfJust f = fmap $ liftM2 (,) f a
fmtUsername s = "Username (" ++ s ++ ")"
fmtPassword s = "Password (" ++ take 32 (replicate (length s) '*') ++ ")"
user = copyIfJust fmtUsername u
pwd = copyIfJust fmtPassword p
--------------------------------------------------------------------------------
-- | DBus
busname :: BusName
busname = "org.rofi.bitwarden"
path :: ObjectPath
path = "/bitwarden"
interface :: InterfaceName
interface = "org.rofi.bitwarden.session"
memGetSession :: MemberName
memGetSession = "GetSession"
memLockSession :: MemberName
memLockSession = "LockSession"
2020-05-11 22:45:26 -04:00
memSyncSession :: MemberName
memSyncSession = "SyncSession"
2020-05-01 21:29:54 -04:00
startService :: BWServerConf -> Session -> IO ()
2020-04-23 23:32:29 -04:00
startService c ses = do
client <- connectSession
let flags = [nameAllowReplacement, nameReplaceExisting]
_ <- requestName client busname flags
putStrLn "Started rofi bitwarden dbus client"
export client path defaultInterface
{ interfaceName = interface
, interfaceMethods =
[ autoMethod memGetSession $ getSession c ses
, autoMethod memLockSession $ lockSession ses
2020-05-11 22:45:26 -04:00
, autoMethod memSyncSession $ syncSession c ses
2020-04-23 23:32:29 -04:00
]
}
2020-05-11 22:45:26 -04:00
callMember :: MemberName -> IO [Variant]
callMember m = do
reply <- callMethod $ methodCall path interface m
2020-04-23 23:32:29 -04:00
case reply of
2020-05-11 22:45:26 -04:00
Left err -> putStrLn (methodErrorMessage err) >> return []
Right body -> return body
callLockSession :: IO ()
callLockSession = void $ callMember memLockSession
callSyncSession :: IO ()
callSyncSession = void $ callMember memSyncSession
2020-04-23 23:32:29 -04:00
callGetSession :: IO (Maybe String)
2020-05-11 22:45:26 -04:00
callGetSession = getBodySession <$> callMember memGetSession
2020-04-23 23:32:29 -04:00
getBodySession :: [Variant] -> Maybe String
2020-05-11 22:45:26 -04:00
getBodySession [b] = case fromVariant b :: Maybe String of
Just "" -> Nothing
s -> s
2020-04-23 23:32:29 -04:00
getBodySession _ = Nothing
callMethod :: MethodCall -> IO (Either MethodError [Variant])
callMethod mc = do
client <- connectSession
reply <- call client mc { methodCallDestination = Just busname }
disconnect client
return $ methodReturnBody <$> reply