1{-# LANGUAGE CPP #-}
2{-# LANGUAGE NoImplicitPrelude #-}
3{-# LANGUAGE ScopedTypeVariables #-}
4{-# LANGUAGE DeriveDataTypeable #-}
5{-# LANGUAGE FlexibleContexts #-}
6{-# LANGUAGE RankNTypes #-}
7{-# LANGUAGE OverloadedStrings #-}
8
9-- | Interacting with external processes.
10--
11-- This module provides a layer on top of "System.Process.Typed", with
12-- the following additions:
13--
14-- * For efficiency, it will cache @PATH@ lookups.
15--
16-- * For convenience, you can set the working directory and env vars
17--   overrides in a 'RIO' environment instead of on the individual
18--   calls to the process.
19--
20-- * Built-in support for logging at the debug level.
21--
22-- In order to switch over to this API, the main idea is:
23--
24-- * Like most of the rio library, you need to create an environment
25--   value (this time 'ProcessContext'), and include it in your 'RIO'
26--   environment. See 'mkProcessContext'.
27--
28-- * Instead of using the 'System.Process.Typed.proc' function from
29--   "System.Process.Typed" for creating a 'ProcessConfig', use the
30--   locally defined 'proc' function, which will handle overriding
31--   environment variables, looking up paths, performing logging, etc.
32--
33-- Once you have your 'ProcessConfig', use the standard functions from
34-- 'System.Process.Typed' (reexported here for convenient) for running
35-- the 'ProcessConfig'.
36--
37-- @since 0.0.3.0
38module RIO.Process
39  ( -- * Process context
40    ProcessContext
41  , HasProcessContext (..)
42  , EnvVars
43  , mkProcessContext
44  , mkDefaultProcessContext
45  , modifyEnvVars
46  , withModifyEnvVars
47  , lookupEnvFromContext
48  , withWorkingDir
49    -- ** Lenses
50  , workingDirL
51  , envVarsL
52  , envVarsStringsL
53  , exeSearchPathL
54    -- ** Actions
55  , resetExeCache
56    -- * Configuring
57  , proc
58    -- * Spawning (run child process)
59  , withProcess
60  , withProcess_
61  , withProcessWait
62  , withProcessWait_
63  , withProcessTerm
64  , withProcessTerm_
65    -- * Exec (replacing current process)
66  , exec
67  , execSpawn
68    -- * Environment helper
69  , LoggedProcessContext (..)
70  , withProcessContextNoLogging
71    -- * Exceptions
72  , ProcessException (..)
73    -- * Utilities
74  , doesExecutableExist
75  , findExecutable
76  , exeExtensions
77  , augmentPath
78  , augmentPathMap
79  , showProcessArgDebug
80    -- * Reexports
81  , P.ProcessConfig
82  , P.StreamSpec
83  , P.StreamType (..)
84  , P.Process
85  , P.setStdin
86  , P.setStdout
87  , P.setStderr
88  , P.setCloseFds
89  , P.setCreateGroup
90  , P.setDelegateCtlc
91#if MIN_VERSION_process(1, 3, 0)
92  , P.setDetachConsole
93  , P.setCreateNewConsole
94  , P.setNewSession
95#endif
96#if MIN_VERSION_process(1, 4, 0) && !WINDOWS
97  , P.setChildGroup
98  , P.setChildUser
99#endif
100  , P.mkStreamSpec
101  , P.inherit
102  , P.closed
103  , P.byteStringInput
104  , P.byteStringOutput
105  , P.createPipe
106  , P.useHandleOpen
107  , P.useHandleClose
108  , P.startProcess
109  , P.stopProcess
110  , P.readProcess
111  , P.readProcess_
112  , P.runProcess
113  , P.runProcess_
114  , P.readProcessStdout
115  , P.readProcessStdout_
116  , P.readProcessStderr
117  , P.readProcessStderr_
118  , P.waitExitCode
119  , P.waitExitCodeSTM
120  , P.getExitCode
121  , P.getExitCodeSTM
122  , P.checkExitCode
123  , P.checkExitCodeSTM
124  , P.getStdin
125  , P.getStdout
126  , P.getStderr
127  , P.ExitCodeException (..)
128  , P.ByteStringOutputException (..)
129  , P.unsafeProcessHandle
130  ) where
131
132import           RIO.Prelude.Display
133import           RIO.Prelude.Reexports
134import           RIO.Prelude.Logger
135import           RIO.Prelude.RIO
136import           RIO.Prelude.Lens
137import qualified Data.Map as Map
138import qualified Data.Text as T
139import qualified System.Directory as D
140import           System.Environment (getEnvironment)
141import           System.Exit (exitWith)
142import qualified System.FilePath as FP
143import qualified System.Process.Typed as P
144import           System.Process.Typed hiding
145                    (withProcess, withProcess_,
146                     withProcessWait, withProcessWait_,
147                     withProcessTerm, withProcessTerm_,
148                     proc)
149
150#ifndef WINDOWS
151import           System.Directory (setCurrentDirectory)
152import           System.Posix.Process (executeFile)
153#endif
154
155-- | The environment variable map
156--
157-- @since 0.0.3.0
158type EnvVars = Map Text Text
159
160-- | Context in which to run processes.
161--
162-- @since 0.0.3.0
163data ProcessContext = ProcessContext
164    { pcTextMap :: !EnvVars
165    -- ^ Environment variables as map
166
167    , pcStringList :: ![(String, String)]
168    -- ^ Environment variables as association list
169
170    , pcPath :: ![FilePath]
171    -- ^ List of directories searched for executables (@PATH@)
172
173    , pcExeCache :: !(IORef (Map FilePath (Either ProcessException FilePath)))
174    -- ^ Cache of already looked up executable paths.
175
176    , pcExeExtensions :: [String]
177    -- ^ @[""]@ on non-Windows systems, @["", ".exe", ".bat"]@ on Windows
178
179    , pcWorkingDir :: !(Maybe FilePath)
180    -- ^ Override the working directory.
181    }
182
183-- | Exception type which may be generated in this module.
184--
185-- /NOTE/ Other exceptions may be thrown by underlying libraries!
186--
187-- @since 0.0.3.0
188data ProcessException
189    = NoPathFound
190    | ExecutableNotFound String [FilePath]
191    | ExecutableNotFoundAt FilePath
192    | PathsInvalidInPath [FilePath]
193    deriving Typeable
194instance Show ProcessException where
195    show NoPathFound = "PATH not found in ProcessContext"
196    show (ExecutableNotFound name path) = concat
197        [ "Executable named "
198        , name
199        , " not found on path: "
200        , show path
201        ]
202    show (ExecutableNotFoundAt name) =
203        "Did not find executable at specified path: " ++ name
204    show (PathsInvalidInPath paths) = unlines $
205        [ "Would need to add some paths to the PATH environment variable \
206          \to continue, but they would be invalid because they contain a "
207          ++ show FP.searchPathSeparator ++ "."
208        , "Please fix the following paths and try again:"
209        ] ++ paths
210instance Exception ProcessException
211
212-- | Get the 'ProcessContext' from the environment.
213--
214-- @since 0.0.3.0
215class HasProcessContext env where
216  processContextL :: Lens' env ProcessContext
217instance HasProcessContext ProcessContext where
218  processContextL = id
219
220data EnvVarFormat = EVFWindows | EVFNotWindows
221
222currentEnvVarFormat :: EnvVarFormat
223currentEnvVarFormat =
224#if WINDOWS
225  EVFWindows
226#else
227  EVFNotWindows
228#endif
229
230-- Don't use CPP so that the Windows code path is at least type checked
231-- regularly
232isWindows :: Bool
233isWindows = case currentEnvVarFormat of
234              EVFWindows -> True
235              EVFNotWindows -> False
236
237-- | Override the working directory processes run in. @Nothing@ means
238-- the current process's working directory.
239--
240-- @since 0.0.3.0
241workingDirL :: HasProcessContext env => Lens' env (Maybe FilePath)
242workingDirL = processContextL.lens pcWorkingDir (\x y -> x { pcWorkingDir = y })
243
244-- | Get the environment variables. We cannot provide a @Lens@ here,
245-- since updating the environment variables requires an @IO@ action to
246-- allocate a new @IORef@ for holding the executable path cache.
247--
248-- @since 0.0.3.0
249envVarsL :: HasProcessContext env => SimpleGetter env EnvVars
250envVarsL = processContextL.to pcTextMap
251
252-- | Get the 'EnvVars' as an associated list of 'String's.
253--
254-- Useful for interacting with other libraries.
255--
256-- @since 0.0.3.0
257envVarsStringsL :: HasProcessContext env => SimpleGetter env [(String, String)]
258envVarsStringsL = processContextL.to pcStringList
259
260-- | Get the list of directories searched for executables (the @PATH@).
261--
262-- Similar to 'envVarMapL', this cannot be a full @Lens@.
263--
264-- @since 0.0.3.0
265exeSearchPathL :: HasProcessContext env => SimpleGetter env [FilePath]
266exeSearchPathL = processContextL.to pcPath
267
268-- | Create a new 'ProcessContext' from the given environment variable map.
269--
270-- @since 0.0.3.0
271mkProcessContext :: MonadIO m => EnvVars -> m ProcessContext
272mkProcessContext tm' = do
273    ref <- newIORef Map.empty
274    return ProcessContext
275        { pcTextMap = tm
276        , pcStringList = map (T.unpack *** T.unpack) $ Map.toList tm
277        , pcPath =
278             (if isWindows then (".":) else id)
279             (maybe [] (FP.splitSearchPath . T.unpack) (Map.lookup "PATH" tm))
280        , pcExeCache = ref
281        , pcExeExtensions =
282            if isWindows
283                then let pathext = fromMaybe defaultPATHEXT
284                                             (Map.lookup "PATHEXT" tm)
285                      in map T.unpack $ T.splitOn ";" pathext
286                else [""]
287        , pcWorkingDir = Nothing
288        }
289  where
290    -- Fix case insensitivity of the PATH environment variable on Windows.
291    tm
292        | isWindows = Map.fromList $ map (first T.toUpper) $ Map.toList tm'
293        | otherwise = tm'
294    -- Default value for PATHTEXT on Windows versions after Windows XP. (The
295    -- documentation of the default at
296    -- https://docs.microsoft.com/en-us/windows-server/administration/windows-commands/start
297    -- is incomplete.)
298    defaultPATHEXT = ".COM;.EXE;.BAT;.CMD;.VBS;.VBE;.JS;.JSE;.WSF;.WSH;.MSC"
299
300
301-- | Reset the executable cache.
302--
303-- @since 0.0.3.0
304resetExeCache :: (MonadIO m, MonadReader env m, HasProcessContext env) => m ()
305resetExeCache = do
306  pc <- view processContextL
307  atomicModifyIORef (pcExeCache pc) (const mempty)
308
309-- | Same as 'mkProcessContext' but uses the system environment (from
310-- 'System.Environment.getEnvironment').
311--
312-- @since 0.0.3.0
313mkDefaultProcessContext :: MonadIO m => m ProcessContext
314mkDefaultProcessContext =
315    liftIO $
316    getEnvironment >>=
317          mkProcessContext
318        . Map.fromList . map (T.pack *** T.pack)
319
320-- | Modify the environment variables of a 'ProcessContext'. This will not
321-- change the working directory.
322--
323-- Note that this requires 'MonadIO', as it will create a new 'IORef'
324-- for the cache.
325--
326-- @since 0.0.3.0
327modifyEnvVars
328  :: MonadIO m
329  => ProcessContext
330  -> (EnvVars -> EnvVars)
331  -> m ProcessContext
332modifyEnvVars pc f = do
333  pc' <- mkProcessContext (f $ pcTextMap pc)
334  return pc' { pcWorkingDir = pcWorkingDir pc }
335
336-- | Use 'modifyEnvVars' to create a new 'ProcessContext', and then
337-- use it in the provided action.
338--
339-- @since 0.0.3.0
340withModifyEnvVars
341  :: (HasProcessContext env, MonadReader env m, MonadIO m)
342  => (EnvVars -> EnvVars)
343  -> m a
344  -> m a
345withModifyEnvVars f inner = do
346  pc <- view processContextL
347  pc' <- modifyEnvVars pc f
348  local (set processContextL pc') inner
349
350-- | Look into the `ProcessContext` and return the specified environmet variable if one is
351-- available.
352--
353-- @since 0.1.14.0
354lookupEnvFromContext :: (MonadReader env m, HasProcessContext env) => Text -> m (Maybe Text)
355lookupEnvFromContext envName = Map.lookup envName <$> view envVarsL
356
357-- | Set the working directory to be used by child processes.
358--
359-- @since 0.0.3.0
360withWorkingDir
361  :: (HasProcessContext env, MonadReader env m, MonadIO m)
362  => FilePath
363  -> m a
364  -> m a
365withWorkingDir = local . set workingDirL . Just
366
367-- | Perform pre-call-process tasks.  Ensure the working directory exists and find the
368-- executable path.
369--
370-- Throws a 'ProcessException' if unsuccessful.
371--
372-- NOT CURRENTLY EXPORTED
373preProcess
374  :: (HasProcessContext env, MonadReader env m, MonadIO m)
375  => String            -- ^ Command name
376  -> m FilePath
377preProcess name = do
378  name' <- findExecutable name >>= either throwIO return
379  wd <- view workingDirL
380  liftIO $ maybe (return ()) (D.createDirectoryIfMissing True) wd
381  return name'
382
383-- | Log running a process with its arguments, for debugging (-v).
384--
385-- This logs one message before running the process and one message after.
386--
387-- NOT CURRENTLY EXPORTED
388withProcessTimeLog
389  :: (MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack)
390  => Maybe FilePath -- ^ working dirj
391  -> String -- ^ executable
392  -> [String] -- ^ arguments
393  -> m a
394  -> m a
395withProcessTimeLog mdir name args proc' = do
396  let cmdText =
397          T.intercalate
398              " "
399              (T.pack name : map showProcessArgDebug args)
400      dirMsg =
401        case mdir of
402          Nothing -> ""
403          Just dir -> " within " <> T.pack dir
404  logDebug ("Run process" <> display dirMsg <> ": " <> display cmdText)
405  start <- getMonotonicTime
406  x <- proc'
407  end <- getMonotonicTime
408  let diff = end - start
409  useColor <- view logFuncUseColorL
410  accentColors <- view logFuncAccentColorsL
411  logDebug
412      ("Process finished in " <>
413      (if useColor then accentColors 0 else "") <> -- accent color 0
414      timeSpecMilliSecondText diff <>
415      (if useColor then "\ESC[0m" else "") <> -- reset
416       ": " <> display cmdText)
417  return x
418
419timeSpecMilliSecondText :: Double -> Utf8Builder
420timeSpecMilliSecondText d = display (round (d * 1000) :: Int) <> "ms"
421
422-- | Provide a 'ProcessConfig' based on the 'ProcessContext' in
423-- scope. Deals with resolving the full path, setting the child
424-- process's environment variables, setting the working directory, and
425-- wrapping the call with 'withProcessTimeLog' for debugging output.
426--
427-- This is intended to be analogous to the @proc@ function provided by
428-- the @System.Process.Typed@ module, but has a different type
429-- signature to (1) allow it to perform @IO@ actions for looking up
430-- paths, and (2) allow logging and timing of the running action.
431--
432-- @since 0.0.3.0
433proc
434  :: (HasProcessContext env, HasLogFunc env, MonadReader env m, MonadIO m, HasCallStack)
435  => FilePath -- ^ command to run
436  -> [String] -- ^ command line arguments
437  -> (ProcessConfig () () () -> m a)
438  -> m a
439proc name0 args inner = do
440  name <- preProcess name0
441  wd <- view workingDirL
442  envStrings <- view envVarsStringsL
443
444  withProcessTimeLog wd name args
445    $ inner
446    $ setEnv envStrings
447    $ maybe id setWorkingDir wd
448    $ P.proc name args
449
450-- | Same as 'P.withProcess', but generalized to 'MonadUnliftIO'.
451--
452-- @since 0.0.3.0
453withProcess
454  :: MonadUnliftIO m
455  => ProcessConfig stdin stdout stderr
456  -> (Process stdin stdout stderr -> m a)
457  -> m a
458withProcess pc f = withRunInIO $ \run -> P.withProcessTerm pc (run . f)
459{-# DEPRECATED withProcess "Please consider using withProcessWait, or instead use withProcessTerm" #-}
460
461-- | Same as 'P.withProcess_', but generalized to 'MonadUnliftIO'.
462--
463-- @since 0.0.3.0
464withProcess_
465  :: MonadUnliftIO m
466  => ProcessConfig stdin stdout stderr
467  -> (Process stdin stdout stderr -> m a)
468  -> m a
469withProcess_ pc f = withRunInIO $ \run -> P.withProcessTerm_ pc (run . f)
470{-# DEPRECATED withProcess_ "Please consider using withProcessWait, or instead use withProcessTerm" #-}
471
472-- | Same as 'P.withProcessWait', but generalized to 'MonadUnliftIO'.
473--
474-- @since 0.1.10.0
475withProcessWait
476  :: MonadUnliftIO m
477  => ProcessConfig stdin stdout stderr
478  -> (Process stdin stdout stderr -> m a)
479  -> m a
480withProcessWait pc f = withRunInIO $ \run -> P.withProcessWait pc (run . f)
481
482-- | Same as 'P.withProcessWait_', but generalized to 'MonadUnliftIO'.
483--
484-- @since 0.1.10.0
485withProcessWait_
486  :: MonadUnliftIO m
487  => ProcessConfig stdin stdout stderr
488  -> (Process stdin stdout stderr -> m a)
489  -> m a
490withProcessWait_ pc f = withRunInIO $ \run -> P.withProcessWait_ pc (run . f)
491
492-- | Same as 'P.withProcessTerm', but generalized to 'MonadUnliftIO'.
493--
494-- @since 0.1.10.0
495withProcessTerm
496  :: MonadUnliftIO m
497  => ProcessConfig stdin stdout stderr
498  -> (Process stdin stdout stderr -> m a)
499  -> m a
500withProcessTerm pc f = withRunInIO $ \run -> P.withProcessTerm pc (run . f)
501
502-- | Same as 'P.withProcessTerm_', but generalized to 'MonadUnliftIO'.
503--
504-- @since 0.1.10.0
505withProcessTerm_
506  :: MonadUnliftIO m
507  => ProcessConfig stdin stdout stderr
508  -> (Process stdin stdout stderr -> m a)
509  -> m a
510withProcessTerm_ pc f = withRunInIO $ \run -> P.withProcessTerm_ pc (run . f)
511
512-- | A convenience environment combining a 'LogFunc' and a 'ProcessContext'
513--
514-- @since 0.0.3.0
515data LoggedProcessContext = LoggedProcessContext ProcessContext LogFunc
516
517instance HasLogFunc LoggedProcessContext where
518  logFuncL = lens (\(LoggedProcessContext _ lf) -> lf) (\(LoggedProcessContext pc _) lf -> LoggedProcessContext pc lf)
519instance HasProcessContext LoggedProcessContext where
520  processContextL = lens (\(LoggedProcessContext x _) -> x) (\(LoggedProcessContext _ lf) pc -> LoggedProcessContext pc lf)
521
522-- | Run an action using a 'LoggedProcessContext' with default
523-- settings and no logging.
524--
525-- @since 0.0.3.0
526withProcessContextNoLogging :: MonadIO m => RIO LoggedProcessContext a -> m a
527withProcessContextNoLogging inner = do
528  pc <- mkDefaultProcessContext
529  runRIO (LoggedProcessContext pc mempty) inner
530
531-- | Execute a process within the configured environment.
532--
533-- Execution will not return, because either:
534--
535-- 1) On non-windows, execution is taken over by execv of the
536-- sub-process. This allows signals to be propagated (#527)
537--
538-- 2) On windows, an 'ExitCode' exception will be thrown.
539--
540-- @since 0.0.3.0
541exec :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env b
542#ifdef WINDOWS
543exec = execSpawn
544#else
545exec cmd0 args = do
546    wd <- view workingDirL
547    envStringsL <- view envVarsStringsL
548    cmd <- preProcess cmd0
549    withProcessTimeLog wd cmd args $ liftIO $ do
550      for_ wd setCurrentDirectory
551      executeFile cmd True args $ Just envStringsL
552#endif
553
554-- | Like 'exec', but does not use 'execv' on non-windows. This way,
555-- there is a sub-process, which is helpful in some cases
556-- (<https://github.com/commercialhaskell/stack/issues/1306>).
557--
558-- This function only exits by throwing 'ExitCode'.
559--
560-- @since 0.0.3.0
561execSpawn :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env a
562execSpawn cmd args = proc cmd args (runProcess . setStdin inherit) >>= liftIO . exitWith
563
564-- | Check if the given executable exists on the given PATH.
565--
566-- @since 0.0.3.0
567doesExecutableExist
568  :: (MonadIO m, MonadReader env m, HasProcessContext env)
569  => String            -- ^ Name of executable
570  -> m Bool
571doesExecutableExist = liftM isRight . findExecutable
572
573-- | Find the complete path for the given executable name.
574--
575-- On POSIX systems, filenames that match but are not exectuables are excluded.
576--
577-- On Windows systems, the executable names tried, in turn, are the supplied
578-- name (only if it has an extension) and that name extended by each of the
579-- 'exeExtensions'. Also, this function may behave differently from
580-- 'RIO.Directory.findExecutable'. The latter excludes as executables filenames
581-- without a @.bat@, @.cmd@, @.com@ or @.exe@ extension (case-insensitive).
582--
583-- @since 0.0.3.0
584findExecutable
585  :: (MonadIO m, MonadReader env m, HasProcessContext env)
586  => String
587  -- ^ Name of executable
588  -> m (Either ProcessException FilePath)
589  -- ^ Full path to that executable on success
590findExecutable name | any FP.isPathSeparator name = do
591  names <- addPcExeExtensions name
592  testFPs (pure $ Left $ ExecutableNotFoundAt name) D.makeAbsolute names
593findExecutable name = do
594  pc <- view processContextL
595  m <- readIORef $ pcExeCache pc
596  case Map.lookup name m of
597    Just epath -> pure epath
598    Nothing -> do
599      let loop [] = pure $ Left $ ExecutableNotFound name (pcPath pc)
600          loop (dir:dirs) = do
601            fps <- addPcExeExtensions $ dir FP.</> name
602            testFPs (loop dirs) D.makeAbsolute fps
603      epath <- loop $ pcPath pc
604      () <- atomicModifyIORef (pcExeCache pc) $ \m' ->
605          (Map.insert name epath m', ())
606      pure epath
607
608-- | A helper function to add the executable extensions of the process context
609-- to a file path. On Windows, the original file path is included, if it has an
610-- existing extension.
611addPcExeExtensions
612  :: (MonadIO m, MonadReader env m, HasProcessContext env)
613  => FilePath -> m [FilePath]
614addPcExeExtensions fp = do
615  pc <- view processContextL
616  pure $ (if isWindows && FP.hasExtension fp then (fp:) else id)
617         (map (fp ++) (pcExeExtensions pc))
618
619-- | A helper function to test whether file paths are to an executable
620testFPs
621  :: (MonadIO m, MonadReader env m, HasProcessContext env)
622  => m (Either ProcessException FilePath)
623  -- ^ Default if no executable exists at any file path
624  -> (FilePath -> IO FilePath)
625  -- ^ Modification to apply to a file path, if an executable exists there
626  -> [FilePath]
627  -- ^ File paths to test, in turn
628  -> m (Either ProcessException FilePath)
629testFPs ifNone _ [] = ifNone
630testFPs ifNone modify (fp:fps) = do
631  exists <- liftIO $ D.doesFileExist fp
632  existsExec <- liftIO $ if exists
633    then if isWindows then pure True else isExecutable
634    else pure False
635  if existsExec then liftIO $ Right <$> modify fp else testFPs ifNone modify fps
636 where
637  isExecutable = D.executable <$> D.getPermissions fp
638
639-- | Get the filename extensions for executable files, including the dot (if
640-- any).
641--
642-- On POSIX systems, this is @[""]@.
643--
644-- On Windows systems, the list is determined by the value of the @PATHEXT@
645-- environment variable, if it present in the environment. If the variable is
646-- absent, this is its default value on a Windows system. This function may,
647-- therefore, behave differently from 'RIO.Directory.exeExtension',
648-- which returns only @".exe"@.
649--
650-- @since 0.1.13.0
651exeExtensions :: (MonadIO m, MonadReader env m, HasProcessContext env)
652              => m [String]
653exeExtensions = do
654  pc <- view processContextL
655  return $ pcExeExtensions pc
656
657-- | Augment the PATH environment variable with the given extra paths.
658--
659-- @since 0.0.3.0
660augmentPath :: [FilePath] -> Maybe Text -> Either ProcessException Text
661augmentPath dirs mpath =
662  case filter (FP.searchPathSeparator `elem`) dirs of
663    [] -> Right
664            $ T.intercalate (T.singleton FP.searchPathSeparator)
665            $ map (T.pack . FP.dropTrailingPathSeparator) dirs
666            ++ maybeToList mpath
667    illegal -> Left $ PathsInvalidInPath illegal
668
669-- | Apply 'augmentPath' on the PATH value in the given 'EnvVars'.
670--
671-- @since 0.0.3.0
672augmentPathMap :: [FilePath] -> EnvVars -> Either ProcessException EnvVars
673augmentPathMap dirs origEnv =
674  do path <- augmentPath dirs mpath
675     return $ Map.insert "PATH" path origEnv
676  where
677    mpath = Map.lookup "PATH" origEnv
678
679-- | Show a process arg including speechmarks when necessary. Just for
680-- debugging purposes, not functionally important.
681--
682-- @since 0.0.3.0
683showProcessArgDebug :: String -> Text
684showProcessArgDebug x
685    | any special x || null x = T.pack (show x)
686    | otherwise = T.pack x
687  where special '"' = True
688        special ' ' = True
689        special _ = False
690