rofi-extras/app/rofi-dev.hs

718 lines
24 KiB
Haskell
Raw Normal View History

2020-04-23 23:32:29 -04:00
{-# LANGUAGE OverloadedStrings #-}
2021-03-22 19:20:32 -04:00
{-# LANGUAGE FlexibleInstances #-}
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | 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
2020-04-23 23:32:29 -04:00
import Data.Maybe
2021-03-19 23:23:45 -04:00
import qualified Data.Text as T
2021-03-18 00:41:04 -04:00
import qualified Data.Vector as V
import Data.Yaml
2020-04-23 23:32:29 -04:00
import Rofi.Command
import Text.Printf
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
2021-03-19 23:23:45 -04:00
(o, n, []) -> runMounts $ foldl (flip id) (defaultOpts n) 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]"
2021-03-19 23:23:45 -04:00
defaultOpts r = Opts
{ optsConfig = Nothing
, optsAlias = Nothing
, optsUnmount = False
, optsRofiArgs = r
}
2020-05-01 21:29:54 -04:00
2021-03-19 23:23:45 -04:00
options :: [OptDescr (Opts -> Opts)]
2020-05-01 21:29:54 -04:00
options =
2021-03-18 00:41:04 -04:00
[ Option ['c'] ["config"]
2021-03-19 23:23:45 -04:00
(ReqArg (\s m -> m { optsConfig = Just s } ) "CONF")
2021-03-18 00:41:04 -04:00
"The path to the config file"
2021-03-19 23:23:45 -04:00
, Option ['m'] ["mount"]
(ReqArg (\s m -> m { optsAlias = Just s } ) "ALIAS")
"Mount the device specified by ALIAS directly"
, Option ['u'] ["unmount"] (NoArg (\m -> m { optsUnmount = True } ))
"Unmount the device specified by ALIAS instead of mounting it."
2020-05-01 21:29:54 -04:00
]
2021-03-19 23:23:45 -04:00
data Opts = Opts
{ optsConfig :: Maybe FilePath
, optsAlias :: Maybe String
, optsUnmount :: Bool
, optsRofiArgs :: [String]
} deriving Show
--------------------------------------------------------------------------------
2021-03-23 21:39:41 -04:00
-- | 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
runMounts :: Opts -> IO ()
runMounts opts = do
static <- join <$> traverse parseStaticConfig (optsConfig opts)
defaultTmpPath <- ("/tmp/media" </>) <$> getEffectiveUserName
2021-03-23 22:39:02 -04:00
let tmpPath = fromMaybe defaultTmpPath $ staticconfigTmpPath =<< static
let staticDevs = maybe M.empty staticconfigDevices static
let verbose = fromMaybe False $ staticconfigVerbose =<< static
2021-03-23 21:39:41 -04:00
let mountconf = MountConf
{ mountconfVolatilePath = tmpPath
, mountconfRofiArgs = optsRofiArgs opts
, mountconfStaticDevs = staticDevs
, mountconfVerbose = verbose
}
let byAlias = mountByAlias $ optsUnmount opts
let byPrompt = runPrompt =<< getGroups
runRofiIO mountconf $ maybe byPrompt byAlias $ optsAlias opts
parseStaticConfig :: FilePath -> IO (Maybe StaticConfig)
parseStaticConfig p = do
res <- decodeFileEither p
case res of
Left e -> print e >> return Nothing
Right c -> return $ Just c
runPrompt :: RofiConf c => [RofiGroup c] -> RofiIO c ()
runPrompt gs = selectAction $ emptyMenu
{ groups = gs
, prompt = Just "Select Device"
}
getGroups :: RofiMountIO [RofiGroup MountConf]
getGroups = do
staticDevs <- asks mountconfStaticDevs
staticActions <- mapM mkAction $ configToTree' staticDevs
removableActions <- mapM mkAction =<< getRemovableDevices
mtpActions <- mapM mkAction =<< getMTPDevices
return $ mapMaybe mkGroup
$ groupBy (\(hx, _) (hy, _) -> hx == hy)
$ sortBy (\(hx, _) (hy, _) -> compare hx hy)
$ staticActions ++ removableActions ++ mtpActions
mountByAlias :: Bool -> String -> RofiMountIO ()
mountByAlias unmountFlag alias = do
static <- asks mountconfStaticDevs
mapM_ (`mountMaybe` unmountFlag) $ configToTree static <$> M.lookup alias static
mkGroup :: [(Header, ProtoAction [String])] -> Maybe (RofiGroup MountConf)
mkGroup [] = Nothing
2021-03-23 22:39:02 -04:00
mkGroup as = let ((h, _):_) = as in
Just $ titledGroup (show h) $ toRofiActions $ alignEntries $ fmap snd as
2021-03-23 21:39:41 -04:00
alignSep :: String
alignSep = " | "
alignEntries :: [ProtoAction [String]] -> [(String, RofiMountIO ())]
alignEntries ps = zip (align es) as
where
(es, as) = unzip $ fmap (\(ProtoAction e a) -> (e, a)) ps
align = fmap (intercalate alignSep)
. transpose
. mapToLast pad
. transpose
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
--------------------------------------------------------------------------------
-- | Global config used in the reader monad stack
data MountConf = MountConf
{ mountconfVolatilePath :: FilePath
, mountconfRofiArgs :: [String]
, mountconfStaticDevs :: M.Map String TreeConfig
, mountconfVerbose :: Bool
} deriving Show
instance RofiConf MountConf where
defArgs MountConf { mountconfRofiArgs = a } = a
--------------------------------------------------------------------------------
-- | Mountable typeclass
--
2021-03-23 21:39:41 -04:00
-- Class to provide common interface for anything that can be mounted.
class Mountable a where
-- | Mount the given type (or dismount if False is passed)
mount :: a -> Bool -> RofiMountIO ()
mountMaybe :: a -> Bool -> RofiMountIO ()
mountMaybe dev mountFlag = do
mounted <- isMounted dev
verbose <- asks mountconfVerbose
if mountFlag == mounted then mount dev mountFlag
else when verbose notify'
where
notify' = io $ notify "dialog-information-symbolic"
$ getLabel dev ++ " already mounted"
-- | Check if the mounting utilities are present
allInstalled :: a -> RofiMountIO Bool
-- | Return a string representing the label of the device
getLabel :: a -> String
-- | Determine if the given type is mounted or not
isMounted :: a -> RofiMountIO Bool
--------------------------------------------------------------------------------
-- | Actionable typeclass
--
-- Class to provide common interface for anything that can be presented in the
-- Rofi menu as an action. Note that this must be separate from the Mountable
-- class above because some devices are represented as trees, and displaying
-- these trees in the rofi menu only requires that the tree itself be presented
-- and not its subcomponents.
class Mountable a => Actionable a where
-- | Return a string to go in the Rofi menu for the given type
fmtEntry :: a -> [String]
fmtEntry d = [getLabel d]
groupHeader :: a -> Header
-- | 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 -> RofiMountIO (Header, ProtoAction [String])
mkAction dev = do
m <- isMounted dev
i <- allInstalled dev
let h = groupHeader dev
let action = when i $ mountMaybe dev m
let entry = case fmtEntry dev of
(e:es) -> (mountedPrefix m i ++ e):es
_ -> []
return (h, ProtoAction entry action)
where
mountedPrefix False True = " "
mountedPrefix True True = "* "
mountedPrefix _ False = "! "
type RofiMountIO a = RofiIO MountConf a
2021-03-23 22:39:02 -04:00
-- headers appear in the order listed here (per Enum)
data Header = CIFSHeader
| SSHFSHeader
| VeracryptHeader
| RemovableHeader
| MTPFSHeader
deriving (Enum, Eq)
instance Show Header where
show h = case h of
CIFSHeader -> suffix "CIFS"
SSHFSHeader -> suffix "SSHFS"
VeracryptHeader -> suffix "Veracrypt"
RemovableHeader -> suffix "Removable"
MTPFSHeader -> suffix "MTPFS"
where
suffix = (++ " Devices")
2021-03-23 21:39:41 -04:00
data ProtoAction a = ProtoAction a (RofiMountIO ())
instance Ord Header where
2021-03-23 22:39:02 -04:00
compare x y = compare (fromEnum x) (fromEnum y)
2021-03-23 21:39:41 -04:00
--------------------------------------------------------------------------------
-- | Static device configuration
--
-- Static devices are defined in a YAML file. These types/instances describe how
-- to parse said YAML file.
2021-03-18 00:41:04 -04:00
defaultTries :: Integer
defaultTries = 2
2021-03-19 23:23:45 -04:00
(.:&) :: FromJSON a => Object -> T.Text -> Parser (V.Vector a)
(.:&) o t = o .:? t .!= V.empty
2021-03-18 00:41:04 -04:00
data MountConfig = MountConfig
2021-03-23 22:39:02 -04:00
{ mountMountpoint :: FilePath
, mountLabel :: Maybe String
2021-03-18 00:41:04 -04:00
} deriving Show
instance FromJSON MountConfig where
2021-03-23 22:39:02 -04:00
parseJSON = withObject "mount" $ \o -> MountConfig
2021-03-18 00:41:04 -04:00
<$> o .: "mountpoint"
<*> o .:? "label"
data BitwardenConfig = BitwardenConfig
2021-03-23 22:39:02 -04:00
{ bitwardenKey :: String
, bitwardenTries :: Integer }
2021-03-18 00:41:04 -04:00
deriving Show
instance FromJSON BitwardenConfig where
parseJSON = withObject "bitwarden" $ \o -> BitwardenConfig
<$> o .: "key"
<*> o .:? "tries" .!= defaultTries
newtype LibSecretConfig = LibSecretConfig
2021-03-23 22:39:02 -04:00
{ libsecretAttributes :: M.Map String String }
2021-03-18 00:41:04 -04:00
deriving Show
instance FromJSON LibSecretConfig where
parseJSON = withObject "libsecret" $ \o -> LibSecretConfig
<$> o .: "attributes"
newtype PromptConfig = PromptConfig
2021-03-23 22:39:02 -04:00
{ promptTries :: Integer }
2021-03-18 00:41:04 -04:00
deriving Show
instance FromJSON PromptConfig where
parseJSON = withObject "libsecret" $ \o -> PromptConfig
<$> o .: "tries" .!= defaultTries
data PasswordConfig = PasswordConfig
2021-03-23 22:39:02 -04:00
{ passwordBitwarden :: Maybe BitwardenConfig
, passwordLibSecret :: Maybe LibSecretConfig
, passwordPrompt :: Maybe PromptConfig
2021-03-18 00:41:04 -04:00
}
deriving Show
instance FromJSON PasswordConfig where
parseJSON = withObject "password" $ \o -> PasswordConfig
<$> o .:? "bitwarden"
<*> o .:? "libsecret"
<*> o .:? "prompt"
2021-03-20 14:00:47 -04:00
2021-03-22 19:20:32 -04:00
data DataConfig = VeracryptConfig
2021-03-23 22:39:02 -04:00
{ veracryptVolume :: String
, veracryptPassword :: Maybe PasswordConfig
2021-03-20 14:00:47 -04:00
} | SSHFSConfig
2021-03-23 22:39:02 -04:00
{ sshfsRemote :: String
2021-03-20 14:00:47 -04:00
} | CIFSConfig
2021-03-23 22:39:02 -04:00
{ cifsRemote :: String
, cifsPassword :: Maybe PasswordConfig
2021-03-18 00:41:04 -04:00
} deriving Show
2021-03-22 19:20:32 -04:00
data DeviceConfig = DeviceConfig
2021-03-23 22:39:02 -04:00
{ deviceMount :: MountConfig
, deviceData :: DataConfig
2021-03-22 19:20:32 -04:00
} deriving Show
data TreeConfig = TreeConfig
2021-03-23 22:39:02 -04:00
{ treeParent :: DeviceConfig
, treeconfigChildren :: V.Vector String
2021-03-22 19:20:32 -04:00
} deriving Show
instance FromJSON TreeConfig where
2021-03-20 14:00:47 -04:00
parseJSON = withObject "devices" $ \o -> do
devType <- o .: "type"
2021-03-22 19:20:32 -04:00
deps <- o .:& "depends"
mountconf <- o .: "mount"
devData <- case (devType :: String) of
"cifs" -> CIFSConfig
<$> o .: "remote"
<*> o .:? "password"
"sshfs" -> SSHFSConfig
<$> o .: "remote"
"veracrypt" -> VeracryptConfig
<$> o .: "volume"
<*> o .:? "password"
-- TODO make this skip adding an entry to the map rather than
-- skipping the map entirely
_ -> fail $ "unknown device type: " ++ devType
return $ TreeConfig
2021-03-23 22:39:02 -04:00
{ treeParent = DeviceConfig
{ deviceMount = mountconf
, deviceData = devData
2021-03-22 19:20:32 -04:00
}
2021-03-23 22:39:02 -04:00
, treeconfigChildren = deps
2021-03-22 19:20:32 -04:00
}
2021-03-18 00:41:04 -04:00
data StaticConfig = StaticConfig
2021-03-23 22:39:02 -04:00
{ staticconfigTmpPath :: Maybe String
, staticconfigVerbose :: Maybe Bool
, staticconfigDevices :: M.Map String TreeConfig
2021-03-18 00:41:04 -04:00
} deriving Show
instance FromJSON StaticConfig where
parseJSON = withObject "devices" $ \o -> StaticConfig
<$> o .:? "mountdir"
2021-03-23 20:42:14 -04:00
<*> o .:? "verbose"
2021-03-20 14:00:47 -04:00
<*> o .: "devices"
2021-03-18 00:41:04 -04:00
--------------------------------------------------------------------------------
2021-03-23 21:39:41 -04:00
-- | Static devices trees
2021-03-18 00:41:04 -04:00
--
2021-03-23 21:39:41 -04:00
-- Static devices as defined in the config file may declare dependencies on
-- other static devices, and thus are best represented as a tree. Note that the
-- tree is both Actionable and Mountable, where each node in the tree is only
-- Mountable; this is because trees need to be displayed and chosen in the Rofi
-- menu.
2021-03-23 21:39:41 -04:00
data Tree a = Tree a [Tree a] deriving (Eq, Show)
2021-03-23 21:39:41 -04:00
type StaticConfigTree = Tree DeviceConfig
instance Mountable a => Mountable (Tree a) where
mount (Tree p cs) False = mapM_ (`mountMaybe` False) cs >> mount p False
mount (Tree p _) True = mount p True
isMounted (Tree p _) = isMounted p
allInstalled (Tree p cs) = do
res <- and <$> mapM allInstalled cs
if res then allInstalled p else return res
getLabel (Tree p _) = getLabel p
instance Actionable (Tree DeviceConfig) where
2021-03-23 22:39:02 -04:00
fmtEntry (Tree p@DeviceConfig{ deviceData = d } _) = [getLabel p, target d]
2021-03-23 21:39:41 -04:00
where
2021-03-23 22:39:02 -04:00
target CIFSConfig{ cifsRemote = r } = r
target SSHFSConfig{ sshfsRemote = r } = r
target VeracryptConfig{ veracryptVolume = v } = v
2021-03-23 21:39:41 -04:00
2021-03-23 22:39:02 -04:00
groupHeader (Tree DeviceConfig{ deviceData = d } _) =
2021-03-23 21:39:41 -04:00
case d of
2021-03-23 22:39:02 -04:00
CIFSConfig{} -> CIFSHeader
SSHFSConfig{} -> SSHFSHeader
VeracryptConfig{} -> VeracryptHeader
2021-03-23 21:39:41 -04:00
configToTree' :: M.Map String TreeConfig -> [StaticConfigTree]
configToTree' devMap = configToTree devMap <$> M.elems devMap
configToTree :: M.Map String TreeConfig -> TreeConfig -> StaticConfigTree
2021-03-23 22:39:02 -04:00
configToTree devMap TreeConfig{ treeParent = p, treeconfigChildren = c } =
2021-03-23 21:39:41 -04:00
Tree p $ fmap go V.toList c
where
go ds = configToTree devMap <$> mapMaybe (`M.lookup` devMap) ds
--------------------------------------------------------------------------------
-- | Static devices
--
-- This is complex because there may be multiple classes of static devices
-- in the config file, and each device may depend on another device that is
-- a different class (eg sshfs on cifs). I deal with this by abstracting the
-- differences between each class in a sum-record type; in this way the
-- processing "splits" and "converges" entirely in this function, so nothing
-- outside of these needs to be aware of these different classes.
instance Mountable DeviceConfig where
2021-03-23 22:39:02 -04:00
mount c@DeviceConfig{ deviceMount = m, deviceData = devData} False = do
2021-03-23 21:39:41 -04:00
m' <- getAbsMountpoint m
bracketOnError_ (mkDirMaybe m') (rmDirMaybe m') $ mount' m'
where
mount' mountpoint = io $ case devData of
2021-03-23 22:39:02 -04:00
SSHFSConfig{ sshfsRemote = r } -> do
2021-03-23 21:39:41 -04:00
runMountNotify "sshfs" [r, mountpoint] (getLabel c) False
2021-03-23 22:39:02 -04:00
CIFSConfig{ cifsPassword = p } -> do
2021-03-23 21:39:41 -04:00
res <- case p of
Just pwd -> do
pwd' <- maybe [] (\p' -> [("PASSWD", p')]) <$> configToPwd pwd
readCmdEither' "mount" [mountpoint] "" pwd'
Nothing -> readCmdEither "mount" [mountpoint] ""
notifyMounted (isRight res) False (getLabel c)
2021-03-23 22:39:02 -04:00
VeracryptConfig{ veracryptPassword = getPwd, veracryptVolume = v } ->
2021-03-23 21:39:41 -04:00
maybe (runVeraCryptWith "" []) (runVeraCryptWithPwd =<<) (configToPwd <$> getPwd)
where
label = getLabel c
runVeraCryptWithPwd = maybe notifyFail (\p -> runVeraCryptWith p ["--stdin"])
runVeraCryptWith stdin args = (\res -> notifyMounted (isRight res) False label)
=<< runVeraCrypt stdin ([v, mountpoint] ++ args)
notifyFail = notify "dialog-error-symbolic" $
printf "Failed to get volume password for %s" label
2021-03-23 22:39:02 -04:00
mount c@DeviceConfig{ deviceMount = m, deviceData = VeracryptConfig{} } True = do
2021-03-23 21:39:41 -04:00
m' <- getAbsMountpoint m
res <- io $ runVeraCrypt "" ["-d", m']
io $ notifyMounted (isRight res) True (getLabel c)
2021-03-23 22:39:02 -04:00
mount c@DeviceConfig{ deviceMount = m } True =
2021-03-23 21:39:41 -04:00
umountNotify (getLabel c) =<< getAbsMountpoint m
2021-03-23 22:39:02 -04:00
allInstalled DeviceConfig{ deviceData = devData } = io $ isJust
2021-03-23 21:39:41 -04:00
<$> findExecutable (exe devData)
where
exe SSHFSConfig{} = "sshfs"
exe CIFSConfig{} = "mount.cifs"
exe VeracryptConfig{} = "veracrypt"
2021-03-23 22:39:02 -04:00
isMounted DeviceConfig{ deviceMount = m } =
2021-03-23 21:39:41 -04:00
(io . isDirMounted) =<< getAbsMountpoint m
getLabel DeviceConfig
2021-03-23 22:39:02 -04:00
{ deviceMount = MountConfig { mountMountpoint = p, mountLabel = l }
2021-03-23 21:39:41 -04:00
} = fromMaybe (takeFileName p) l
getAbsMountpoint :: MountConfig -> RofiMountIO FilePath
2021-03-23 22:39:02 -04:00
getAbsMountpoint MountConfig{ mountMountpoint = m } =
2021-03-23 21:39:41 -04:00
asks $ flip appendRoot m . mountconfVolatilePath
-- NOTE: the user is assumed to have added themselves to the sudoers file so
-- that this command will work
runVeraCrypt :: String -> [String] -> IO (Either (Int, String, String) String)
runVeraCrypt stdin args = do
readCmdEither "sudo" (defaultArgs ++ args) stdin
where
defaultArgs = ["/usr/bin/veracrypt", "--text", "--non-interactive"]
2020-05-01 21:29:54 -04:00
--------------------------------------------------------------------------------
2021-03-23 21:39:41 -04:00
-- | Password-getting functions for static devices
2021-03-18 00:41:04 -04:00
type PasswordGetter = IO (Maybe String)
2020-05-01 21:29:54 -04:00
2021-03-23 22:39:02 -04:00
runSecret :: M.Map String String -> PasswordGetter
runSecret kvs = readCmdSuccess "secret-tool" ("lookup":kvs') ""
2020-05-01 21:29:54 -04:00
where
2021-03-23 22:39:02 -04:00
kvs' = concatMap (\(k, v) -> [k, v]) $ M.toList kvs
2020-05-01 21:29:54 -04:00
runBitwarden :: String -> PasswordGetter
runBitwarden pname = ((password . login) <=< find (\i -> name i == pname))
<$> getItems
2021-03-18 00:41:04 -04:00
runPromptLoop :: Integer -> PasswordGetter -> PasswordGetter
runPromptLoop n pwd = do
res <- pwd
if isNothing res then
if n <= 0 then return Nothing else runPromptLoop (n-1) pwd
else return res
configToPwd :: PasswordConfig -> PasswordGetter
2021-03-23 22:00:25 -04:00
configToPwd PasswordConfig
2021-03-23 22:39:02 -04:00
{ passwordBitwarden = b
, passwordLibSecret = s
, passwordPrompt = p
2021-03-23 22:00:25 -04:00
} =
2021-03-18 00:41:04 -04:00
getBW b `runMaybe` getLS s `runMaybe` getPrompt p
where
2021-03-23 22:39:02 -04:00
getBW (Just BitwardenConfig{ bitwardenKey = k, bitwardenTries = n }) =
2021-03-18 00:41:04 -04:00
runPromptLoop n $ runBitwarden k
getBW _ = return Nothing
2021-03-23 22:39:02 -04:00
getLS = maybe (return Nothing) (runSecret . libsecretAttributes)
getPrompt = maybe (return Nothing) (flip runPromptLoop readPassword . promptTries)
2021-03-23 22:00:25 -04:00
runMaybe x y = (\r -> if isNothing r then y else return r) =<< x
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | Removable devices
--
2021-03-23 21:39:41 -04:00
-- A device which can be removed (such as a flash drive). These are distinct
-- from any device in the static configuration in that they only have device
-- addresses (eg in /dev) and labels.
2020-04-23 23:32:29 -04:00
data Removable = Removable
2021-03-23 22:39:02 -04:00
{ removablePath :: String
, removableLabel :: String
2020-04-23 23:32:29 -04:00
}
deriving (Eq, Show)
instance Mountable Removable where
2021-03-23 22:39:02 -04:00
mount Removable { removablePath = d, removableLabel = 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
2021-03-23 22:39:02 -04:00
isMounted Removable { removablePath = d } = elem d <$> io curDeviceSpecs
2020-04-23 23:32:29 -04:00
2021-03-23 22:39:02 -04:00
getLabel Removable { removableLabel = l } = l
2021-03-22 19:20:32 -04:00
instance Actionable Removable where
2021-03-23 22:39:02 -04:00
fmtEntry Removable { removablePath = d, removableLabel = l } = [l, d]
2020-04-23 23:32:29 -04:00
2021-03-23 22:39:02 -04:00
groupHeader _ = RemovableHeader
2021-03-22 19:20:32 -04:00
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
2021-03-23 22:39:02 -04:00
mk d l = Just $ Removable { removablePath = d, removableLabel = l }
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
-- | MTP devices
data MTPFS = MTPFS
2021-03-23 22:39:02 -04:00
{ mtpfsBus :: String
, mtpfsDevice :: String
, mtpfsMountpoint :: FilePath
, mtpfsDescription :: String
2020-04-23 23:32:29 -04:00
}
deriving (Eq, Show)
instance Mountable MTPFS where
2021-03-23 22:39:02 -04:00
mount MTPFS { mtpfsBus = b
, mtpfsDevice = n
, mtpfsMountpoint = m
, mtpfsDescription = d
} False = do
2020-04-23 23:32:29 -04:00
-- TODO add autodismount to options
2021-03-23 22:39:02 -04:00
let dev = "-device=" ++ b ++ "," ++ n
2020-05-01 21:29:54 -04:00
bracketOnError_
2021-03-23 22:39:02 -04:00
(mkDirMaybe m)
(rmDirMaybe m)
$ io $ runMountNotify "jmtpfs" [dev, m] d False
2020-04-23 23:32:29 -04:00
2021-03-23 22:39:02 -04:00
mount MTPFS { mtpfsMountpoint = m, mtpfsDescription = 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
2021-03-23 22:39:02 -04:00
isMounted = io . isDirMounted <$> mtpfsMountpoint
2020-04-23 23:32:29 -04:00
2021-03-23 22:39:02 -04:00
getLabel = mtpfsDescription
2021-03-22 19:20:32 -04:00
-- | Return list of all available MTP devices
2021-03-23 21:39:41 -04:00
getMTPDevices :: RofiMountIO [MTPFS]
2020-05-01 21:29:54 -04:00
getMTPDevices = do
2021-03-19 23:23:45 -04:00
dir <- asks mountconfVolatilePath
2020-05-01 21:29:54 -04:00
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
2021-03-23 22:39:02 -04:00
{ mtpfsBus = busNum
, mtpfsDevice = devNum
, mtpfsMountpoint = dir </> canonicalize d
, mtpfsDescription = d
2020-04-23 23:32:29 -04:00
}
_ -> Nothing
canonicalize = mapMaybe repl
repl c
| c `elem` ("\"*/:<>?\\|" :: String) = Nothing
| c == ' ' = Just '-'
| otherwise = Just c
2021-03-23 21:39:41 -04:00
instance Actionable MTPFS where
2021-03-23 01:09:43 -04:00
fmtEntry d = [getLabel d]
2021-03-22 19:20:32 -04:00
2021-03-23 22:39:02 -04:00
groupHeader _ = MTPFSHeader
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)
2021-03-23 21:39:41 -04:00
mkDirMaybe :: FilePath -> RofiMountIO ()
2020-05-01 21:29:54 -04:00
mkDirMaybe fp = whenInMountDir fp $ io $ createDirectoryIfMissing True fp
2021-03-23 21:39:41 -04:00
rmDirMaybe :: FilePath -> RofiMountIO ()
2020-05-01 21:29:54 -04:00
rmDirMaybe fp = whenInMountDir fp $ unlessMountpoint fp
2021-03-19 23:23:45 -04:00
$ asks mountconfVolatilePath >>= io . rmUntil fp
2020-05-01 21:29:54 -04:00
where
rmUntil cur target = unless (target == cur) $ do
removePathForcibly cur
rmUntil (takeDirectory cur) target
2021-03-23 21:39:41 -04:00
whenInMountDir :: FilePath -> RofiMountIO () -> RofiIO MountConf ()
2020-05-01 21:29:54 -04:00
whenInMountDir fp f = do
2021-03-19 23:23:45 -04:00
mDir <- asks mountconfVolatilePath
2020-05-01 21:29:54 -04:00
when (mDir `isPrefixOf` fp) f
2021-03-23 21:39:41 -04:00
unlessMountpoint :: MonadIO m => FilePath -> m () -> m ()
2020-05-01 21:29:54 -04:00
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
2021-03-23 21:39:41 -04:00
umountNotify' :: String -> String -> FilePath -> RofiMountIO ()
2020-08-15 13:54:33 -04:00
umountNotify' cmd msg dir = finally
(io $ runMountNotify cmd [dir] msg True)
(rmDirMaybe dir)
2021-03-23 21:39:41 -04:00
umountNotify :: String -> FilePath -> RofiMountIO ()
2020-08-15 13:54:33 -04:00
umountNotify = umountNotify' "umount"
-- | Send a notification indicating the mount succeeded
notifyMounted :: Bool -> Bool -> String -> IO ()
notifyMounted succeeded mounted label = notify icon body
where
(format, icon) = if succeeded
2020-05-02 00:13:25 -04:00
then ("Successfully %sed %s", "dialog-information-symbolic")
else ("Failed to %s %s", "dialog-error-symbolic")
m = if mounted then "unmount" else "mount" :: String
body = printf format m label
notify :: String -> String -> IO ()
notify icon body = void $ spawnProcess "notify-send" ["-i", icon, body]
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
2021-03-18 00:41:04 -04:00
appendRoot :: FilePath -> FilePath -> FilePath
appendRoot root path = if isRelative path then root </> path else path