rofi-extras/app/rofi-dev.hs

823 lines
28 KiB
Haskell
Raw Normal View History

2023-01-24 09:22:19 -05:00
{-# LANGUAGE DeriveAnyClass #-}
2023-02-14 00:37:50 -05:00
{-# LANGUAGE TemplateHaskell #-}
2023-02-13 22:19:49 -05:00
{-# LANGUAGE NoGeneralizedNewtypeDeriving #-}
2022-08-07 11:42:06 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05: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
2023-01-24 09:22:19 -05:00
import Bitwarden.Internal
2023-02-13 22:19:49 -05:00
import qualified Data.Text.IO as TI
2023-01-24 09:22:19 -05:00
import Dhall hiding (maybe, sequence, void)
2023-02-14 00:37:50 -05:00
import Dhall.TH
2023-02-13 22:19:49 -05:00
import RIO
import RIO.Directory
import qualified RIO.List as L
import qualified RIO.Map as M
2023-02-14 23:09:12 -05:00
import qualified RIO.NonEmpty as NE
2023-02-13 22:19:49 -05:00
import qualified RIO.Text as T
2023-01-24 09:22:19 -05:00
import Rofi.Command
import System.Console.GetOpt
import System.Environment
import System.FilePath.Posix
import System.Posix.User (getEffectiveUserName)
import System.Process
2020-05-01 21:29:54 -04:00
2023-02-14 00:37:50 -05:00
--------------------------------------------------------------------------------
-- Static device configuration (dhall)
makeHaskellTypesWith
(defaultGenerateOptions {generateToDhallInstance = False})
[ MultipleConstructors "PasswordConfig" "(./dhall/rofi-dev.dhall).PasswordConfig"
, MultipleConstructors "DataConfig" "(./dhall/rofi-dev.dhall).DataConfig"
, SingleConstructor "TreeMap" "TreeMap" "(./dhall/rofi-dev.dhall).TreeMap"
, SingleConstructor "SecretMap" "SecretMap" "(./dhall/rofi-dev.dhall).SecretMap"
, SingleConstructor "StaticConfig" "StaticConfig" "(./dhall/rofi-dev.dhall).StaticConfig"
, SingleConstructor "PromptConfig" "PromptConfig" "(./dhall/rofi-dev.dhall).PromptConfig"
, SingleConstructor "TreeConfig" "TreeConfig" "(./dhall/rofi-dev.dhall).TreeConfig"
, SingleConstructor "DeviceConfig" "DeviceConfig" "(./dhall/rofi-dev.dhall).DeviceConfig"
, SingleConstructor "SecretConfig" "SecretConfig" "(./dhall/rofi-dev.dhall).SecretConfig"
, SingleConstructor "MountConfig" "MountConfig" "(./dhall/rofi-dev.dhall).MountConfig"
, SingleConstructor "BitwardenConfig" "BitwardenConfig" "(./dhall/rofi-dev.dhall).BitwardenConfig"
, SingleConstructor "VeracryptData" "VeracryptData" "(./dhall/rofi-dev.dhall).VeracryptData"
, SingleConstructor "CIFSData" "CIFSData" "(./dhall/rofi-dev.dhall).CIFSData"
, SingleConstructor "CIFSOpts" "CIFSOpts" "(./dhall/rofi-dev.dhall).CIFSOpts"
, SingleConstructor "SSHFSData" "SSHFSData" "(./dhall/rofi-dev.dhall).SSHFSData"
]
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
2023-02-13 23:31:50 -05:00
(o, n, []) -> runMounts $ L.foldl (flip id) (defaultOpts (fmap T.pack n)) o
2023-02-13 22:19:49 -05:00
(_, _, errs) -> TI.putStrLn $ T.pack $ concat errs ++ usageInfo h options
2020-05-01 21:29:54 -04:00
where
h = "Usage: rofi-dev [OPTIONS] [-- ROFI-OPTIONS]"
2023-01-24 09:22:19 -05: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 =
2023-01-24 09:22:19 -05:00
[ Option
['c']
["config"]
(ReqArg (\s m -> m {optsConfig = Just s}) "CONF")
"The path to the config file"
, Option
['m']
["mount"]
2023-02-13 23:31:50 -05:00
(ReqArg (\s m -> m {optsAlias = Just $ T.pack s}) "ALIAS")
2023-01-24 09:22:19 -05:00
"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
2023-01-24 09:22:19 -05:00
{ optsConfig :: Maybe FilePath
2023-02-13 23:31:50 -05:00
, optsAlias :: Maybe T.Text
2023-01-24 09:22:19 -05:00
, optsUnmount :: Bool
2023-02-13 23:31:50 -05:00
, optsRofiArgs :: [T.Text]
2023-01-24 09:22:19 -05:00
}
deriving (Show)
2021-03-19 23:23:45 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Main prompt
2021-03-23 21:39:41 -04:00
--
-- 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
2023-02-14 00:37:50 -05:00
let tmpPath = fromMaybe defaultTmpPath $ (fmap T.unpack . scTmpPath) =<< static
let staticDevs = maybe M.empty (M.fromList . fmap (\(TreeMap k v) -> (k, v)) . scDevices) static
let verbose = fromMaybe False $ scVerbose =<< static
2023-01-24 09:22:19 -05:00
let mountconf =
MountConf
{ mountconfVolatilePath = tmpPath
, mountconfRofiArgs = optsRofiArgs opts
, mountconfStaticDevs = staticDevs
, mountconfVerbose = verbose
}
2021-03-23 21:39:41 -04:00
let byAlias = mountByAlias $ optsUnmount opts
let byPrompt = runPrompt =<< getGroups
2023-02-14 22:28:26 -05:00
runRIO mountconf $ maybe byPrompt byAlias $ optsAlias opts
2021-03-23 21:39:41 -04:00
parseStaticConfig :: FilePath -> IO (Maybe StaticConfig)
parseStaticConfig p = do
2023-02-14 23:32:04 -05:00
res <- tryIO $ inputFile auto p
case res of
2023-02-14 23:32:04 -05:00
Left e -> TI.putStrLn (T.pack $ show e) >> return Nothing
Right c -> return $ Just c
2021-03-23 21:39:41 -04:00
2023-02-14 22:28:26 -05:00
runPrompt :: HasRofiConf c => [RofiGroup c] -> RIO c ()
2023-01-24 09:22:19 -05:00
runPrompt gs =
selectAction $
emptyMenu
{ groups = gs
, prompt = Just "Select Device"
}
2021-03-23 21:39:41 -04:00
getGroups :: RofiMountIO [RofiGroup MountConf]
getGroups = do
2021-03-25 00:35:59 -04:00
actions <- sequence [getStaticActions, getRemovableActions, getMTPActions]
2023-01-24 09:22:19 -05:00
return $
(++ [metaActions]) $
2023-02-14 23:09:12 -05:00
fmap mkGroup $
NE.groupAllWith fst $
concat actions
2023-01-24 09:22:19 -05:00
where
metaActions =
titledGroup "Meta Actions" $
toRofiActions [(" Dismount All", dismountAll)]
dismountAll :: RofiMountIO ()
dismountAll = do
umount =<< asks (configToTree' . mountconfStaticDevs)
umount =<< getRemovableDevices
umount =<< getMTPDevices
return ()
where
umount :: Mountable a => [a] -> RofiMountIO ()
umount = mapM_ (`mountMaybe` True)
2021-03-23 21:39:41 -04:00
2023-02-13 23:31:50 -05:00
mountByAlias :: Bool -> T.Text -> RofiMountIO ()
2021-03-23 21:39:41 -04:00
mountByAlias unmountFlag alias = do
static <- asks mountconfStaticDevs
mapM_ (`mountMaybe` unmountFlag) $ configToTree static <$> M.lookup alias static
2023-02-14 23:09:12 -05:00
mkGroup :: NE.NonEmpty (Header, ProtoAction) -> RofiGroup MountConf
2023-02-14 23:32:04 -05:00
mkGroup as = titledGroup h $ toRofiActions $ NE.toList $ alignEntries $ snd <$> as
where
h = (T.pack $ show $ fst $ NE.head as)
2021-03-23 21:39:41 -04:00
2023-02-13 23:31:50 -05:00
alignSep :: T.Text
2021-03-23 21:39:41 -04:00
alignSep = " | "
2023-02-14 23:09:12 -05:00
alignEntries :: NE.NonEmpty (ProtoAction) -> NE.NonEmpty (T.Text, RofiMountIO ())
alignEntries ps = NE.zip (align es) as
2021-03-23 21:39:41 -04:00
where
2023-02-14 23:09:12 -05:00
(es, as) = NE.unzip $ fmap (\(ProtoAction e a) -> (e, a)) ps
2023-01-24 09:22:19 -05:00
align =
2023-02-14 23:09:12 -05:00
fmap (T.intercalate alignSep . NE.toList)
. NE.transpose
. fmap padAll
. NE.transpose
padAll xs = let m = maxNE $ fmap T.length xs in fmap (rpad m ' ') xs
maxNE (x :| []) = x
maxNE (x :| (y : ys)) = maxNE $ (max x y) :| ys
rpad :: Int -> Char -> T.Text -> T.Text
rpad n c s = T.append s $ T.replicate (n - T.length s) $ T.singleton c
2021-03-23 21:39:41 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Global config used in the reader monad stack
2021-03-23 21:39:41 -04:00
data MountConf = MountConf
2021-03-25 00:35:59 -04:00
{ mountconfVolatilePath :: FilePath
2023-02-13 23:31:50 -05:00
, mountconfRofiArgs :: [T.Text]
, mountconfStaticDevs :: M.Map T.Text TreeConfig
2023-01-24 09:22:19 -05:00
, mountconfVerbose :: Bool
}
2023-02-14 00:37:50 -05:00
-- deriving (Show)
2021-03-23 21:39:41 -04:00
2023-02-14 22:28:26 -05:00
instance HasRofiConf MountConf where
2023-01-24 09:22:19 -05:00
defArgs MountConf {mountconfRofiArgs = a} = a
2021-03-23 21:39:41 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Mountable typeclass
--
2021-03-23 21:39:41 -04:00
-- Class to provide common interface for anything that can be mounted.
data MountState = Unmounted | Mounted | Partial deriving (Show, Eq)
mountedState :: MountState -> Bool
mountedState Mounted = True
2023-01-24 09:22:19 -05:00
mountedState _ = False
2021-03-23 21:39:41 -04:00
class Mountable a where
-- | Mount the given type (or dismount if False is passed)
2021-03-25 00:35:59 -04:00
mount :: a -> Bool -> RofiMountIO MountResult
2021-03-23 21:39:41 -04:00
mountMaybe :: a -> Bool -> RofiMountIO ()
mountMaybe dev mountFlag = do
2023-02-14 23:32:04 -05:00
let lab = getLabel dev
2021-03-23 21:39:41 -04:00
mounted <- isMounted dev
verbose <- asks mountconfVerbose
2023-02-14 23:32:04 -05:00
if
| mountFlag == mounted -> do
r <- mount dev mountFlag
io $ notifyMountResult mounted lab r
| verbose ->
io $ notify IconInfo (T.append lab " already mounted") Nothing
| otherwise ->
return ()
2021-03-23 21:39:41 -04:00
-- | Check if the mounting utilities are present
allInstalled :: a -> RofiMountIO Bool
-- | Return a string representing the label of the device
2023-02-13 23:31:50 -05:00
getLabel :: a -> T.Text
2021-03-23 21:39:41 -04:00
-- | Determine if the given type is mounted or not
isMounted :: a -> RofiMountIO Bool
isMounted dev = mountedState <$> mountState dev
mountState :: a -> RofiMountIO MountState
2021-03-23 21:39:41 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Actionable typeclass
2021-03-23 21:39:41 -04:00
--
-- 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
2023-02-14 23:09:12 -05:00
fmtEntry :: a -> NE.NonEmpty T.Text
fmtEntry d = (getLabel d :| [])
2021-03-23 21:39:41 -04:00
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)
2023-02-14 23:09:12 -05:00
mkAction :: a -> RofiMountIO (Header, ProtoAction)
2021-03-23 21:39:41 -04:00
mkAction dev = do
m <- mountState dev
2021-03-23 21:39:41 -04:00
i <- allInstalled dev
let h = groupHeader dev
let action = when i $ mountMaybe dev $ mountedState m
2021-03-23 21:39:41 -04:00
let entry = case fmtEntry dev of
2023-02-14 23:09:12 -05:00
(e :| es) -> (T.append (mountedPrefix m i) e) :| es
2021-03-23 21:39:41 -04:00
return (h, ProtoAction entry action)
where
2023-01-24 09:22:19 -05:00
mountedPrefix _ False = "! "
mountedPrefix Unmounted True = " "
2023-01-24 09:22:19 -05:00
mountedPrefix Mounted True = "* "
mountedPrefix Partial True = "- "
2021-03-23 21:39:41 -04:00
2023-01-24 09:22:19 -05:00
mountableToAction
:: Actionable a
=> RofiMountIO [a]
2023-02-14 23:09:12 -05:00
-> RofiMountIO [(Header, ProtoAction)]
2021-03-25 00:35:59 -04:00
mountableToAction ms = mapM mkAction =<< ms
2023-02-14 22:28:26 -05:00
type RofiMountIO a = RIO MountConf a
2021-03-23 21:39:41 -04:00
2021-03-23 22:39:02 -04:00
-- headers appear in the order listed here (per Enum)
2023-01-24 09:22:19 -05:00
data Header
= CIFSHeader
2021-03-23 22:39:02 -04:00
| SSHFSHeader
| VeracryptHeader
| RemovableHeader
| MTPFSHeader
2023-02-14 23:32:04 -05:00
deriving (Ord, Enum, Eq)
2021-03-23 22:39:02 -04:00
instance Show Header where
show h = case h of
2023-01-24 09:22:19 -05:00
CIFSHeader -> suffix "CIFS"
SSHFSHeader -> suffix "SSHFS"
2021-03-23 22:39:02 -04:00
VeracryptHeader -> suffix "Veracrypt"
RemovableHeader -> suffix "Removable"
2023-01-24 09:22:19 -05:00
MTPFSHeader -> suffix "MTPFS"
2021-03-23 22:39:02 -04:00
where
suffix = (++ " Devices")
2021-03-23 21:39:41 -04:00
2023-02-14 23:09:12 -05:00
data ProtoAction = ProtoAction (NE.NonEmpty T.Text) (RofiMountIO ())
2021-03-25 00:35:59 -04:00
2021-03-18 00:41:04 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Static devices trees
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
2023-01-24 09:22:19 -05:00
mount (Tree p _) True = mount p True
2021-03-23 21:39:41 -04:00
mountState (Tree p _) = mountState p
2021-03-23 21:39:41 -04:00
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
2023-02-14 23:09:12 -05:00
fmtEntry (Tree p@DeviceConfig {deviceData = d} _) = (getLabel p :| [target d])
2021-03-23 21:39:41 -04:00
where
2023-01-24 09:22:19 -05:00
target (CIFSConfig (CIFSData {cifsRemote = r})) = r
target (SSHFSConfig (SSHFSData {sshfsRemote = r})) = r
target (VeracryptConfig (VeracryptData {vcVolume = v})) = v
2021-03-23 21:39:41 -04:00
2023-01-24 09:22:19 -05:00
groupHeader (Tree DeviceConfig {deviceData = d} _) =
2021-03-23 21:39:41 -04:00
case d of
2023-01-24 09:22:19 -05:00
CIFSConfig {} -> CIFSHeader
SSHFSConfig {} -> SSHFSHeader
VeracryptConfig {} -> VeracryptHeader
2021-03-23 21:39:41 -04:00
2023-02-13 23:31:50 -05:00
configToTree' :: M.Map T.Text TreeConfig -> [StaticConfigTree]
2021-03-23 21:39:41 -04:00
configToTree' devMap = configToTree devMap <$> M.elems devMap
2023-02-13 23:31:50 -05:00
configToTree :: M.Map T.Text TreeConfig -> TreeConfig -> StaticConfigTree
2023-01-24 09:22:19 -05:00
configToTree devMap TreeConfig {tcParent = p, tcChildren = c} =
2023-02-14 00:37:50 -05:00
-- TODO wut?
Tree p $ fmap go id c
2021-03-23 21:39:41 -04:00
where
go ds = configToTree devMap <$> mapMaybe (`M.lookup` devMap) ds
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Static devices
2021-03-23 21:39:41 -04:00
--
-- 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
2023-01-24 09:22:19 -05:00
mount DeviceConfig {deviceMount = m, deviceData = devData} False = do
2021-03-23 21:39:41 -04:00
m' <- getAbsMountpoint m
2023-01-24 09:22:19 -05:00
withTmpMountDir m' $
io $
case devData of
SSHFSConfig (SSHFSData {sshfsRemote = r, sshfsPassword = p}) ->
2022-07-31 20:30:27 -04:00
mountSSHFS m' p r
2023-01-24 09:22:19 -05:00
CIFSConfig
( CIFSData
{ cifsRemote = r
, cifsSudo = s
, cifsPassword = p
, cifsOpts = o
}
) ->
mountCIFS s r m' o p
VeracryptConfig
( VeracryptData
{ vcPassword = p
, vcVolume = v
}
) ->
mountVeracrypt m' p v
mount DeviceConfig {deviceMount = m, deviceData = d} True = do
2021-03-23 21:39:41 -04:00
m' <- getAbsMountpoint m
2021-03-25 00:35:59 -04:00
runAndRemoveDir m' $ io $ case d of
2023-02-13 23:31:50 -05:00
CIFSConfig (CIFSData {cifsSudo = s}) -> runMountSudoMaybe s "umount" [T.pack m']
VeracryptConfig _ -> runVeraCrypt ["-d", T.pack m'] ""
_ -> runMount "umount" [T.pack m'] ""
2023-01-24 09:22:19 -05:00
allInstalled DeviceConfig {deviceData = devData} =
io $
isJust
<$> findExecutable (exe devData)
2021-03-23 21:39:41 -04:00
where
2023-01-24 09:22:19 -05:00
exe SSHFSConfig {} = "sshfs"
exe CIFSConfig {} = "mount.cifs"
exe VeracryptConfig {} = "veracrypt"
2021-03-23 21:39:41 -04:00
2023-01-24 09:22:19 -05:00
mountState DeviceConfig {deviceMount = m, deviceData = d} = do
-- mountState DeviceConfig{ deviceMount = m } = do
case d of
2023-01-24 09:22:19 -05:00
VeracryptConfig {} -> veracryptMountState m
_ -> do
b <- (io . isDirMounted) =<< getAbsMountpoint m
return $ if b then Mounted else Unmounted
2021-03-23 21:39:41 -04:00
2023-01-24 09:22:19 -05:00
getLabel
DeviceConfig
{ deviceMount = MountConfig {mpPath = p, mpLabel = l}
2023-02-14 00:37:50 -05:00
} = fromMaybe (T.pack $ takeFileName $ T.unpack p) l
2021-03-23 21:39:41 -04:00
2023-02-13 23:31:50 -05:00
mountSSHFS :: FilePath -> Maybe PasswordConfig -> T.Text -> IO MountResult
mountSSHFS mountpoint pwdConfig remote =
withPasswordGetter pwdConfig (run ["-o", "password_stdin"]) $ run [] ""
where
2023-02-13 23:31:50 -05:00
run other = runMount "sshfs" (other ++ [remote, T.pack mountpoint])
2021-03-25 00:35:59 -04:00
2023-01-24 09:22:19 -05:00
mountCIFS
:: Bool
2023-02-13 23:31:50 -05:00
-> T.Text
2023-01-24 09:22:19 -05:00
-> FilePath
-> Maybe CIFSOpts
-> Maybe PasswordConfig
-> IO MountResult
2021-03-26 00:17:13 -04:00
mountCIFS useSudo remote mountpoint opts pwdConfig =
withPasswordGetter pwdConfig runPwd run
where
run = runMountSudoMaybe useSudo "mount.cifs" args
runPwd p = runMountSudoMaybe' useSudo "mount.cifs" args [("PASSWD", p)]
2023-02-13 23:31:50 -05:00
args = [remote, T.pack mountpoint] ++ maybe [] (\o -> ["-o", fromCIFSOpts o]) opts
2021-03-26 00:17:13 -04:00
2023-02-13 23:31:50 -05:00
fromCIFSOpts :: CIFSOpts -> T.Text
fromCIFSOpts o = T.intercalate "," $ mapMaybe concatMaybe fs
2021-03-25 00:35:59 -04:00
where
2023-01-24 09:22:19 -05:00
fs =
[ ("username", cifsoptsUsername)
, ("workgroup", cifsoptsWorkgroup)
2023-02-13 23:31:50 -05:00
, ("uid", fmap (T.pack . show) . cifsoptsUID)
, ("gid", fmap (T.pack . show) . cifsoptsGID)
2023-01-24 09:22:19 -05:00
, ("iocharset", cifsoptsIocharset)
]
2023-02-13 23:31:50 -05:00
concatMaybe (k, f) = (\v -> T.concat [k, "=", v]) <$> f o
2021-03-25 00:35:59 -04:00
2023-02-13 23:31:50 -05:00
mountVeracrypt :: FilePath -> Maybe PasswordConfig -> T.Text -> IO MountResult
mountVeracrypt mountpoint pwdConfig volume =
2023-01-24 09:22:19 -05:00
withPasswordGetter pwdConfig (runVeraCrypt (args ++ ["--stdin"])) $
runVeraCrypt args ""
2021-03-25 00:35:59 -04:00
where
2023-02-13 23:31:50 -05:00
args = [volume, T.pack mountpoint]
2021-03-23 21:39:41 -04:00
-- NOTE: the user is assumed to have added themselves to the sudoers file so
-- that this command will work
2023-02-13 23:31:50 -05:00
runVeraCrypt :: [T.Text] -> T.Text -> IO MountResult
2021-03-25 00:35:59 -04:00
runVeraCrypt args = runMount "sudo" (defaultArgs ++ args)
2021-03-23 21:39:41 -04:00
where
defaultArgs = ["/usr/bin/veracrypt", "--text", "--non-interactive"]
2020-05-01 21:29:54 -04:00
veracryptMountState :: MountConfig -> RofiMountIO MountState
veracryptMountState mc = do
mp <- getAbsMountpoint mc
primary <- io $ lookupSpec mp
aux <- io $ fmap join $ mapM lookupSpec $ auxPath =<< primary
return $ case (primary, aux) of
2023-01-24 09:22:19 -05:00
(Just _, Just _) -> Mounted
(Nothing, Nothing) -> Unmounted
2023-01-24 09:22:19 -05:00
_ -> Partial
where
-- TODO don't hardcode the tmp directory
auxPath = fmap (\i -> "/tmp/.veracrypt_aux_mnt" ++ [i]) . vcIndex
2023-02-13 23:31:50 -05:00
vcIndex spec = case T.uncons $ T.reverse spec of
-- TODO what if I have more than one digit?
2023-02-13 23:31:50 -05:00
Just (i, _) -> if i `elem` ['0' .. '9'] then Just i else Nothing
2023-01-24 09:22:19 -05:00
_ -> Nothing
2021-03-25 00:35:59 -04:00
getAbsMountpoint :: MountConfig -> RofiMountIO FilePath
2023-01-24 09:22:19 -05:00
getAbsMountpoint MountConfig {mpPath = m} =
2023-02-14 00:37:50 -05:00
asks $ flip appendRoot (T.unpack m) . mountconfVolatilePath
2021-03-25 00:35:59 -04:00
2023-02-14 23:09:12 -05:00
getStaticActions :: RofiMountIO [(Header, ProtoAction)]
getStaticActions = mountableToAction $ asks $ configToTree' . mountconfStaticDevs
2021-03-25 00:35:59 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Password-getting functions for static devices
2023-02-13 23:31:50 -05:00
type PasswordGetter = IO (Maybe T.Text)
2020-05-01 21:29:54 -04:00
2023-02-13 23:31:50 -05:00
runSecret :: M.Map T.Text T.Text -> PasswordGetter
2023-01-24 09:22:19 -05:00
runSecret kvs = readCmdSuccess "secret-tool" ("lookup" : kvs') ""
2020-05-01 21:29:54 -04:00
where
kvs' = concatMap (\(k, v) -> [k, v]) $ M.toList kvs
2020-05-01 21:29:54 -04:00
2023-02-13 23:31:50 -05:00
runBitwarden :: T.Text -> PasswordGetter
2023-01-24 09:22:19 -05:00
runBitwarden pname =
2023-02-13 22:19:49 -05:00
((password . login) <=< L.find (\i -> name i == pname))
2023-01-24 09:22:19 -05:00
<$> getItems
2023-02-14 00:37:50 -05:00
runPromptLoop :: Natural -> PasswordGetter -> PasswordGetter
2021-03-18 00:41:04 -04:00
runPromptLoop n pwd = do
res <- pwd
2023-01-24 09:22:19 -05:00
if isNothing res
then if n <= 0 then return Nothing else runPromptLoop (n - 1) pwd
2021-03-18 00:41:04 -04:00
else return res
-- configToPwd :: PasswordConfig -> PasswordGetter
-- configToPwd PasswordConfig
-- { passwordBitwarden = b
-- , passwordLibSecret = s
-- , passwordPrompt = p
-- } =
-- getBW b `runMaybe` getLS s `runMaybe` getPrompt p
-- where
-- getBW (Just BitwardenConfig{ bwKey = k, bwTries = n }) =
-- runPromptLoop n $ runBitwarden k
-- getBW _ = return Nothing
-- getLS = maybe (return Nothing) (runSecret . secretAttributes)
-- getPrompt = maybe (return Nothing) (flip runPromptLoop readPassword . promptTries)
-- runMaybe x y = (\r -> if isNothing r then y else return r) =<< x
2021-03-18 00:41:04 -04:00
configToPwd :: PasswordConfig -> PasswordGetter
2023-01-24 09:22:19 -05:00
configToPwd (PwdBW (BitwardenConfig {bwKey = k, bwTries = n})) =
runPromptLoop n $ runBitwarden k
2023-02-14 00:37:50 -05:00
configToPwd (PwdLS s) = runSecret $ M.fromList $ fmap (\(SecretMap k v) -> (k, v)) $ secretAttributes s
configToPwd (PwdPr p) = flip runPromptLoop readPassword $ promptTries p
2023-01-24 09:22:19 -05:00
withPasswordGetter
:: Maybe PasswordConfig
2023-02-13 23:31:50 -05:00
-> (T.Text -> IO MountResult)
2023-01-24 09:22:19 -05:00
-> IO MountResult
-> IO MountResult
2021-03-25 00:35:59 -04:00
withPasswordGetter (Just pwdConfig) runPwd _ =
maybe (return $ MountError "Password could not be obtained") runPwd
2023-01-24 09:22:19 -05:00
=<< configToPwd pwdConfig
2021-03-25 00:35:59 -04:00
withPasswordGetter Nothing _ run = run
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Removable devices
2020-04-23 23:32:29 -04:00
--
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
2023-02-13 23:31:50 -05:00
{ removablePath :: T.Text
, removableLabel :: T.Text
2023-01-24 09:22:19 -05:00
}
deriving (Eq, Show)
2020-04-23 23:32:29 -04:00
instance Mountable Removable where
2023-01-24 09:22:19 -05:00
mount Removable {removablePath = d} m =
2021-03-25 00:35:59 -04:00
io $ runMount "udisksctl" [c, "-b", d] ""
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
2023-01-24 09:22:19 -05:00
mountState Removable {removablePath = d} = do
s <- elem d <$> io curDeviceSpecs
return $ if s then Mounted else Unmounted
2020-04-23 23:32:29 -04:00
2023-01-24 09:22:19 -05:00
getLabel Removable {removableLabel = l} = l
2021-03-22 19:20:32 -04:00
instance Actionable Removable where
2023-02-14 23:09:12 -05: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
2023-02-14 22:28:26 -05:00
getRemovableDevices :: RIO c [Removable]
2023-01-24 09:22:19 -05:00
getRemovableDevices =
2023-02-13 23:31:50 -05:00
fromLines toDev . T.lines . T.pack
2023-01-24 09:22:19 -05: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
2023-02-13 23:31:50 -05:00
toDev line = case T.split (== ' ') line of
2023-01-24 09:22:19 -05:00
("" : _) -> Nothing
2023-02-13 23:31:50 -05:00
[_, "1", d, "", s] -> mk d $ T.append s " Volume"
2023-01-24 09:22:19 -05:00
[_, "1", d, l, _] -> mk d l
_ -> Nothing
mk d l = Just $ Removable {removablePath = d, removableLabel = l}
2020-04-23 23:32:29 -04:00
2023-02-14 23:09:12 -05:00
getRemovableActions :: RofiMountIO [(Header, ProtoAction)]
2021-03-25 00:35:59 -04:00
getRemovableActions = mountableToAction getRemovableDevices
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- MTP devices
2020-04-23 23:32:29 -04:00
2023-02-13 23:31:50 -05:00
mtpExe :: FilePath
mtpExe = "jmtpfs"
2020-04-23 23:32:29 -04:00
data MTPFS = MTPFS
2023-02-13 23:31:50 -05:00
{ mtpfsBus :: T.Text
, mtpfsDevice :: T.Text
2023-01-24 09:22:19 -05:00
, mtpfsMountpoint :: FilePath
2023-02-13 23:31:50 -05:00
, mtpfsDescription :: T.Text
2023-01-24 09:22:19 -05:00
}
deriving (Eq, Show)
2020-04-23 23:32:29 -04:00
instance Mountable MTPFS where
2023-01-24 09:22:19 -05:00
mount MTPFS {mtpfsBus = b, mtpfsDevice = n, mtpfsMountpoint = m} False = do
2020-04-23 23:32:29 -04:00
-- TODO add autodismount to options
2023-02-13 23:31:50 -05:00
let dev = T.concat ["-device=", b, ",", n]
withTmpMountDir m $ io $ runMount (T.pack mtpExe) [dev, T.pack m] ""
2023-01-24 09:22:19 -05:00
mount MTPFS {mtpfsMountpoint = m} True =
2023-02-13 23:31:50 -05:00
runAndRemoveDir m $ io $ runMount "umount" [T.pack m] ""
2020-04-23 23:32:29 -04:00
2023-01-24 09:22:19 -05:00
-- \| return True always since the list won't even show without jmtpfs
2020-05-01 21:29:54 -04:00
allInstalled _ = return True
2020-04-23 23:32:29 -04:00
2023-01-24 09:22:19 -05:00
mountState MTPFS {mtpfsMountpoint = m} = do
s <- io $ isDirMounted m
return $ if s then Mounted else Unmounted
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
i <- io mtpExeInstalled
if i then go else return []
2020-04-23 23:32:29 -04:00
where
go = do
dir <- asks mountconfVolatilePath
res <- io $ readProcess mtpExe ["-l"] ""
2023-02-13 23:31:50 -05:00
return $ fromLines (toDev dir) $ toDevList $ T.pack res
2023-01-24 09:22:19 -05:00
toDevList =
reverse
2023-02-13 23:31:50 -05:00
. L.takeWhile (not . T.isPrefixOf "Available devices")
. L.reverse
. T.lines
toDev dir s = case L.filter (== " ") $ T.split (== ',') s of
2023-01-24 09:22:19 -05:00
[busNum, devNum, _, _, desc, vendor] ->
2023-02-13 23:31:50 -05:00
let d = T.unwords [vendor, desc]
2023-01-24 09:22:19 -05:00
in Just $
MTPFS
{ mtpfsBus = busNum
, mtpfsDevice = devNum
2023-02-13 23:31:50 -05:00
, mtpfsMountpoint = dir </> canonicalize (T.unpack d)
2023-01-24 09:22:19 -05:00
, mtpfsDescription = d
}
2020-04-23 23:32:29 -04:00
_ -> Nothing
canonicalize = mapMaybe repl
repl c
2023-02-13 23:31:50 -05:00
| c `elem` ("\"*/:<>?\\|" :: [Char]) = Nothing
2020-04-23 23:32:29 -04:00
| c == ' ' = Just '-'
| otherwise = Just c
2023-02-14 23:09:12 -05:00
getMTPActions :: RofiMountIO [(Header, ProtoAction)]
2021-03-25 00:35:59 -04:00
getMTPActions = mountableToAction getMTPDevices
mtpExeInstalled :: IO Bool
mtpExeInstalled = isJust <$> findExecutable mtpExe
2021-03-23 21:39:41 -04:00
instance Actionable MTPFS where
2023-02-14 23:09:12 -05:00
fmtEntry d = (getLabel d :| [])
2021-03-22 19:20:32 -04:00
2021-03-23 22:39:02 -04:00
groupHeader _ = MTPFSHeader
2021-03-25 00:35:59 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Notifications
2021-03-25 00:35:59 -04:00
data NotifyIcon = IconError | IconInfo
instance Show NotifyIcon where
show IconError = "dialog-error-symbolic"
2023-01-24 09:22:19 -05:00
show IconInfo = "dialog-information-symbolic"
2021-03-25 00:35:59 -04:00
2023-02-13 23:31:50 -05:00
notifyMountResult :: Bool -> T.Text -> MountResult -> IO ()
2021-03-25 00:35:59 -04:00
notifyMountResult mounted label result = case result of
2023-02-13 23:31:50 -05:00
MountError e -> notify IconError (T.unwords ["Failed", "to", verb, label]) $ Just e
MountSuccess -> notify IconInfo (T.concat ["Successfully ", verb, "ed ", label]) Nothing
2021-03-25 00:35:59 -04:00
where
2023-02-13 23:31:50 -05:00
verb = if mounted then "unmount" else "mount" :: T.Text
2021-03-25 00:35:59 -04:00
2023-02-13 23:31:50 -05:00
notify :: NotifyIcon -> T.Text -> Maybe T.Text -> IO ()
2023-01-24 09:22:19 -05:00
notify icon summary body =
void $
spawnProcess "notify-send" $
2023-02-13 23:31:50 -05:00
maybe args (\b -> args ++ [b]) $
fmap T.unpack body
2021-03-25 00:35:59 -04:00
where
2023-02-13 23:31:50 -05:00
args = ["-i", show icon, T.unpack summary]
2021-03-25 00:35:59 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Mount commands
2021-03-25 00:35:59 -04:00
2023-02-13 23:31:50 -05:00
data MountResult = MountSuccess | MountError T.Text deriving (Show, Eq)
2021-03-25 00:35:59 -04:00
2023-02-13 23:31:50 -05:00
runMount :: T.Text -> [T.Text] -> T.Text -> IO MountResult
2023-02-13 22:19:49 -05:00
runMount cmd args stdin_ = eitherToMountResult <$> readCmdEither cmd args stdin_
2021-03-25 00:35:59 -04:00
2023-02-13 23:31:50 -05:00
runMount' :: T.Text -> [T.Text] -> T.Text -> [(T.Text, T.Text)] -> IO MountResult
2023-02-13 22:19:49 -05:00
runMount' cmd args stdin_ environ =
2023-01-24 09:22:19 -05:00
eitherToMountResult
2023-02-13 22:19:49 -05:00
<$> readCmdEither' cmd args stdin_ environ
2021-03-25 00:35:59 -04:00
2023-02-13 23:31:50 -05:00
runMountSudoMaybe :: Bool -> T.Text -> [T.Text] -> IO MountResult
2021-03-25 23:16:55 -04:00
runMountSudoMaybe useSudo cmd args =
runMountSudoMaybe' useSudo cmd args []
2023-02-13 23:31:50 -05:00
runMountSudoMaybe' :: Bool -> T.Text -> [T.Text] -> [(T.Text, T.Text)] -> IO MountResult
2023-01-24 09:22:19 -05:00
runMountSudoMaybe' useSudo cmd args environ =
maybe
(runMount' cmd args "" environ)
(\r -> runSudoMount' r cmd args environ)
=<< if useSudo then readPassword' "Sudo Password" else return Nothing
2021-03-25 23:16:55 -04:00
-- TODO untested
2023-02-13 23:31:50 -05:00
-- runSudoMount :: T.Text -> T.Text -> [T.Text] -> T.Text -> IO MountResult
2021-03-25 23:16:55 -04:00
-- runSudoMount rootpass cmd args stdin = runSudoMount' rootpass cmd args stdin []
2023-02-13 23:31:50 -05:00
runSudoMount' :: T.Text -> T.Text -> [T.Text] -> [(T.Text, T.Text)] -> IO MountResult
2021-03-25 23:16:55 -04:00
runSudoMount' rootpass cmd args environ = runMount "sudo" args' rootpass
where
args' = ["-S"] ++ environ' ++ [cmd] ++ args
2023-02-13 23:31:50 -05:00
environ' = fmap (\(k, v) -> T.concat [k, "=", v]) environ
2021-03-25 23:16:55 -04:00
2023-02-13 23:31:50 -05:00
eitherToMountResult :: Either (Int, T.Text, T.Text) T.Text -> MountResult
2023-01-24 09:22:19 -05:00
eitherToMountResult (Right _) = MountSuccess
eitherToMountResult (Left (_, _, e)) = MountError e
2021-03-25 00:35:59 -04:00
2020-04-23 23:32:29 -04:00
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Low-level mount functions
2020-04-23 23:32:29 -04:00
2023-02-13 23:31:50 -05:00
mountMap :: IO (M.Map FilePath T.Text)
mountMap = do
2023-02-13 22:19:49 -05:00
parseFile <$> readFileUtf8 "/proc/mounts"
where
2023-02-13 22:19:49 -05:00
parseFile = M.fromList . mapMaybe (parseLine . T.words) . T.lines
-- none of these should fail since this file format will never change
2023-02-13 23:31:50 -05:00
parseLine [spec, mountpoint, _, _, _, _] = Just (T.unpack mountpoint, spec)
2023-01-24 09:22:19 -05:00
parseLine _ = Nothing
2020-05-01 21:29:54 -04:00
2023-02-13 23:31:50 -05:00
curDeviceSpecs :: IO [T.Text]
curDeviceSpecs = M.elems <$> mountMap
2020-05-01 21:29:54 -04:00
2023-02-13 23:31:50 -05:00
curMountpoints :: IO [FilePath]
curMountpoints = M.keys <$> mountMap
2023-02-13 23:31:50 -05:00
lookupSpec :: FilePath -> IO (Maybe T.Text)
lookupSpec mountpoint = M.lookup mountpoint <$> mountMap
2020-05-01 21:29:54 -04:00
-- 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-25 00:35:59 -04:00
rmDirOnMountError :: FilePath -> RofiMountIO MountResult -> RofiMountIO MountResult
rmDirOnMountError d f = do
res <- f
unless (res == MountSuccess) $ rmDirMaybe d
return res
2021-03-25 23:16:55 -04:00
-- | Run a mount command and create the mountpoint if it does not exist, and
-- remove the mountpoint if a mount error occurs
2021-03-25 00:35:59 -04:00
withTmpMountDir :: FilePath -> RofiMountIO MountResult -> RofiMountIO MountResult
2023-01-24 09:22:19 -05:00
withTmpMountDir m =
rmDirOnMountError m
. bracketOnError_ (mkDirMaybe m) (rmDirMaybe m)
2021-03-25 00:35:59 -04:00
2021-03-25 23:16:55 -04:00
-- | Run an unmount command and remove the mountpoint if no errors occur
2021-03-25 00:35:59 -04:00
runAndRemoveDir :: FilePath -> RofiMountIO MountResult -> RofiMountIO MountResult
2021-03-25 23:16:55 -04:00
runAndRemoveDir m f = do
2023-02-13 23:31:50 -05:00
res <- catch f (return . MountError . (T.pack . displayException :: SomeException -> T.Text))
2021-03-25 23:16:55 -04:00
when (res == MountSuccess) $ rmDirMaybe m
return res
2021-03-25 00:35:59 -04:00
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 ()
2023-01-24 09:22:19 -05:00
rmDirMaybe fp =
whenInMountDir fp $
unlessMountpoint fp $
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-25 00:35:59 -04:00
whenInMountDir :: FilePath -> RofiMountIO () -> RofiMountIO ()
2020-05-01 21:29:54 -04:00
whenInMountDir fp f = do
2021-03-19 23:23:45 -04:00
mDir <- asks mountconfVolatilePath
2023-02-13 22:19:49 -05:00
when (mDir `L.isPrefixOf` fp) f
2020-05-01 21:29:54 -04:00
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
--------------------------------------------------------------------------------
2023-01-24 09:22:19 -05:00
-- Other functions
2020-04-23 23:32:29 -04:00
2023-02-13 23:31:50 -05:00
fromLines :: (T.Text -> Maybe a) -> [T.Text] -> [a]
fromLines f = mapMaybe (f . stripWS)
2020-04-23 23:32:29 -04:00
-- TODO this exists somewhere...
2023-02-13 23:31:50 -05:00
-- splitBy :: Char -> T.Text -> [T.Text]
-- splitBy delimiter = T.foldr f [[]]
-- where
-- f _ [] = []
-- f c l@(x : xs)
-- | c == delimiter = [] : l
-- | otherwise = (c : x) : xs
2020-04-23 23:32:29 -04:00
2021-03-18 00:41:04 -04:00
appendRoot :: FilePath -> FilePath -> FilePath
appendRoot root path = if isRelative path then root </> path else path