{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} module System.FilePath.FilePather.Process( spawnProcess , showCommandForUser , readProcess , proc , callProcess , readProcessWithExitCode ) where import Control.Exitcode as E ( ExitcodeT ) import Control.Exception ( Exception ) import Control.Monad.Reader.Class ( MonadReader(reader) ) import Control.Monad.Except ( ExceptT ) import Control.Process( ProcessHandle, CreateProcess ) import qualified Control.Process as P import Data.String ( String ) import System.FilePath.FilePather.ReadFilePath ( ReadFilePath, ReadFilePathT, successReadFilePath, tryReadFilePath ) import System.IO ( IO ) spawnProcess :: Exception e => [String] -> ReadFilePathT e IO ProcessHandle spawnProcess x = tryReadFilePath (`P.spawnProcess` x) showCommandForUser :: [String] -> ReadFilePath e String showCommandForUser x = reader (`P.showCommandForUser` x) readProcess :: Exception e => [String] -> String -> ReadFilePathT e IO String readProcess args i = tryReadFilePath (\p -> P.readProcess p args i) proc :: [String] -> ReadFilePath e CreateProcess proc s = reader (`P.proc` s) callProcess :: Exception e => [String] -> ReadFilePathT e IO () callProcess s = tryReadFilePath (`P.callProcess` s) readProcessWithExitCode :: Exception e' => [String] -> String -> ReadFilePathT e (ExitcodeT (ExceptT e' IO) (String, String)) (String, String) readProcessWithExitCode as a = successReadFilePath (\p -> P.readProcessWithExitCode p as a)