ADD systemd mount unit thing support

This commit is contained in:
Nathan Dwarshuis 2021-02-14 19:33:10 -05:00
parent 335c5b74c9
commit 7234cb3799
1 changed files with 70 additions and 5 deletions

View File

@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | rofi-dev - a rofi prompt for mountable devices -- | rofi-dev - a rofi prompt for mountable devices
@ -33,6 +34,7 @@ import Text.Wrap
import System.Console.GetOpt import System.Console.GetOpt
import System.Directory import System.Directory
import System.Environment import System.Environment
import System.Exit (ExitCode(..))
import System.FilePath.Posix import System.FilePath.Posix
import System.Posix.User (getEffectiveUserName) import System.Posix.User (getEffectiveUserName)
import System.Process import System.Process
@ -170,17 +172,29 @@ runPrompt gs = selectAction $ emptyMenu
getGroups :: RofiIO MountConf [RofiGroup MountConf] getGroups :: RofiIO MountConf [RofiGroup MountConf]
getGroups = do getGroups = do
fstab <- readFSTab fstab <- readFSTab
sysd <- io getSystemdDevices
sequence sequence
[ mkGroup "SSHFS Devices" $ sshfsDevices fstab [ mkGroup2 "SSHFS Devices" (filterSysd SystemdSSHFS sysd) $ sshfsDevices fstab
, mkGroup "CIFS Devices" $ cifsDevices fstab , mkGroup "CIFS Devices" $ cifsDevices fstab
, mkGroup "Veracrypt Devices" =<< getVeracryptDevices , mkGroup2 "Veracrypt Devices" (filterSysd SystemdVeracrypt sysd) =<< getVeracryptDevices
, mkGroup "Removable Devices" =<< getRemovableDevices , mkGroup "Removable Devices" =<< getRemovableDevices
, mkGroup "MTP Devices" =<< getMTPDevices , mkGroup "MTP Devices" =<< getMTPDevices
] ]
where
filterSysd t = filter (\s -> sysdType s == t)
mkGroup :: Mountable d => String -> [d] -> RofiIO MountConf (RofiGroup MountConf) mkGroup :: Mountable d => String -> [d] -> RofiIO MountConf (RofiGroup MountConf)
mkGroup header devs = titledGroup header . alignEntries . toRofiActions mkGroup header devs = sortGroup header <$> mapM mkAction devs
<$> mapM mkAction devs
mkGroup2 :: (Mountable d, Mountable e) => String
-> [d] -> [e] -> RofiIO MountConf (RofiGroup MountConf)
mkGroup2 header devs1 devs2 = do
r1 <- mapM mkAction devs1
r2 <- mapM mkAction devs2
return $ sortGroup header (r1 ++ r2)
sortGroup :: String -> [(String, RofiIO MountConf ())] -> RofiGroup MountConf
sortGroup header = titledGroup header . alignEntries . toRofiActions
alignSep :: String alignSep :: String
alignSep = " | " alignSep = " | "
@ -424,6 +438,57 @@ getMTPDevices = do
| c == ' ' = Just '-' | c == ' ' = Just '-'
| otherwise = Just c | otherwise = Just c
--------------------------------------------------------------------------------
-- | Systemd typeclass
data SystemdMountType = SystemdVeracrypt | SystemdSSHFS deriving (Eq, Show)
data Systemd = Systemd
{ sysdType :: SystemdMountType
, sysdInstance :: String
}
deriving (Eq, Show)
instance Mountable Systemd where
mount s@Systemd { sysdInstance = i } m = let
unit = fmtSysdInstanceName s
op = if m then "stop" else "start" in
io $ runMountNotify "systemctl" ["--user", op, unit] i m
allInstalled Systemd { sysdType = SystemdVeracrypt } =
io $ isJust <$> findExecutable "veracrypt"
allInstalled Systemd { sysdType = SystemdSSHFS } =
io $ isJust <$> findExecutable "sshfs"
isMounted s = let
unit = fmtSysdInstanceName s
args = ["--user", "is-active", "--quiet", unit] in
io $ (\(ec, _, _) -> ec == ExitSuccess)
<$> readProcessWithExitCode "systemctl" args ""
fmtEntry Systemd { sysdInstance = i } = i ++ alignSepPre ++ "Systemd"
fmtSysdInstanceName :: Systemd -> String
fmtSysdInstanceName Systemd { sysdType = SystemdVeracrypt, sysdInstance = i } =
"mount-veracrypt@" ++ i ++ ".service"
fmtSysdInstanceName Systemd { sysdType = SystemdSSHFS, sysdInstance = i } =
"mount-sshfs@" ++ i ++ ".service"
getSystemdDevices :: IO [Systemd]
getSystemdDevices = do
systemdHome <- io $ getXdgDirectory XdgConfig "systemd/user"
io $ mapMaybe toDev
<$> (filterM (doesDirectoryExist . (systemdHome </>))
=<< listDirectory systemdHome)
where
toDev (splitInstance "mount-veracrypt@" -> Just s) =
Just $ Systemd { sysdType = SystemdVeracrypt , sysdInstance = s }
toDev (splitInstance "mount-sshfs@" -> Just s) =
Just $ Systemd { sysdType = SystemdSSHFS , sysdInstance = s }
toDev _ = Nothing
splitInstance p = fmap (takeWhile (not . (==) '.')) . stripPrefix p
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- | Mountable typeclass -- | Mountable typeclass
-- --