module HSH.Helpers.Utils where import HSH import Text.StringTemplate.Helpers import Control.Monad.Error import System.IO.Error failIf ioP m = do p <- ioP if p then fail m else return () -- Executes an IO action with a modified environment, where the $PATH variable has the given paths prepended -- Useful, for example, for getting commands to work from the cron command, -- where $PATH may vary from the $PATH you have at user login, with unpredictable results -- withPath :: [FilePath] -> IO a -> IO a inPath :: FilePath -> ErrorT String IO () inPath p = do ErrorT $ do res <- tryS $ runIO $ render1 [("p",p)] $ "which $p$" case res of Left _ -> return . Left $ render1 [("p",p)] "$p$ is not in \\$PATH, maybe you need to modify your shell environment" Right _ -> return . Right $ () tryS :: IO a -> IO (Either String a) tryS ma = do etRes <- try ma return $ case etRes of Left e -> Left $ show e Right r -> Right r {- | Like tryEC in HSH, but doesn't attempt to parse error message, so all errors result in Left result type and nothing gets re-raised via ioError -} {- tryECPromiscuous :: IO a -> IO (Either ProcessStatus a) tryECPromiscuous action = do r <- try action case r of Left ioe -> if isUserError ioe then case (ioeGetErrorString ioe =~~ pat) of Nothing -> ioError ioe -- not ours; re-raise it Just e -> return . Left . proc $ e else ioError ioe -- not ours; re-raise it Right result -> return (Right result) where pat = ": exited with code [0-9]+$|: terminated by signal ([0-9]+)$|: stopped by signal [0-9]+" proc :: String -> ProcessStatus proc e | e =~ "^: exited" = Exited (ExitFailure (str2ec e)) | e =~ "^: terminated by signal" = Terminated (str2ec e) | e =~ "^: stopped by signal" = Stopped (str2ec e) | otherwise = error "Internal error in tryEC" str2ec e = read (e =~ "[0-9]+$") -} -- | like HSH.runSL, but returns all output, not just the first line. runS :: String -> IO String runS = run -- | like runS, but returns as list of lines runStrings :: String -> IO [String] runStrings = ( return . lines =<< ) . run