ENH use rio process for vbox command

This commit is contained in:
Nathan Dwarshuis 2022-12-27 00:14:58 -05:00
parent 7e8cc295f6
commit af5877a402
2 changed files with 34 additions and 32 deletions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -17,63 +18,63 @@
module Main (main) where module Main (main) where
import Control.Exception import qualified Data.ByteString.Lazy.UTF8 as BU
import Data.List
import RIO
import RIO.Process
import qualified RIO.Text as T import qualified RIO.Text as T
import Text.Read
import Text.XML.Light import Text.XML.Light
import System.Environment import System.Environment
import System.Exit
import XMonad.Internal.Concurrent.VirtualBox import XMonad.Internal.Concurrent.VirtualBox
import XMonad.Internal.Process import XMonad.Internal.Process (waitUntilExit)
main :: IO () main :: IO ()
main = runAndWait =<< getArgs main = do
args <- getArgs
runSimpleApp $
runAndWait args
runAndWait :: [String] -> IO () runAndWait :: [String] -> RIO SimpleApp ()
runAndWait [n] = either (putStrLn . T.unpack) runConfig =<< vmInstanceConfig (T.pack n) runAndWait [n] = do
c <- liftIO $ vmInstanceConfig (T.pack n)
either (logError . displayBytesUtf8 . encodeUtf8) runConfig c
where where
runConfig c = maybe err runID =<< vmMachineID c runConfig c = maybe err runID =<< vmMachineID c
runID i = do runID i = do
vmLaunch i vmLaunch i
p <- vmPID i p <- vmPID i
waitUntilExit p liftIO $ waitUntilExit p
err = putStrLn "Could not get machine ID" err = logError "Could not get machine ID"
runAndWait _ = putStrLn "Usage: vbox-start VBOXNAME" runAndWait _ = liftIO $ putStrLn "Usage: vbox-start VBOXNAME"
vmLaunch :: String -> IO () vmLaunch :: T.Text -> RIO SimpleApp ()
vmLaunch i = do vmLaunch i = do
(rc, _, _) <- readCreateProcessWithExitCode' cmd "" rc <- proc "VBoxManage" ["startvm", T.unpack i] runProcess
case rc of case rc of
ExitSuccess -> return () ExitSuccess -> return ()
_ -> putStrLn $ "Failed to start VM: " ++ i _ -> logError $ "Failed to start VM: "
where <> displayBytesUtf8 (encodeUtf8 i)
cmd = proc "VBoxManage" ["startvm", i]
vmPID :: String -> IO (Maybe Int) vmPID :: T.Text -> RIO SimpleApp (Maybe Int)
vmPID vid = do vmPID vid = do
(rc, out, _) <- readCreateProcessWithExitCode' cmd "" (rc, out) <- proc "pgrep" ["-f", "VirtualBoxVM.*" ++ T.unpack vid] readProcessStdout
return $ case rc of return $ case rc of
ExitSuccess -> readMaybe $ T.unpack out ExitSuccess -> readMaybe $ BU.toString out
_ -> Nothing _ -> Nothing
where
cmd = proc "pgrep" ["-f", "VirtualBoxVM.*" ++ vid]
vmMachineID :: FilePath -> IO (Maybe String) vmMachineID :: FilePath -> RIO SimpleApp (Maybe T.Text)
vmMachineID iPath = do vmMachineID iPath = do
(s :: Either IOException String) <- try $ readFile iPath res <- tryAny $ readFileUtf8 iPath
return $ case s of case res of
(Left _) -> Nothing Right contents -> return $ findMachineID contents
(Right x) -> findMachineID =<< parseXMLDoc x Left e -> logError (displayShow e) >> return Nothing
where where
findMachineID e = stripPrefix "{" findMachineID c = T.stripSuffix "}"
=<< (fmap reverse . stripPrefix "}" . reverse) =<< T.stripPrefix "{"
=<< findAttr (blank_name { qName = "uuid" }) =<< (fmap T.pack . findAttr (blank_name { qName = "uuid" }))
=<< findChild (qual e "Machine") e =<< (\e -> findChild (qual e "Machine") e)
=<< parseXMLDoc c

View File

@ -40,6 +40,7 @@ dependencies:
- hashable >= 1.3.5.0 - hashable >= 1.3.5.0
- xml >= 1.3.14 - xml >= 1.3.14
- lifted-base >= 0.2.3.12 - lifted-base >= 0.2.3.12
- utf8-string >= 1.0.2
library: library:
source-dirs: lib/ source-dirs: lib/