rofi-extras/app/rofi-dev.hs

616 lines
22 KiB
Haskell
Raw Normal View History

2020-04-23 23:32:29 -04:00
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
--------------------------------------------------------------------------------
-- | rofi-dev - a rofi prompt for mountable devices
--
-- Like all "mount helpers" this is basically a wrapper for low-level utilities
-- the mount things from the command line. It also creates/destroys mountpoint
-- paths given a specific location for such mountpoints.
2020-04-23 23:32:29 -04:00
module Main (main) where
import Bitwarden.Internal
2020-04-23 23:32:29 -04:00
import Control.Monad
2020-05-01 21:29:54 -04:00
import Control.Monad.Reader
2020-04-23 23:32:29 -04:00
import Data.Either
import Data.List
2020-05-01 21:29:54 -04:00
import Data.List.Split (splitOn)
import qualified Data.Map as M
import qualified Data.Map.Ordered as O
2020-04-23 23:32:29 -04:00
import Data.Maybe
2020-05-01 22:22:28 -04:00
import Data.Text (unpack)
2020-04-23 23:32:29 -04:00
import Rofi.Command
import Text.Printf
import Text.Regex.TDFA
2020-05-01 22:22:28 -04:00
import Text.Wrap
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
import System.Console.GetOpt
2020-04-23 23:32:29 -04:00
import System.Directory
import System.Environment
2020-05-01 21:29:54 -04:00
import System.FilePath.Posix
import System.Posix.User (getEffectiveUserName)
2020-04-23 23:32:29 -04:00
import System.Process
2020-05-01 21:29:54 -04:00
import UnliftIO.Exception
2020-04-23 23:32:29 -04:00
main :: IO ()
main = getArgs >>= parse
2020-05-01 21:29:54 -04:00
parse :: [String] -> IO ()
parse args = case getOpt Permute options args of
(o, n, []) -> initMountConf n >>= \i -> runMounts $ foldl (flip id) i o
(_, _, errs) -> ioError $ userError $ concat errs ++ usageInfo h options
2020-05-01 21:29:54 -04:00
where
h = "Usage: rofi-dev [OPTIONS] [-- ROFI-OPTIONS]"
2020-05-01 21:29:54 -04:00
options :: [OptDescr (MountConf -> MountConf)]
options =
[ Option ['s'] ["secret"]
(ReqArg (\s m -> m { passwords = addSecret (passwords m) s } ) "SECRET")
2020-05-01 22:22:28 -04:00
$ wrap "Use libsecret to retrieve password for DIR using ATTR/VAL pairs. \
\The pairs will be supplied to a 'secret-tool lookup' call. \
\ Argument is formatted like 'DIR:ATTR1=VAL1,ATTR2=VAL2...'"
, Option ['b'] ["bitwarden"]
(ReqArg (\s m -> m { passwords = addBitwarden (passwords m) s } ) "BW")
$ wrap "Use the Bitwarden CLI to retrieve a password for DIR. \
\The argument is formatted like 'DIR:NAME' where NAME is the \
\name of the Bitwarden entry to find."
2020-12-12 00:11:00 -05:00
, Option ['p'] ["password"]
(ReqArg (\s m -> m { passwords = addPwdPrompt (passwords m) s } ) "DIR")
"Prompt for password when mounting DIR."
2020-05-01 21:29:54 -04:00
, Option ['d'] ["directory"]
(ReqArg (\s m -> m { mountDir = s } ) "DIR")
2020-05-01 22:22:28 -04:00
$ wrap "The DIR in which new mountpoints will be created. This is assumed \
\to be writable to the current user, and will be used for fuse \
\entries as well as user mounts in fstab. For the latter, it is \
\assumed that all user mounts contain this directory if a \
\mountpoint does not already exist for them. If not given this will \
\default to '/tmp/media/USER'."
2020-12-12 00:11:00 -05:00
, Option ['v'] ["veracrypt"]
(ReqArg (\s m -> m { vcMounts = addVeracryptMount (vcMounts m) s } ) "VC")
$ wrap "A veracrypt mount specification formatted like DIR:VOL where \
\DIR is the mountpoint and VOL is the path to the encrypted \
\volume. To specify a password, use the -p, -b- or -s options."
2020-05-01 21:29:54 -04:00
]
2020-05-01 22:22:28 -04:00
where
wrap = unpack . wrapText defaultWrapSettings 40
2020-05-01 21:29:54 -04:00
--------------------------------------------------------------------------------
-- | Static configuration
--
-- This is defined by the mount options on the command line, and holds:
-- - a map between mountpoints and a means to get passwords when mounting those
-- mountpoints
-- - a mount directory where mountpoints will be created if needed (defaults
-- to '/tmp/media/USER'
-- - any arguments to be passed to the rofi command
type Password = IO (Maybe String)
type MountpointPasswords = M.Map String Password
2020-12-12 00:11:00 -05:00
type VeracryptMount = (FilePath, FilePath)
addVeracryptMount :: [VeracryptMount] -> String -> [VeracryptMount]
addVeracryptMount l s = case splitPrefix s of
(dir, ":", vol) -> (dir, vol):l
_ -> l
2020-05-02 00:13:45 -04:00
-- TODO check if mountdir exists or puke
data MountConf = MountConf
{ passwords :: MountpointPasswords
, mountDir :: FilePath
, rofiArgs :: [String]
2020-12-12 00:11:00 -05:00
, vcMounts :: [VeracryptMount]
}
instance RofiConf MountConf where
defArgs MountConf { rofiArgs = a } = a
initMountConf :: [String] -> IO MountConf
initMountConf a = conf <$> getEffectiveUserName
2020-05-01 22:22:28 -04:00
where
conf u = MountConf
{ passwords = M.empty
, mountDir = "/tmp/media" </> u
, rofiArgs = a
2020-12-12 00:11:00 -05:00
, vcMounts = []
}
2020-05-01 21:29:54 -04:00
--------------------------------------------------------------------------------
-- | Password-getting functions
addSecret :: MountpointPasswords -> String -> MountpointPasswords
addSecret pwds c = case splitPrefix c of
(dir, ":", r) -> M.insert dir (runSecret $ fromCommaSepString' r) pwds
2020-05-01 21:29:54 -04:00
_ -> pwds
runSecret :: [(String, String)] -> Password
runSecret kvs = readCmdSuccess "secret-tool" ("lookup":kvs') ""
2020-05-01 21:29:54 -04:00
where
kvs' = concatMap (\(k, v) -> [k, v]) kvs
addBitwarden :: MountpointPasswords -> String -> MountpointPasswords
addBitwarden pwds c = case splitPrefix c of
(dir, ":", name) -> M.insert dir (runBitwarden name) pwds
_ -> pwds
runBitwarden :: String -> Password
runBitwarden pname = ((password . login) <=< find (\i -> name i == pname))
<$> getItems
addPwdPrompt :: MountpointPasswords -> String -> MountpointPasswords
addPwdPrompt pwds dir = M.insert dir readPassword pwds
2020-05-01 21:29:54 -04:00
splitPrefix :: String -> (String, String, String)
splitPrefix s = s =~ (":" :: String)
--------------------------------------------------------------------------------
-- | Main prompt
--
-- This command will have one Rofi prompt and will display all available
-- mounts grouped by device type (eg removable, sshfs, cifs, etc). I like
-- pretty things, so ensure the entries are aligned properly as well
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
runMounts :: MountConf -> IO ()
runMounts c = runRofiIO c $ runPrompt =<< getGroups
runPrompt :: RofiConf c => [RofiGroup c] -> RofiIO c ()
runPrompt gs = selectAction $ emptyMenu
{ groups = gs
, prompt = Just "Select Device"
}
getGroups :: RofiIO MountConf [RofiGroup MountConf]
getGroups = do
fstab <- readFSTab
sequence
[ mkGroup "SSHFS Devices" $ sshfsDevices fstab
, mkGroup "CIFS Devices" $ cifsDevices fstab
2020-12-12 00:11:00 -05:00
, mkGroup "Veracrypt Devices" =<< getVeracryptDevices
2020-05-01 21:29:54 -04:00
, mkGroup "Removable Devices" =<< getRemovableDevices
, mkGroup "MTP Devices" =<< getMTPDevices
]
mkGroup :: Mountable d => String -> [d] -> RofiIO MountConf (RofiGroup MountConf)
mkGroup header devs = titledGroup header . alignEntries . toRofiActions
<$> mapM mkAction devs
2020-04-23 23:32:29 -04:00
alignSep :: String
alignSep = " | "
alignSepPre :: String
alignSepPre = "@@@"
2020-05-01 21:29:54 -04:00
alignEntries :: RofiActions c -> RofiActions c
2020-04-23 23:32:29 -04:00
alignEntries = O.fromList . withKeys . O.assocs
where
withKeys as = let (ks, vs) = unzip as in zip (align ks) vs
align = fmap (intercalate alignSep)
. transpose
. mapToLast pad
. transpose
. fmap (splitOn alignSepPre)
2020-04-23 23:32:29 -04:00
pad xs = let m = getMax xs in fmap (\x -> take m (x ++ repeat ' ')) xs
getMax = maximum . fmap length
mapToLast _ [] = []
mapToLast _ [x] = [x]
mapToLast f (x:xs) = f x : mapToLast f xs
--------------------------------------------------------------------------------
-- | Removable devices
--
-- A device which can be removed (which is all the devices we care about)
2020-05-01 21:29:54 -04:00
-- This can be minimally described by a device DEVICESPEC and LABEL.
2020-04-23 23:32:29 -04:00
data Removable = Removable
2020-05-01 21:29:54 -04:00
{ deviceSpec :: String
2020-04-23 23:32:29 -04:00
, label :: String
}
deriving (Eq, Show)
instance Mountable Removable where
mount Removable { deviceSpec = d, label = l } m =
2020-05-02 00:13:33 -04:00
io $ runMountNotify "udisksctl" [c, "-b", d] l m
where
c = if m then "unmount" else "mount"
2020-05-01 21:29:54 -04:00
allInstalled _ = fmap isJust $ io $ findExecutable "udisksctl"
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
isMounted Removable { deviceSpec = d } = elem d <$> io curDeviceSpecs
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
fmtEntry Removable { deviceSpec = d, label = l } = l ++ alignSepPre ++ d
2020-04-23 23:32:29 -04:00
-- | Return list of possible rofi actions for removable devices
-- A 'removable device' is defined as a hotplugged device with a filesystem as
-- reported by 'lsblk'. If the LABEL does not exist on the filesystem, the
-- label shown on the prompt will be 'SIZE Volume' where size is the size of
-- the device
2020-05-01 21:29:54 -04:00
getRemovableDevices :: RofiConf c => RofiIO c [Removable]
getRemovableDevices = fromLines toDev . lines
2020-05-01 21:29:54 -04:00
<$> io (readProcess "lsblk" ["-n", "-r", "-o", columns] "")
2020-04-23 23:32:29 -04:00
where
columns = "FSTYPE,HOTPLUG,PATH,LABEL,SIZE"
-- can't use 'words' here since it will drop spaces in the front
toDev line = case splitBy ' ' line of
("":_) -> Nothing
2020-05-01 21:29:54 -04:00
[_, "1", d, "", s] -> mk d $ s ++ " Volume"
[_, "1", d, l, _] -> mk d l
2020-04-23 23:32:29 -04:00
_ -> Nothing
2020-05-01 21:29:54 -04:00
mk d l = Just $ Removable { deviceSpec = d, label = l }
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | CIFS Devices
--
-- This wraps the Removable device (since it is removable) and also adds its
-- own mount options and passwords for authentication.
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
data CIFS = CIFS Removable FilePath (Maybe Password)
2020-04-23 23:32:29 -04:00
instance Mountable CIFS where
2020-05-01 21:29:54 -04:00
mount (CIFS Removable{ label = l } m getPwd) False =
bracketOnError_
(mkDirMaybe m)
(rmDirMaybe m)
$ io $ do
res <- case getPwd of
Just pwd -> do
p <- maybe [] (\p -> [("PASSWD", p)]) <$> pwd
readCmdEither' "mount" [m] "" p
Nothing -> readCmdEither "mount" [m] ""
notifyMounted (isRight res) False l
mount (CIFS Removable{ label = l } m _) True = umountNotify l m
allInstalled _ = io $ isJust <$> findExecutable "mount.cifs"
isMounted (CIFS _ dir _) = io $ isDirMounted dir
fmtEntry (CIFS r _ _) = fmtEntry r
-- TODO this smells like something that should be in a typeclass
fstabToCIFS :: FSTabEntry -> RofiIO MountConf CIFS
fstabToCIFS FSTabEntry{ fstabSpec = s, fstabDir = d, fstabOptions = o } = do
2020-05-01 22:22:28 -04:00
-- If the options specify "guest" don't require a password. Else try to find a
-- means to get the password from the command line options provided for the
-- this mountpoint. If nothing is found, prompt for a password. In any case,
-- the output will be passed to env variable PASSWD when mounting this cifs
-- directory and cause it to fail. Setting the env variable is necessary as
2020-05-01 21:29:54 -04:00
-- the cifs mount call will prompt for a password and hang otherwise.
pwd <- if M.member "guest" o
then return Nothing
else Just . M.findWithDefault readPassword d <$> asks passwords
2020-05-01 21:29:54 -04:00
let r = Removable { deviceSpec = smartSlashPrefix s, label = takeFileName d }
return $ CIFS r d pwd
where
smartSlashPrefix a = if "//" `isPrefixOf` a then a else "//" ++ a
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | SSHFS Devices
--
-- This wraps the Removable device (since it is removable) and also adds its
-- own mount options. If the path does not point to an aliased entry in the ssh
-- config that specifies the port, hostname, user, and identity file, these
-- need to be passed as mount options.
2020-05-01 21:29:54 -04:00
data SSHFS = SSHFS Removable FilePath
2020-04-23 23:32:29 -04:00
instance Mountable SSHFS where
2020-05-01 21:29:54 -04:00
mount (SSHFS Removable{ label = l } m) False =
bracketOnError_
(mkDirMaybe m)
(rmDirMaybe m)
(io $ runMountNotify "mount" [m] l False)
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
mount (SSHFS Removable{ label = l } m) True = umountNotify l m
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
allInstalled _ = fmap isJust $ io $ findExecutable "sshfs"
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
isMounted (SSHFS _ dir) = io $ isDirMounted dir
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
fmtEntry (SSHFS r _) = fmtEntry r
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
fstabToSSHFS :: FSTabEntry -> RofiIO MountConf SSHFS
fstabToSSHFS FSTabEntry{ fstabSpec = s, fstabDir = d } = return $ SSHFS r d
where
r = Removable { deviceSpec = s, label = takeFileName d }
2020-04-23 23:32:29 -04:00
2020-08-15 13:54:33 -04:00
--------------------------------------------------------------------------------
-- | VeraCrypt Devices
--
data VeraCrypt = VeraCrypt Removable FilePath (Maybe Password)
instance Mountable VeraCrypt where
2020-12-12 00:11:00 -05:00
mount (VeraCrypt Removable{ deviceSpec = s, label = l } m getPwd) False =
2020-08-15 13:54:33 -04:00
bracketOnError_
(mkDirMaybe m)
(rmDirMaybe m)
2020-12-12 00:11:00 -05:00
$ io $ (\res -> notifyMounted (isRight res) False l)
=<< runVeraCrypt
=<< ([s, m] ++) . maybe [] (\p -> ["-p", p]) . join
<$> sequence getPwd
2020-08-15 13:54:33 -04:00
2020-12-12 00:11:00 -05:00
mount (VeraCrypt Removable{ label = l } m _) True = io $ do
res <- runVeraCrypt ["-d", m]
notifyMounted (isRight res) True l
2020-08-15 13:54:33 -04:00
2020-12-12 00:11:00 -05:00
allInstalled _ = io $ isJust <$> findExecutable "veracrypt"
2020-08-15 13:54:33 -04:00
isMounted (VeraCrypt _ dir _) = io $ isDirMounted dir
fmtEntry (VeraCrypt r _ _) = fmtEntry r
2020-12-12 00:11:00 -05:00
runVeraCrypt :: [String] -> IO (Either (Int, String, String) String)
runVeraCrypt args = do
rootpass <- maybe "" (++ "\n") <$> readPassword' "Sudo Password"
readCmdEither "sudo" (defaultArgs ++ args) rootpass
where
defaultArgs = ["-S", "-E", "/usr/bin/veracrypt", "--text", "--non-interactive"]
getVeracryptDevices :: RofiIO MountConf [VeraCrypt]
getVeracryptDevices = mapM toDev =<< asks vcMounts
where
toDev (d, s) = do
pwd <- Just . M.findWithDefault readPassword d <$> asks passwords
let r = Removable { deviceSpec = s, label = takeFileName d }
return $ VeraCrypt r d pwd
2020-08-15 13:54:33 -04:00
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | MTP devices
--
-- These devices are a bit special because they are not based on Removable
-- devices (eg they don't have a label and a device spec). Instead they
-- are defined by a bus:device path. The program used for this is jmtpfs
-- (which seems to be the fastest and most robust)
2020-04-23 23:32:29 -04:00
data MTPFS = MTPFS
2020-05-01 21:29:54 -04:00
{ bus :: String
, device :: String
, mountpoint :: FilePath
, description :: String
2020-04-23 23:32:29 -04:00
}
deriving (Eq, Show)
instance Mountable MTPFS where
mount MTPFS {..} False = do
-- TODO add autodismount to options
let dev = "-device=" ++ bus ++ "," ++ device
2020-05-01 21:29:54 -04:00
bracketOnError_
(mkDirMaybe mountpoint)
(rmDirMaybe mountpoint)
(io $ runMountNotify "jmtpfs" [dev, mountpoint] description False)
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
mount MTPFS { mountpoint = m, description = d } True = umountNotify d m
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
-- | return True always since the list won't even show without jmtpfs
allInstalled _ = return True
2020-04-23 23:32:29 -04:00
2020-05-01 21:29:54 -04:00
isMounted MTPFS { mountpoint = dir } = io $ isDirMounted dir
2020-04-23 23:32:29 -04:00
fmtEntry MTPFS { description = d } = d
-- | Return list of all available MTP devices
2020-05-01 21:29:54 -04:00
getMTPDevices :: RofiIO MountConf [MTPFS]
getMTPDevices = do
dir <- asks mountDir
res <- io $ readProcess "jmtpfs" ["-l"] ""
return $ fromLines (toDev dir) $ toDevList res
2020-04-23 23:32:29 -04:00
where
toDevList = reverse
. takeWhile (not . isPrefixOf "Available devices")
. reverse
. lines
2020-05-01 21:29:54 -04:00
toDev dir s = case splitOn ", " s of
2020-04-23 23:32:29 -04:00
[busNum, devNum, _, _, desc, vendor] -> let d = unwords [vendor, desc]
in Just $ MTPFS
{ bus = busNum
, device = devNum
2020-05-01 21:29:54 -04:00
, mountpoint = dir </> canonicalize d
2020-04-23 23:32:29 -04:00
, description = d
}
_ -> Nothing
canonicalize = mapMaybe repl
repl c
| c `elem` ("\"*/:<>?\\|" :: String) = Nothing
| c == ' ' = Just '-'
| otherwise = Just c
--------------------------------------------------------------------------------
-- | Mountable typeclass
--
-- Let this class represent anything that can be mounted. The end goal is to
-- create a Rofi action which will define an entry in the rofi prompt for the
-- device at hand. In order to make an action, we need functions to mount the
-- device, check if the necessary mounting program(s) is installed, make the
-- entry to go in the prompt, and test if the device is mounted.
class Mountable a where
-- | Mount the given type (or dismount if False is passed)
mount :: a -> Bool -> RofiIO MountConf ()
-- | Check if the mounting utilities are present
allInstalled :: a -> RofiIO MountConf Bool
-- | Return a string to go in the Rofi menu for the given type
fmtEntry :: a -> String
-- | Determine if the given type is mounted or not
isMounted :: a -> RofiIO MountConf Bool
-- | Given a mountable type, return a rofi action (string to go in the
-- Rofi prompt and an action to perform when it is selected)
mkAction :: a -> RofiIO MountConf (String, RofiIO MountConf ())
mkAction dev = do
m <- isMounted dev
i <- allInstalled dev
let a = when i $ mount dev m
let s = mountedPrefix m i ++ fmtEntry dev
return (s, a)
where
mountedPrefix False True = " "
mountedPrefix True True = "* "
mountedPrefix _ False = "! "
-- TODO add truecrypt volumes
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
2020-05-01 21:29:54 -04:00
-- | Fstab devices
--
-- Functions to gather all user fstab mounts on the system
2020-05-01 21:29:54 -04:00
-- | Intermediate structure to hold fstab devices
2020-05-01 21:29:54 -04:00
data FSTab = FSTab
2020-12-12 00:11:00 -05:00
{ sshfsDevices :: [SSHFS]
, cifsDevices :: [CIFS]
-- , veracryptDevices :: [VeraCrypt]
2020-04-23 23:32:29 -04:00
}
2020-05-01 21:29:54 -04:00
-- | Data structure representing an fstab device (or one line in the fstab file)
2020-05-01 21:29:54 -04:00
data FSTabEntry = FSTabEntry
{ fstabSpec :: String
, fstabDir :: FilePath
, fstabType :: String
, fstabOptions :: MountOptions
}
-- | Key/val pairs to represent mount options. A Nothing for the value signifies
-- a standalone option (eg 'rw' and 'ro')
type MountOptions = M.Map String (Maybe String)
-- | Return all user fstab devices from /etc/fstab
2020-05-01 21:29:54 -04:00
readFSTab :: RofiIO MountConf FSTab
readFSTab = do
2020-12-12 00:11:00 -05:00
-- let i = FSTab { sshfsDevices = [], cifsDevices = [], veracryptDevices = []}
let i = FSTab { sshfsDevices = [], cifsDevices = []}
2020-05-01 21:29:54 -04:00
fstab <- io $ readFile "/etc/fstab"
foldM addFstabDevice i $ fromLines toEntry $ lines fstab
2020-04-23 23:32:29 -04:00
where
toEntry line = case words line of
2020-05-01 21:29:54 -04:00
(('#':_):_) -> Nothing
[spec, dir, fsType, opts, _, _] -> Just $ FSTabEntry
{ fstabSpec = spec
, fstabDir = dir
, fstabType = fsType
, fstabOptions = parseOptions opts
2020-05-01 21:29:54 -04:00
}
_ -> Nothing
parseOptions = M.fromList . fromCommaSepString
2020-05-01 21:29:54 -04:00
-- | Add entry to the fstab devices list, but only if it is a known user mount
2020-05-01 21:29:54 -04:00
addFstabDevice :: FSTab -> FSTabEntry -> RofiIO MountConf FSTab
addFstabDevice f@FSTab{..} e@FSTabEntry{..}
| M.notMember "users" fstabOptions = return f
| fstabType == "cifs" =
(\d -> f { cifsDevices = append d cifsDevices }) <$> fstabToCIFS e
2020-05-01 21:29:54 -04:00
| fstabType == "fuse.sshfs" =
(\d -> f { sshfsDevices = append d sshfsDevices }) <$> fstabToSSHFS e
2020-12-12 00:11:00 -05:00
-- | fstabType == "veracrypt" =
-- (\d -> f { veracryptDevices = append d veracryptDevices }) <$> fstabToVeraCrypt e
2020-05-01 21:29:54 -04:00
| otherwise = return f
where
append x xs = xs ++ [x]
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | Low-level mount functions
-- ASSUME these will never fail because the format of /proc/mounts is fixed
2020-05-01 21:29:54 -04:00
curMountField :: Int -> IO [String]
curMountField i = fmap ((!! i) . words) . lines <$> readFile "/proc/mounts"
curDeviceSpecs :: IO [String]
curDeviceSpecs = curMountField 0
curMountpoints :: IO [String]
curMountpoints = curMountField 1
-- ASSUME the base mount path will always be created because
-- 'createDirectoryIfMissing' will make parents if missing, and that removing
-- all the directories will leave the base mount path intact regardless of if it
-- was present before doing anything (which matters here since I'm putting the
-- base path in /tmp, so all this is saying is that umounting everything will
-- leave /tmp/media/USER without removing all the way down to /tmp)
2020-05-01 21:29:54 -04:00
mkDirMaybe :: FilePath -> RofiIO MountConf ()
mkDirMaybe fp = whenInMountDir fp $ io $ createDirectoryIfMissing True fp
rmDirMaybe :: FilePath -> RofiIO MountConf ()
rmDirMaybe fp = whenInMountDir fp $ unlessMountpoint fp
$ asks mountDir >>= io . rmUntil fp
where
rmUntil cur target = unless (target == cur) $ do
removePathForcibly cur
rmUntil (takeDirectory cur) target
whenInMountDir :: FilePath -> RofiIO MountConf () -> RofiIO MountConf ()
whenInMountDir fp f = do
mDir <- asks mountDir
when (mDir `isPrefixOf` fp) f
unlessMountpoint :: FilePath -> RofiIO MountConf () -> RofiIO MountConf ()
unlessMountpoint fp f = do
mounted <- io $ isDirMounted fp
unless mounted f
isDirMounted :: FilePath -> IO Bool
isDirMounted fp = elem fp <$> curMountpoints
2020-04-23 23:32:29 -04:00
runMountNotify :: String -> [String] -> String -> Bool -> IO ()
runMountNotify cmd args msg mounted = do
res <- readCmdEither cmd args ""
notifyMounted (isRight res) mounted msg
2020-08-15 13:54:33 -04:00
umountNotify' :: String -> String -> FilePath -> RofiIO MountConf ()
umountNotify' cmd msg dir = finally
(io $ runMountNotify cmd [dir] msg True)
(rmDirMaybe dir)
2020-08-15 13:54:33 -04:00
umountNotify :: String -> FilePath -> RofiIO MountConf ()
umountNotify = umountNotify' "umount"
-- | Send a notification indicating the mount succeeded
notifyMounted :: Bool -> Bool -> String -> IO ()
2020-05-02 00:13:25 -04:00
notifyMounted succeeded mounted label =
void $ spawnProcess "notify-send" ["-i", i, msg]
where
2020-05-02 00:13:25 -04:00
(f, i) = if succeeded
then ("Successfully %sed %s", "dialog-information-symbolic")
else ("Failed to %s %s", "dialog-error-symbolic")
m = if mounted then "unmount" else "mount" :: String
msg = printf f m label
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | Other functions
fromLines :: (String -> Maybe a) -> [String] -> [a]
fromLines f = mapMaybe (f . stripWS)
2020-04-23 23:32:29 -04:00
-- TODO this exists somewhere...
splitBy :: Char -> String -> [String]
splitBy delimiter = foldr f [[]]
where
f _ [] = []
f c l@(x:xs) | c == delimiter = []:l
| otherwise = (c:x):xs
-- | Like fromCommaSepString but only return substrings with '='
fromCommaSepString' :: String -> [(String, String)]
fromCommaSepString' s = [(k, v) | (k, Just v) <- fromCommaSepString s]
-- | Split a string of comma-separated values into an alist
-- If the substrings have an '=' in them, the left side will become the key and
-- the right will become the value of the cell. If there is not '=' then the
-- entire substring will become the key and the value will be Nothing
fromCommaSepString :: String -> [(String, Maybe String)]
fromCommaSepString = fmap (toCell . splitEq) . splitBy ','
2020-04-23 23:32:29 -04:00
where
splitEq e = e =~ ("=" :: String) :: (String, String, String)
toCell (k, "=", v) = (k, Just v)
toCell (k, _, _) = (k, Nothing)