simple-cmd-0.2.1: Simple String-based process commands

Safe HaskellSafe
LanguageHaskell2010

SimpleCmd

Description

Some simple String wrappers of readProcess, readProcessWithExitCode, rawSystem from the Haskell process library.

Simplest is

cmd_ :: String -> [String] -> IO ()

which outputs to stdout. For example:

cmd_ "git" ["clone", url]

Then

cmd :: String -> [String] -> IO String

returns stdout as a String.

There are also cmdBool, cmdMaybe, cmdLines, shell, and others.

Other examples:

grep_ pat file :: IO Bool
sudo c args :: IO ()
Synopsis

Documentation

cmd Source #

Arguments

:: String

command to run

-> [String]

list of arguments

-> IO String

stdout

'cmd c args' runs a command in a process and returns stdout

cmd_ :: String -> [String] -> IO () Source #

'cmd_ c args' runs command in a process, output goes to stdout and stderr

cmdBool :: String -> [String] -> IO Bool Source #

'cmdBool c args' runs a command, and return Boolean status

cmdIgnoreErr :: String -> [String] -> String -> IO String Source #

'cmdIgnoreErr c args inp' runs a command with input, drops stderr, and return stdout

cmdLines :: String -> [String] -> IO [String] Source #

'cmdLines c args' runs a command, and returns list of stdout lines

Since: 0.1.1

cmdMaybe :: String -> [String] -> IO (Maybe String) Source #

'cmdMaybe c args' runs a command, maybe returning output if it succeeds

cmdLog :: String -> [String] -> IO () Source #

'cmdLog c args' logs a command with a datestamp

Since: 0.1.4

cmdlog :: String -> [String] -> IO () Source #

cmdlog deprecated alias for cmdLog (will be removed in 0.3)

cmdN :: String -> [String] -> IO () Source #

'cmdN c args' dry-runs a command: prints command to stdout - more used for debugging

cmdQuiet :: String -> [String] -> IO String Source #

'cmdQuiet c args' runs a command hiding stderr, if it succeeds returns stdout

cmdSilent :: String -> [String] -> IO () Source #

'cmdSilent c args' runs a command hiding stdout: stderr is only output if it fails.

cmdStdIn :: String -> [String] -> String -> IO String Source #

'cmdStdIn c args inp' runs a command, passing input string as stdin, and returns stdout

cmdStdErr :: String -> [String] -> IO (String, String) Source #

'cmdStdErr c args' runs command in a process, returning stdout and stderr

cmdTry_ :: String -> [String] -> IO () Source #

'cmdTry_ c args' runs the command if available

Since: 0.2.1

error' :: String -> a Source #

Alias for errorWithoutStackTrace (for base >= 4.9)

Since: 0.1.4

egrep_ :: String -> FilePath -> IO Bool Source #

'egrep_ pat file' greps extended regexp in file, and returns Boolean status

grep :: String -> FilePath -> IO [String] Source #

'grep pat file' greps pattern in file, and returns list of matches

Since: 0.1.2

grep_ Source #

Arguments

:: String

pattern

-> FilePath

file

-> IO Bool

result

'grep_ pat file' greps pattern in file and returns Boolean status

ifM :: Monad m => m Bool -> m a -> m a -> m a Source #

Monadic if ifM test actTrue actFalse (taken from protolude)

Since: 0.2.1

logMsg :: String -> IO () Source #

'logMsg msg' outputs message with a timestamp

needProgram :: String -> IO () Source #

Assert program in PATH needProgram progname

Since: 0.2.1

removePrefix :: String -> String -> String Source #

'removePrefix prefix original' removes prefix from string if present

removeStrictPrefix :: String -> String -> String Source #

'removeStrictPrefix prefix original' removes prefix, or fails with error'

removeSuffix :: String -> String -> String Source #

'removeSuffix suffix original' removes suffix from string if present

shell :: String -> IO String Source #

'shell cs' runs a command string in a shell, and returns stdout

shell_ :: String -> IO () Source #

'shell_ cs' runs a command string in a shell, output goes to stdout

shellBool :: String -> IO Bool Source #

'shellBool cs' runs a command string in a shell, output goes to stdout

Since: 0.2.0

sudo Source #

Arguments

:: String

command

-> [String]

arguments

-> IO String 

'sudo c args' runs a command as sudo returning stdout

Result type changed from IO () to IO String in 0.2.0

sudo_ Source #

Arguments

:: String

command

-> [String]

arguments

-> IO () 

'sudo_ c args' runs a command as sudo

Since: 0.2.0

warning :: String -> IO () Source #

warning outputs to stderr

Since: 0.2.0

type PipeCommand = (String, [String]) Source #

Type alias for a command in a pipe

Since: 0.2.0

pipe :: PipeCommand -> PipeCommand -> IO String Source #

Return stdout from piping the output of one process to another

Since: 0.2.0

pipe_ :: PipeCommand -> PipeCommand -> IO () Source #

Pipe two commands without returning anything

Since: 0.2.0

pipeBool :: PipeCommand -> PipeCommand -> IO Bool Source #

Bool result of piping of commands

Since: 0.2.0

pipe3_ :: PipeCommand -> PipeCommand -> PipeCommand -> IO () Source #

Pipe 3 commands, no returning anything

Since: 0.2.0

pipeFile_ :: FilePath -> PipeCommand -> PipeCommand -> IO () Source #

Pipe a file to the first of a pipe of commands

Since: 0.2.0

whenM :: Monad m => m Bool -> m () -> m () Source #

Monadic when whenM test action

Since: 0.2.1

(+-+) :: String -> String -> String infixr 4 Source #

Combine two strings with a single space