Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
- cmd :: String -> [String] -> IO String
- cmd_ :: String -> [String] -> IO ()
- cmdBool :: String -> [String] -> IO Bool
- cmdIgnoreErr :: String -> [String] -> String -> IO String
- cmdLines :: String -> [String] -> IO [String]
- cmdMaybe :: String -> [String] -> IO (Maybe String)
- cmdLog :: String -> [String] -> IO ()
- cmdlog :: String -> [String] -> IO ()
- cmdN :: String -> [String] -> IO ()
- cmdQuiet :: String -> [String] -> IO String
- cmdSilent :: String -> [String] -> IO ()
- cmdStdIn :: String -> [String] -> String -> IO String
- cmdStdErr :: String -> [String] -> IO (String, String)
- error' :: String -> a
- egrep_ :: String -> FilePath -> IO Bool
- grep :: String -> FilePath -> IO [String]
- grep_ :: String -> FilePath -> IO Bool
- logMsg :: String -> IO ()
- removePrefix :: String -> String -> String
- removeStrictPrefix :: String -> String -> String
- removeSuffix :: String -> String -> String
- shell :: String -> IO String
- shell_ :: String -> IO ()
- sudo :: String -> [String] -> IO ()
- (+-+) :: String -> String -> String
Documentation
'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
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
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_ pat file' greps pattern in file and returns Boolean status
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