hsshellscript-3.3.1: Haskell for Unix shell scripting tasks

Safe HaskellNone

HsShellScript.ProcErr

Synopsis

Documentation

setFileMode' :: FilePath -> FileMode -> IO ()Source

Improved version of System.Posix.Files.setFileMode, which sets the file name in the IOError which is thrown in case of an error. The implementation in GHC 6.2.2 neglects to do this.

setFileMode' path mode =
   fill_in_filename path $
      setFileMode path mode

subprocSource

Arguments

:: IO a

Action to execute in a child process

-> IO () 

Execute an IO action as a separate process, and wait for it to finish. Report errors as exceptions.

This forks a child process, which performs the specified IO action. In case the child process has been stopped by a signal, the parent blocks.

If the action throws an IOError, it is transmitted to the parent. It is then raised there, as if it happened locally. The child then aborts quietly with an exit code of 0.

Exceptions in the child process, other than IOErrors, result in an error message on stderr, and a ProcessStatus exception in the parent, with the value of Exited (ExitFailure 1). The following exceptions are understood by subproc, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

If the child process exits with an exit code other than zero, or it is terminated by a signal, the corresponding ProcessStatus is raised as an exception in the parent program. Only IOErrors are transmitted to the parent.

When used in conjunction with an exec variant, this means that the parent process can tell the difference between failure of the exec call itself, and failure of the child program being executed after a successful call of the exec variant. In case of failure of the exec call, You get the IOError, which happened in the child when calling executeFile (from the GHC hierarchical libraries). In case of the called program failing, you get the ProcessStatus.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally (unless it throws an IOError). The child process is then properly terminated by subproc, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

If you want to run an external program, by calling one of the exec variants in the child action, you might want to call runprog instead of subproc.

Examples:

Run a program with the environment replaced:

subproc (execpe "foobar" ["1","2","3"] new_env)

This results in a ProcessStatus exception:

subproc (exec "/bin/false" [])

This results in an IOError (unless you actually have /frooble):

subproc (exec "/frooble" [])

See runprog, spawn, exec, execp, exece, execpe.

callSource

Arguments

:: IO a

action to execute as a child process

-> IO () 

Execute an IO action as a separate process, and wait for it to finish. Report errors as exceptions.

This function is included only for backwards compatibility. New code should use subproc instead, which has better error handling.

The program forks a child process and performs the specified action. Then it waits for the child process to finish. If it exits in any way which indicates an error, the ProcessStatus is thrown.

The parent process waits for the child processes, which have been stopped by a signal.

See HsShellScript for further details.

See subproc, spawn.

spawnSource

Arguments

:: IO a

Action to execute as a child process.

-> IO ProcessID

Process ID of the new process.

Execute an IO action as a separate process, and continue without waiting for it to finish.

The program forks a child process, which performs the specified action and terminates. The child's process ID is returned.

See HsShellScript for further details.

See subproc.

runSource

Arguments

:: FilePath

Name of the executable to run

-> [String]

Command line arguments

-> IO () 

Run an external program. This starts a program as a child process, and waits for it to finish. The executable is searched via the PATH.

This function is included for backwards compatibility only. New code should use runprog, which has much better error handling.

When the specified program can't be executed, an error message is printed, and the main process gets a ProcessStatus thrown, with the value Exited (ExitFailure 1). This means that the main program can't distinguish between failure of calling the program and the program exiting with an exit code of 1. However, an error message "Error calling ...", including the description in the IOError produced by the failed execp call, is printed on stderr.

run prog par is essentially call (execp prog par).

Example:

run "/usr/bin/foobar" ["some", "args"]
   `catch` (\ps -> do -- oops...
              )

See runprog, subproc, spawn.

data RunError Source

An error which occured when calling an external program. The fields specifiy the details of the call.

See show_runerror, to_ioe, as_ioe, System.Posix.ProcessStatus.

Constructors

RunError 

Fields

re_prog :: String

Program name

re_pars :: [String]

Program arguments

re_env :: [(String, String)]

The environment in use when the call was done

re_wd :: String

The working directory when the call was done

re_ps :: ProcessStatus

The process status of the failure

re_errno :: Maybe CInt

The error (errno) code

show_runerror :: RunError -> StringSource

Make a readable error message. This includes all the fields of RunError except for the environment.

See RunError.

explain_processstatus :: ProcessStatus -> StringSource

Generate a human-readable description of a ProcessStatus.

See exec, runprog and System.Posix.ProcessStatus in the GHC hierarchical library documentation.

to_ioe :: RunError -> IOErrorSource

Convert a RunError to an IOError.

The IOError type isn't capable of holding all the information which is contained in a RunError. The environment is left out, and most of the other fields are included only informally, in the description.

The fields of the generated IOError are:

  • The handle (ioeGetHandle): Nothing
  • The error type (ioeGetErrorType): GHC.IO.Exception.SystemError
  • ioe_location: "runprog"
  • ioe_description: The error message, as procuded by show_runerror.
  • ioe_filename: This is Just (shell_command prog pars), with prog and pars being the program and its arguments.

See as_ioe, runprog, show_runerror.

as_ioe :: IO a -> IO aSource

Call the specified IO action (which is expected to contain calls of runprog) and convert any RunError exceptions to IOErrors.

The conversion is done by to_ioe.

See to_ioe, runprog.

runprogSource

Arguments

:: FilePath

Name of the executable to run

-> [String]

Command line arguments

-> IO () 

Run an external program, and report errors as exceptions. The executable is searched via the PATH. In case the child process has been stopped by a signal, the parent blocks.

In case the program exits in an way which indicates an error, or is terminated by a signal, a RunError is thrown. It contains the details of the call. The runprog action can also be converted to throw IOErrors instaed, by applying as_ioe to it. Either can be used to generate an informative error message.

In case of starting the program itself failed, an IOError is thrown.

runprog prog par is a simple front end to subproc. It is essentially subproc (execp prog par), apart from building a RunError from a ProcessStatus.

Example 1:

do runprog "foo" ["some", "args"]
   ...
`catch` (\re -> do errm (show_runerror re)
                      ...
           )

Example 2:

do as_ioe $ runprog "foo" ["some", "args"]
   ...
`catch` (\ioe -> do errm (show_ioerror ioe)
                       ...
           )

See subproc, spawn, RunError, show_runerror, to_ioe, as_ioe.

echoSource

Arguments

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

Action to perform

-> FilePath

Name or path of the executable to run

-> [String]

Command line arguments

-> IO () 

Print an action as a shell command, then perform it.

This is used with actions such as runprog, exec or subproc. For instance, echo runprog prog args is a variant of runprog prog args, which prints what is being done before doing it.

See runprog, subproc, exec.

execSource

Arguments

:: String

Full path to the executable

-> [String]

Command line arguments

-> IO a

Never returns

Execute an external program. This replaces the running process. The path isn't searched, the environment isn't changed. In case of failure, an IOError is thrown.

exec path args =
   execute_file path False args Nothing

See execute_file, HsShellScript.

execpSource

Arguments

:: String

Name or path of the executable

-> [String]

Command line arguments

-> IO a

Never returns

Execute an external program. This replaces the running process. The path is searched, the environment isn't changed. In case of failure, an IOError is thrown.

execp prog args =
   execute_file prog True args Nothing

See execute_file, HsShellScript.

execeSource

Arguments

:: String

Full path to the executable

-> [String]

Command line arguments

-> [(String, String)]

New environment

-> IO a

Never returns

Execute an external program. This replaces the running process. The path isn't searched, the environment of the program is set as specified. In case of failure, an IOError is thrown.

exece path args env =
   execute_file path False args (Just env)

See execute_file, HsShellScript.

execpeSource

Arguments

:: String

Name or path of the executable

-> [String]

Command line arguments

-> [(String, String)]

New environment

-> IO a

Never returns

Execute an external program. This replaces the running process. The path is searched, the environment of the program is set as specified. In case of failure, an IOError is thrown.

execpe prog args env =
   execute_file prog True args (Just env)

See execute_file, HsShellScript.

(-|-)Source

Arguments

:: IO a

Action which won't be forked

-> IO b

Action which will be forked and connected with a pipe

-> IO a

Result action

Build left handed pipe of stdout.

"p -|- q" builds an IO action from the two IO actions p and q. q is executed in an external process. The standard output of p is sent to the standard input of q through a pipe. The result action consists of forking off q (connected with a pipe), and p.

The result action does not run p in a separate process. So, the pipe itself can be seen as a modified action p, forking a connected q. The pipe is called "left handed", because p remains unforked, and not q.

The exit code of q is silently ignored. The process ID of the forked copy of q isn't returned to the caller, so it's lost.

The pipe, which connects p and q, is in text mode. This means that the output of p is converted from Unicode to the system character set, which is determined by the environment variable LANG.

See HsShellScript and HsShellScript for further details.

Examples:

call (exec "/usr/bin/foo" [] -|- exec "/usr/bin/bar" [])
call (    execp "foo" ["..."]
      -|= ( -- Do something with foo's output
            do cnt <- lazy_contents "-"
               ...
          )
     )

See subproc, '(=|-)', '(-|=)', redirect

(=|-)Source

Arguments

:: IO a

Action which won't be forked

-> IO b

Action which will be forked and connected with a pipe

-> IO a

Result action

Build left handed pipe of stderr.

"p =|- q" builds an IO action from the two IO actions p and q. q is executed in an external process. The standard error output of p is sent to the standard input of q through a pipe. The result action consists of forking off q (connected with a pipe), and p.

The result action does not run p in a separate process. So, the pipe itself can be seen as a modified action p, forking a connected q. The pipe is called "left handed", because p has this property, and not q.

The exit code of q is silently ignored. The process ID of the forked copy of q isn't returned to the caller, so it's lost.

The pipe, which connects p and q, is in text mode. This means that the output of p is converted from Unicode to the system character set, which is determined by the environment variable LANG.

See HsShellScript and HsShellScript for further details.

Example:

call (exec "/usr/bin/foo" [] =|- exec "/usr/bin/bar" [])

See subproc, '(-|-)', '(-|=)'.

(-|=)Source

Arguments

:: IO a

Action which will be forked and connected with a pipe

-> IO b

Action which won't be forked

-> IO b

Result action

Build right handed pipe of stdout.

"p -|= q" builds an IO action from the two IO actions p and q. p is executed in an external process. The standard output of p is sent to the standard input of q through a pipe. The result action consists of forking off p (connected with a pipe), and q.

The result action does not run q in a separate process. So, the pipe itself can be seen as a modified action q, forking a connected p. The pipe is called "right handed", because q has this property, and not p.

The exit code of p is silently ignored. The process ID of the forked copy of q isn't returned to the caller, so it's lost.

The pipe, which connects p and q, is in text mode. This means that the output of p is converted from Unicode to the system character set, which is determined by the environment variable LANG.

See HsShellScript and HsShellScript for further details.

Example:

@call (exec \"\/usr\/bin\/foo\" [] -|= exec \"\/usr\/bin\/bar\" [])@

See subproc, '(=|-)', '(=|=)'.

(=|=)Source

Arguments

:: IO a

Action which will be forked and connected with a pipe

-> IO b

Action which won't be forked

-> IO b

Result action

Build right handed pipe of stderr.

"p =|= q" builds an IO action from the two IO actions p and q. p is executed in an external process. The standard error output of p is sent to the standard input of q through a pipe. The result action consists of forking off p (connected with a pipe), and q.

The result action does not run q in a separate process. So, the pipe itself can be seen as a modified action q, forking a connected p. The pipe is called "right handed", because q has this property, and not p.

The exit code of p is silently ignored. The process ID of the forked copy of q isn't returned to the caller, so it's lost.

The pipe, which connects p and q, is in text mode. This means that the output of p is converted from Unicode to the system character set, which is determined by the environment variable LANG.

See HsShellScript and HsShellScript for further details.

Example:

 call (exec "/usr/bin/foo" [] =|= exec "/usr/bin/bar" [])

See subproc, =|-, -|=.

redirectSource

Arguments

:: Handle

Handle to replace

-> Handle

Handle to replace it with

-> IO a

Action

-> IO a 

Temporarily replace a handle. This makes a backup copy of the original handle (typically a standard handle), overwrites it with the specified one, runs the specified action, and restores the handle from the backup.

Example:

   h <- openFile "/tmp/log" WriteMode
   redirect stdout h io
   hClose h

This is the same as

   io ->- "/tmp/log"

See -|-, =|-.

(->-)Source

Arguments

:: IO a

Action, whose output will be redirected

-> FilePath

File to redirect the output to

-> IO a

Result action

Redirect the standard output of the specified IO action to a file. The file will be overwritten, if it already exists.

What's actually modified is the stdout handle, not the file descriptor 1. The exec functions know about this. See HsShellScript and HsShellScript for details.

The file is written in text mode. This means that the output is converted from Unicode to the system character set, which is determined by the environment variable LANG.

Example:

runprog "/some/program" [] ->- "/tmp/output"

Note: You can't redirect to "/dev/null" this way, because GHC 6.4's openFile throws an "invalid argument" IOError. (This may be a bug in the GHC 6.4 libraries). Use ->>- instead.

See subproc, runprog, ->>-, =>-.

(->>-)Source

Arguments

:: IO a

Action, whose output will be redirected

-> FilePath

File to redirect the output to

-> IO a

Result action

Redirect the standard output of the specified IO action to a file. If the file already exists, the output will be appended.

What's actually modified is the stdout handle, not the file descriptor 1. The exec functions know about this. See HsShellScript and HsShellScript for details.

The file is written in text mode. This means that the output is converted from Unicode to the system character set, which is determined by the environment variable LANG.

Example:

run "/some/noisy/program" [] ->>- "/dev/null"

See subproc, runprog, '(->-)', '(=>>-)'.

(=>-)Source

Arguments

:: IO a

Action, whose error output will be redirected

-> FilePath

File to redirect the error output to

-> IO a

Result action

Redirect the standard error output of the specified IO action to a file. If the file already exists, it will be overwritten.

What's actually modified is the stderr handle, not the file descriptor 2. The exec functions know about this. See HsShellScript and HsShellScript for details.

Note: You can't redirect to "/dev/null" this way, because GHC 6.4's openFile throws an "invalid argument" IOError. (This may be a bug in the GHC 6.4 libraries). Use =>>- instead.

The file is written in text mode. This means that the output is converted from Unicode to the system character set, which is determined by the environment variable LANG.

Example:

run "/path/to/foo" [] =>- "/tmp/errlog"

See subproc, runprog, '(->-)', '(=>>-)'.

(=>>-)Source

Arguments

:: IO a

Action, whose error output will be redirected

-> FilePath

File to redirect the error output to

-> IO a

Result action

Redirect the standard error output of the specified IO action to a file. If the file already exists, the output will be appended.

What's actually modified is the stderr handle, not the file descriptor 2. The exec functions know about this. See HsShellScript and HsShellScript for details.

The file is written in text mode. This means that the output is converted from Unicode to the system character set, which is determined by the environment variable LANG.

Example:

run "/some/program" [] =>>- "/dev/null"

See subproc, runprog, '(->>-)', '(=>-)'.

(-&>-)Source

Arguments

:: IO a

Action, whose output and error output will be redirected

-> FilePath

File to redirect to

-> IO a

Result action

Redirect both stdout and stderr to a file. This is equivalent to the shell's &> operator. If the file already exists, it will be overwritten.

What's actually modified are the stdout and stderr handles, not the file descriptors 1 and 2. The exec functions know about this. See HsShellScript and HsShellScript for details.

Note: You can't redirect to "/dev/null" this way, because GHC 6.4's openFile throws an "invalid argument" IOError. (This may be a bug in the GHC 6.4 libraries). Use -&>>- instead.

The file is written in text mode. This means that the output is converted from Unicode to the system character set, which is determined by the environment variable LANG.

(-&>-) io path = err_to_out io ->- path

Example:

call (exec "/path/to/foo" [] -&>- "log")

See '(-&>>-)', err_to_out.

(-&>>-)Source

Arguments

:: IO a

Action, whose output and error output will be redirected

-> FilePath

File to redirect to

-> IO a

Result action

Redirect both stdout and stderr to a file. If the file already exists, the output will be appended.

What's actually modified are the stdout and stderr handles, not the file descriptors 1 and 2. The exec functions know about this. See HsShellScript and HsShellScript for details.

The file is written in text mode. This means that the output is converted from Unicode to the system character set, which is determined by the environment variable LANG.

(-&>>-) io path = (err_to_out >> io) ->>- path

Example:

run "/some/noisy/program" [] -&>>- "/dev/null"

See '(-&>-)', out_to_err.

(-<-) :: IO a -> FilePath -> IO aSource

Redirect stdin from a file. This modifies the specified action, such that the standard input is read from a file.

What's actually modified is the stdin handle, not the file descriptor 0. The exec functions know about this. See HsShellScript and HsShellScript for details.

The file is read in text mode. This means that the input is converted from the system character set to Unicode. The system's character set is determined by the environment variable LANG.

Example:

call (exec "/path/to/foo" [] -<- "bar")

See exec, runprog, '(->-)', '(=>-)'.

err_to_out :: IO a -> IO aSource

Send the error output of the specified action to its standard output.

What's actually modified is the stdout handle, not the file descriptor 1. The exec functions know about this. See HsShellScript and HsShellScript for details.

err_to_out = redirect stderr stdout

See redirect.

out_to_err :: IO a -> IO aSource

Send the output of the specified action to its standard error output.

What's actually modified is the stderr handle, not the file descriptor 2. The exec functions know about this. See HsShellScript and HsShellScript for details.

redirect stdout stderr

See redirect.

pipe_toSource

Arguments

:: String

Text to pipe

-> IO a

Action to run as a separate process, and to pipe to

-> IO () 

Run an IO action as a separate process, and pipe some text to its stdin. Then close the pipe and wait for the child process to finish.

This forks a child process, which executes the specified action. The specified text is sent to the action's stdin through a pipe. Then the pipe is closed. In case the action replaces the process by calling an exec variant, it is made sure that the process gets the text on it's file descriptor 0.

In case the action fails (exits with an exit status other than 0, or is terminated by a signal), the ProcessStatus is thrown, such as reported by getProcessStatus. No attempt is made to create more meaningful exceptions, like it is done by runprog/subproc.

Exceptions in the action result in an error message on stderr, and the termination of the child. The parent gets a ProcessStatus exception, with the value of Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

The pipe is set to text mode. This means that the Unicode characters in the text are converted to the system character set. If you need to pipe binary data, you should use h_pipe_to, and set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True. The system character set is determined by the environment variable LANG.

Example:

pipe_to "blah" (exec "/usr/bin/foo" ["bar"])

Example: Access both stdin and stdout of an external program.

import HsShellScript

main = mainwrapper $ do

   res <- pipe_from $
      pipe_to "2\n3\n1" $
         exec "/usr/bin/sort" []

   putStrLn res

See subproc, runprog, -<-, h_pipe_to.

h_pipe_toSource

Arguments

:: IO a

Action to run as a separate process, and to pipe to

-> IO (Handle, ProcessID)

Returns handle connected to the standard input of the child process, and the child's process ID

Run an IO action as a separate process, and get a connection (a pipe) to its stdin as a file handle.

This forks a subprocess, which executes the specified action. A file handle, which is connected to its stdin, is returned. The child's ProcessID is returned as well. If the action replaces the child process, by calling an exec variant, it is made sure that its file descriptor 0 is connected to the returned file handle.

This gives you full control of the pipe, and of the forked process. But you must cope with the child process by yourself.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

Errors can only be detected by examining the child's process status (using getProcessStatus). If the child action throws an exception, an error message is printed on stderr, and the child process exits with a ProcessStatus of Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

If the child process exits in a way which signals an error, the corresponding ProcessStatus is returned by getProcessStatus. See getProcessStatus for details.

The pipe is set to text mode. This means that the Unicode characters in the text are converted to the system character set. You can set the returned handle to binary mode, by calling hSetBinaryMode handle True. The system character set is determined by the environment variable LANG.

Example:

(handle, pid) <- h_pipe_to $ exec "/usr/bin/foo" ["bar"]
hPutStrLn handle "Some text to go through the pipe"
(Just ps) <- getProcessStatus True False pid
when (ps /= Exited ExitSuccess) $
   throw ps

See -<-, pipe_to, pipe_from, pipe_from2. See HsShellScript for more details.

pipe_fromSource

Arguments

:: IO a

Action to run as a separate process. Its return value is ignored.

-> IO String

The action's standard output

Run an IO action as a separate process, and read its stdout strictly. Then wait for the child process to finish. This is like the backquote feature of shells.

This forks a child process, which executes the specified action. The output of the child is read from its standard output. In case it replaces the process by calling an exec variant, it is make sure that the output is read from the new process' file descriptor 1.

The end of the child's output is reached when either the standard output is closed, or the child process exits. The program blocks until the action exits, even if the child closes its standard output earlier. So the parent process always notices a failure of the action (when it exits in a way which indicates an error).

When the child action exits in a way which indicates an error, the corresponding ProcessStatus is thrown. See getProcessStatus. No attempt is made to create more meaningful exceptions, like it is done by runprog/subproc.

Exceptions in the action result in an error message on stderr, and the proper termination of the child. The parent gets a ProcessStatus exception, with the value of Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

Unlike shells' backquote feature, pipe_from does not remove any trailing newline characters. The entire output of the action is returned. You might want to apply chomp to the result.

The pipe is set to text mode. This means that the Unicode characters in the text, which is read from stdin, is converted from the system character set to Unicode. The system character set is determined by the environment variable LANG. If you need to read binary data from the forked process, you should use h_pipe_from and set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True.

Example:

output <- pipe_from $ exec "/bin/mount" []

Example: Access both stdin and stdout of an external program.

import HsShellScript

main = mainwrapper $ do

   res <- pipe_from $
      pipe_to "2\n3\n1" $
         exec "/usr/bin/sort" []

   putStrLn res

See exec, pipe_to, pipe_from2, h_pipe_from, lazy_pipe_from, chomp, silently.

pipe_from2Source

Arguments

:: IO a

Action to run as a separate process

-> IO String

The action's standard error output

Run an IO action as a separate process, and read its standard error output strictly. Then wait for the child process to finish. This is like the backquote feature of shells. This function is exactly the same as pipe_from, except that the standard error output is read, instead of the standard output.

This forks a child process, which executes the specified action. The error output of the child is read from its standard error output. In case it replaces the process by calling an exec variant, it is made sure that the output is read from the new process' file descriptor 2.

The end of the child's error output is reached when either the standard error output is closed, or the child process exits. The program blocks until the action exits, even if the child closes its standard error output earlier. So the parent process always notices a failure of the action (which means it exits in a way which indicates an error).

When the child action exits in a way which indicates an error, the corresponding ProcessStatus is thrown. See getProcessStatus. No attempt is made to create more meaningful exceptions, like it is done by runprog/subproc.

Exceptions in the action result in an error message on stderr, and the proper termination of the child. This means that the error message is sent through the pipe, to the parent process. The message can be found in the text which has been read from the child process. It doesn't appear on the console.

The parent gets a ProcessStatus exception, with the value of Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

Unlike shells' backquote feature, pipe_from2 does not remove any trailing newline characters. The entire error output of the action is returned. You might want to apply chomp to the result.

The pipe is set to text mode. This means that the Unicode characters in the text, which is read from stdin, is converted from the system character set to Unicode. The system character set is determined by the environment variable LANG. If you need to read binary data from the forked process, you should use h_pipe_from and set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True.

Example:

output <- pipe_from $ exec "/bin/mount" []

Example: Access both stdin and stdout of an external program.

import HsShellScript

main = mainwrapper $ do

   res <- pipe_from $
      pipe_to "2\n3\n1" $
         exec "/usr/bin/sort" []

   putStrLn res

See exec, pipe_to, pipe_from, h_pipe_from2, lazy_pipe_from2, silently. See HsShellScript for more details.

h_pipe_fromSource

Arguments

:: IO a

Action to run as a separate process, and to pipe from

-> IO (Handle, ProcessID)

Returns handle connected to the standard output of the child process, and the child's process ID

Run an IO action as a separate process, and connect to its stdout with a file handle. This is like the backquote feature of shells.

This forks a subprocess, which executes the specified action. A file handle, which is connected to its stdout, is returned. The child's ProcessID is returned as well. If the action replaces the child process, by calling an exec variant, it is made sure that its file descriptor 1 is connected to the returned file handle.

This gives you full control of the pipe, and of the forked process. But you must cope with the child process by yourself.

When you call getProcessStatus blockingly, you must first ensure that all data has been read, or close the handle. Otherwise you'll get a deadlock. When you close the handle before all data has been read, then the child gets a SIGPIPE signal.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

Errors can only be detected by examining the child's process status (using getProcessStatus). No attempt is made to create more meaningful exceptions, like it is done by runprog/subproc. If the child action throws an exception, an error message is printed on stderr, and the child process exits with a ProcessStatus of Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

The pipe is set to text mode. This means that the Unicode characters in the text, which is read from stdin, is converted from the system character set to Unicode. The system character set is determined by the environment variable LANG. If you need to read binary data from the forked process, you can set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True.

Example:

(h,pid) <- h_pipe_from $ exec "/usr/bin/foo" ["bar"]

See exec, pipe_to, h_pipe_from2, pipe_from, lazy_pipe_from, chomp, silently. See HsShellScript for more details.

h_pipe_from2Source

Arguments

:: IO a

Action to run as a separate process, and to pipe from

-> IO (Handle, ProcessID)

Returns handle connected to the standard output of the child process, and the child's process ID

Run an IO action as a separate process, and connect to its stderr with a file handle.

This forks a subprocess, which executes the specified action. A file handle, which is connected to its stderr, is returned. The child's ProcessID is returned as well. If the action replaces the child process, by calling an exec variant, it is made sure that its file descriptor 2 is connected to the returned file handle.

This gives you full control of the pipe, and of the forked process. But you must cope with the child process by yourself.

When you call getProcessStatus blockingly, you must first ensure that all data has been read, or close the handle. Otherwise you'll get a deadlock. When you close the handle before all data has been read, then the child gets a SIGPIPE signal.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

Errors can only be detected by examining the child's process status (using getProcessStatus). No attempt is made to create more meaningful exceptions, like it is done by runprog/subproc. If the child action throws an exception, an error message is printed on stderr. This means that the message goes through the pipe to the parent process. Then the child process exits with a ProcessStatus of Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

The pipe is set to text mode. This means that the Unicode characters in the text, which is read from stdin, is converted from the system character set to Unicode. The system character set is determined by the environment variable LANG. If you need to read binary data from the forked process, you can set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True.

Example:

(h,pid) <- h_pipe_from $ exec "/usr/bin/foo" ["bar"]

See exec, pipe_from, pipe_from2, h_pipe_from, pipe_to, lazy_pipe_from, chomp, silently.

lazy_pipe_fromSource

Arguments

:: IO a

Action to run as a separate process

-> IO (String, ProcessID)

The action's lazy output and the process ID of the child process

Run an IO action in a separate process, and read its standard output, The output is read lazily, as the returned string is evaluated. The child's output along with its process ID are returned.

This forks a child process, which executes the specified action. The output of the child is read lazily through a pipe, which connncts to its standard output. In case the child replaces the process by calling an exec variant, it is make sure that the output is read from the new process' file descriptor 1.

lazy_pipe_from calls hGetContents, in order to read the pipe lazily. This means that the file handle goes to semi-closed state. The handle holds a file descriptor, and as long as the string isn't fully evaluated, this file descriptor won't be closed. For the file descriptor to be closed, first its standard output needs to be closed on the child side. This happens when the child explicitly closes it, or the child process exits. When afterwards the string on the parent side is completely evaluated, the handle, along with the file descritor it holds, are closed and freed.

If you use the string in such a way that you only access the beginning of the string, the handle will remain in semi-closed state, holding a file descriptor, even when the pipe is closed on the child side. When you do that repeatedly, you may run out of file descriptors.

Unless you're sure that your program will reach the string's end, you should take care for it explicitly, by doing something like this:

(output, pid) <- lazy_pipe_from (exec "\/usr\/bin\/foobar" [])
...
seq (length output) (return ())

This will read the entire standard output of the child, even if it isn't needed. You can't cut the child process' output short, when you use lazy_pipe_from. If you need to do this, you should use h_pipe_from, which gives you the handle, which can then be closed by hClose, even if the child's output isn't completed:

(h, pid) <- h_pipe_from io

-- Lazily read io's output
output <- hGetContents h
...
-- Not eveyting read yet, but cut io short.
hClose h

-- Wait for io to finish, and detect errors
(Just ps) <- System.Posix.getProcessStatus True False pid
when (ps /= Exited ExitSuccess) $
   throw ps

When you close the handle before all data has been read, then the child gets a SIGPIPE signal.

After all the output has been read, you should call getProcessStatus on the child's process ID, in order to detect errors. Be aware that you must evaluate the whole string, before calling getProcessStatus blockingly, or you'll get a deadlock.

You won't get an exception, if the child action exits in a way which indicates an error. Errors occur asynchronously, when the output string is evaluated. You must detect errors by yourself, by calling getProcessStatus.

In case the action doesn't replace the child process with an external program, an exception may be thrown out of the action. This results in an error message on stderr, and the proper termination of the child. The ProcessStatus, which can be accessed in the parent process by getProcessStatus, is Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

Unlike shells' backquote feature, lazy_pipe_from does not remove any trailing newline characters. The entire output of the action is returned. You might want to apply chomp to the result.

The pipe is set to text mode. This means that the Unicode characters in the text, which is read from the IO action's stdout, are converted from the system character set to Unicode. The system character set is determined by the environment variable LANG. If you need to read binary data from the forked process, you should use h_pipe_from and set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True. Then you can lazily read the output of the action from the handle.

Example: Lazily read binary data from an IO action. Don't forget to collect the child process later, using getProcessStatus True False pid.

(h, pid) <- h_pipe_from io
hSetBinaryMode h True
txt <- hGetContents h
...
(Just ps) <- System.Posix.getProcessStatus True False pid

See exec, pipe_to, pipe_from, h_pipe_from, lazy_pipe_from2, silently.

lazy_pipe_from2Source

Arguments

:: IO a

Action to run as a separate process

-> IO (String, ProcessID)

The action's lazy output and the process ID of the child process

Run an IO action in a separate process, and read its standard error output, The output is read lazily, as the returned string is evaluated. The child's error output along with its process ID are returned.

This forks a child process, which executes the specified action. The error output of the child is read lazily through a pipe, which connncts to its standard error output. In case the child replaces the process by calling an exec variant, it is make sure that the output is read from the new process' file descriptor 1.

lazy_pipe_from calls hGetContents, in order to read the pipe lazily. This means that the file handle goes to semi-closed state. The handle holds a file descriptor, and as long as the string isn't fully evaluated, this file descriptor won't be closed. For the file descriptor to be closed, first its standard error output needs to be closed on the child side. This happens when the child explicitly closes it, or the child process exits. When afterwards the string on the parent side is completely evaluated, the handle, along with the file descritor it holds, are closed and freed.

If you use the string in such a way that you only access the beginning of the string, the handle will remain in semi-closed state, holding a file descriptor, even when the pipe is closed on the child side. When you do that repeatedly, you may run out of file descriptors.

Unless you're sure that your program will reach the string's end, you should take care for it explicitly, by doing something like this:

(errmsg, pid) <- lazy_pipe_from2 (exec "/usr/bin/foobar" [])
...
seq (length errmsg) (return ())

This will read the entire standard error output of the child, even if it isn't needed. You can't cut the child process' output short, when you use lazy_pipe_from. If you need to do this, you should use h_pipe_from, which gives you the handle, which can then be closed by hClose, even if the child's output isn't completed:

(h, pid) <- h_pipe_from io

-- Lazily read io's output
output <- hGetContents h
...
-- Not eveyting read yet, but cut io short.
hClose h

-- Wait for io to finish, and detect errors
(Just ps) <- System.Posix.getProcessStatus True False pid
when (ps /= Exited ExitSuccess) $
   throw ps

When you close the handle before all data has been read, then the child gets a SIGPIPE signal.

After all the output has been read, you should call getProcessStatus on the child's process ID, in order to detect errors. Be aware that you must evaluate the whole string, before calling getProcessStatus blockingly, or you'll get a deadlock.

You won't get an exception, if the child action exits in a way which indicates an error. Errors occur asynchronously, when the output string is evaluated. You must detect errors by yourself, by calling getProcessStatus.

In case the action doesn't replace the child process with an external program, an exception may be thrown out of the action. This results in an error message on stderr. This means that the message is sent through the pipe, to the parent process. Then the child process is properly terminated. The ProcessStatus, which can be accessed in the parent process by getProcessStatus, is Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. The child process is then properly terminated, such that no resources, which have been duplicated by the fork, cause problems. See HsShellScript for details.

The pipe is set to text mode. This means that the Unicode characters in the text, which is read from stdin, is converted from the system character set to Unicode. The system character set is determined by the environment variable LANG. If you need to read binary data from the forked process, you can set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True.

Unlike shells' backquote feature, lazy_pipe_from does not remove any trailing newline characters. The entire output of the action is returned. You might want to apply chomp to the result.

The pipe is set to text mode. This means that the Unicode characters in the text, which is read from the IO action's stdout, are converted from the system character set to Unicode. The system character set is determined by the environment variable LANG. If you need to read binary data from the forked process' standard error output, you should use h_pipe_from2 and set the returned handle to binary mode. This is accomplished by hSetBinaryMode h True. Then you can lazily read the output of the action from the handle.

Example: Lazily read binary data from an IO action. Don't forget to collect the child process later, using getProcessStatus True False pid.

(h, pid) <- h_pipe_from2 io
hSetBinaryMode h True
txt <- hGetContents h
...
(Just ps) <- System.Posix.getProcessStatus True False pid

See exec, pipe_to, pipe_from2, h_pipe_from2, lazy_pipe_from, silently.

pipesSource

Arguments

:: IO a

Action to run in a new process

-> Bool

Whether to make stdin pipe

-> Bool

Whether to make stdout pipe

-> Bool

Whether to make stderr pipe

-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessID)

Pipes to the new process's stdin, stdout and stderr, if applicable; and its process id.

Run an IO action as a separate process, and optionally connect to its stdin, its stdout and its stderr output with pipes.

This forks a subprocess, which executes the specified action. The child's ProcessID is returned. Some of the action's standard handles are made to connected to pipes, which the caller can use in order to communicate with the new child process. Which, this is determined by the first three arguments.

You get full control of the pipes, and of the forked process. But you must cope with the child process by yourself.

Errors in the child process can only be detected by examining its process status (using getProcessStatus). If the child action throws an exception, an error message is printed on stderr, and the child process exits with a ProcessStatus of Exited (ExitFailure 1). The following exceptions are understood, and result in corresponding messages: ArgError, ProcessStatus, RunError, IOError and ExitCode. Other exceptions result in the generic message, as produced by show.

Unless you replace the child process, calling an exec variant, the child should let the control flow leave the action normally. It is then properly take care of.

The pipes are set to text mode. When connecting to the child's stdin, this means that the Unicode characters in the Haskell side text are converted to the system character set. When reading from the child's stdout or stderr, the text is converted from the system character set to Unicode in the Haskell-side strings. The system character set is determined by the environment variable LANG. If you need to read or write binary data, then this is no problem. Just call hSetBinaryMode handle True. This sets the corresponding pipe to binary mode.

See pipe_from, h_pipe_from, pipe_from2, h_pipe_from2, pipe_to, h_pipe_to, lazy_pipe_from, lazy_pipe_from2

_exitSource

Arguments

:: Int

Exit code

-> IO a

Never returns

Forcibly terminate the program, circumventing normal program shutdown.

This is the _exit(2) system call. No cleanup actions installed with bracket are performed, no data buffered by file handles is written out, etc.

strerrorSource

Arguments

:: Errno

errno value

-> IO String

Corresponding error message

Generate an error message from an errno value. This is the POSIX strerror system library function.

See the man page strerror(3).

errnoSource

Arguments

:: IO Errno

errno value

Read the global system error number. This is the POSIX errno value. This function is redundant. Use Foreign.C.Error.getErrno instead.

perror'Source

Arguments

:: Errno

errno error number

-> String

Text to precede the message, separated by ": "

-> IO () 

Print error message corresponding to the specified errno error number. This is similar to the POSIX system library function perror.

See the man page perror(3).

perrorSource

Arguments

:: String

Text to precede the message, separated by ": "

-> IO () 

Print error message corresponding to the global errno error number. This is the same as the POSIX system library function perror.

See the man page perror(3).

failIO :: String -> IO aSource

Print a message to stderr and exit with an exit code indicating an error.

failIO msg = hPutStrLn stderr msg >> exitFailure

exitcodeSource

Arguments

:: IO ()

Action to modify

-> IO ExitCode

Modified action

Modify an IO action to return the exit code of a failed program call, instead of throwing an exception.

This is used to modify the error reporting behaviour of an IO action which uses 'run'/'runprog' or 'call'/'subproc'. When an external program exits with an exit code which indicates an error, normally an exception is thrown. After exitcode has been applied, the exit code is retruned instead.

The caught exceptions are RunError and ProcessStatus. Termination by a signal is still reported by an exception, which is passed through.

Example: ec <- exitcode $ runprog "foo" ["bar"]

See runprog, subproc, run, call.

throwErrno'Source

Arguments

:: String

Description of the location where the error occurs in the program

-> Maybe Handle

Optional handle

-> Maybe FilePath

Optional file name (for failing operations on files)

-> IO a 

Create and throw an IOError from the current errno value, an optional handle and an optional file name.

This is an extended version of the Foreign.C.Error.throwErrno function from the GHC libraries, which additionally allows to specify a handle and a file name to include in the IOError thrown.

See Foreign.C.Error.throwErrno, Foreign.C.Error.errnoToIOError.

show_ioerror :: IOError -> StringSource

Convert an IOError to a string.

There is an instance declaration of IOError in Show in the GHC.IO library, but show_ioerror produces a more readable, and more complete, message.

system_throw :: String -> IO ()Source

Call the shell to execute a command. In case of an error, throw the ProcessStatus (such as (Exited (ExitFailure ec))) as an exception. This is like the Haskell standard library function system, except that error handling is brought in accordance with HsShellScript's scheme.

exitcode . system_throw is the same as the system function, except that when the called shell is terminated or stopped by a signal, this still lead to the ProcessStatus being thrown. The Haskell library report says nothing about what happens in this case, when using the system function.

system_throw cmd = run "/bin/sh" ["-c", "--", cmd]

This function is deprecated. You should rather use system_runprog, which provides for much better error reporting.

system_runprog :: String -> IO ()Source

Call the shell to execute a command. In case of an error, a RunError ist thrown. This is like the Haskell standard library function system, except that error handling is brought in accordance with HsShellScript's scheme. (It is not a front end to system.)

system_runprog cmd = runprog "/bin/sh" ["-c", "--", cmd]

Example: Call "foo" and report Errors as IOErrors, rather than RunErrors.

as_ioe $ system_runprog "foo" ["bar", "baz"]

See RunError, as_ioe

silentlySource

Arguments

:: IORef String

A mutable variable, which gets the output (stdout and stderr) of the action appended.

-> IO ()

The IO action to run.

-> IO () 

Run a subroutine as a child process, but don't let it produce any messages. Read its stdout and stderr instead, and append it to the contents of a mutable variable. The idea is that you can run some commands silently, and report them and their messages to the user only when something goes wrong.

If the child process terminates in a way which indicates an error, then the process status is thrown, in the same way as runprog does. If the subroutine throws an (Exited ec) exception (of type ProcessStatus), such as thrown by runprog, then the child process exits with the same exit code, such that the parent process reports it to the caller, again as a ProcessStatus exception.

When the subroutine finishes, the child process is terminated with _exit 0. When it throws an exception, an error message is printed and it is terminated with _exit 1. See HsShellScript for details.

The standard output (and the standard error output) of the parent process are flushed before the fork, such that no output appears twice.

Example:

let handler :: IORef String -> ProcessStatus -> IO ()
    handler msgref ps = do hPutStrLn stderr ("Command failed with " ++ show ps ++ ". Actions so far: ")
                           msg <- readIORef msgref
                           hPutStrLn stderr msg
                           exitWith (ExitFailure 1)

msgref <- newIORef ""
do silently msgref $ do putStrLn "Now doing foobar:"
                        echo exec "/foo/bar" ["arguments"]
   silently msgref $ echo exec "/bar/baz" ["arguments"]
`catch` (handler msgref)

See lazy_pipe_from, subproc, runprog, Data.IORef.

child :: IO a -> IO bSource

Modify a subroutine action in order to make it suitable to run as a child process.

This is used by functions like call, silently, pipe_to etc. The action is executed. When it returns, the (child) process is terminated with _exit 0 (after flushing stdout), circumventing normal program shutdown. When it throws an exception, an error message is printed and the (child) process is terminated with _exit 1.

outmSource

Arguments

:: String

Message to print

-> IO () 

Print text to stdout.

This is a shorthand for putStrLn, except for stderr being flushed beforehand. This way normal output and error output appear in order, even when they aren't buffered as by default.

An additional newline is printed at the end.

outm msg = do
   hFlush stderr
   putStrLn msg

outm_Source

Arguments

:: String

Message to print

-> IO () 

Print text to stdout.

This is a shorthand for putStr, except for stderr being flushed beforehand. This way normal output and error output appear in order, even when they aren't buffered as by default.

No newline is printed at the end.

outm_ msg = do
   hFlush stderr
   putStr msg

logmSource

Arguments

:: String

Message to print

-> IO () 

Colorful log message to stderr.

This prints a message to stderr. When stderr is connected to a terminal (as determined by isatty(3)), additional escape sequences are printed, which make the message appear in cyan. Additionally, a newline character is output at the end.

stdout is flushed beforehand. So normal output and error output appear in order, even when they aren't buffered as by default.

See logm_, errm, errm_.

logm_ :: String -> IO ()Source

Colorful log message to stderr.

This prints a message to stderr. When stderr is connected to a terminal (as determined by isatty(3)), additional escape sequences are printed, which make the message appear in cyan. No a newline character is output at the end.

stdout is flushed beforehand. So normal output and error output appear in order, even when they aren't buffered as by default.

See logm, errm, errm_.

errm :: String -> IO ()Source

Colorful error message to stderr.

This prints a message to stderr. When stderr is connected to a terminal (as determined by isatty(3)), additional escape sequences are printed, which make the message appear in red. Additionally, a newline character is output at the end.

stdout is flushed beforehand. So normal output and error output appear in order, even when they aren't buffered as by default.

See logm, logm_, errm_.

errm_ :: String -> IO ()Source

Colorful error message to stderr.

This prints a message to stderr. When stderr is connected to a terminal (as determined by isatty(3)), additional escape sequences are printed, which make the message appear in red. No a newline character is output at the end.

stdout is flushed beforehand. So normal output and error output appear in order, even when they aren't buffered as by default.

See logm, logm_, errm.

fill_in_filenameSource

Arguments

:: String

File name to fill in

-> IO a

IO action to modify

-> IO a

Modified IO action

In case the specified action throws an IOError, fill in its filename field. This way, more useful error messages can be produced.

Example:

-- Oh, the GHC libraries neglect to fill in the file name
executeFile' prog a b c =
   fill_in_filename prog $ executeFile prog a b c

See fill_in_location, add_location.

fill_in_locationSource

Arguments

:: String

Location name to fill in

-> IO a

IO action to modify

-> IO a

Modified IO action

In case the specified action throws an IOError, fill in its location field. This way, more useful error messages can be produced.

Example:

my_fun a b c = do
   -- ...
   fill_in_location "my_fun" $  -- Give the caller a more useful location information in case of failure
      rename "foo" "bar"
   -- ...

See fill_in_filename.

add_locationSource

Arguments

:: String

Location name to add

-> IO a

IO action to modify

-> IO a

Modified IO action

In case the specified action throws an IOError, add a line to its location field. This way, more useful error messages can be produced. The specified string is prepended to the old location, separating it with a newline from the previous location, if any. When using this thoroughly, you get a reverse call stack in IOErrors.

Example:

my_fun =
   add_location "my_fun" $ do
      -- ...

See fill_in_filename, fill_in_location.

execute_fileSource

Arguments

:: FilePath

Program to call

-> Bool

Search PATH?

-> [String]

Arguments

-> Maybe [(String, String)]

Optionally new environment

-> IO a

Never returns

This is a replacement for System.Posix.Process.executeFile. It does additional preparations, then calls executeFile. executeFile can't normally be used directly, because it doesn't do the things which are outlined here.

This are the differences to executeFile:

  1. stdout and stderr are flushed.
  2. The standard file descriptors 0-2 are made copies of the file descriptors which the standard handles currently use. This is necessary because they might no longer use the standard handles. See HsShellScript.

If the standard handles stdin, stdout, stderr aren't in closed state, and they aren't already connected to the respective standard file descriptors, their file descriptors are copied to the respective standard file descriptors (with dup2). Backup copies are made of the file descriptors which are overwritten. If some of the standard handles are closed, the corresponding standard file descriptors are closed as well.

  1. All file descriptors, except for the standard ones, are set to close-on-exec (see fcntl(2)), and will be closed on successful replacement of the process. Before that, the old file descriptor flags are saved.
  2. The standard file descriptors are set to blocking mode, since GHC 6.2.2 sets file descriptors to non-blocking (except 0-2, which may get overwritten by a non-blocking one in step 2). The called program doesn't expect that.
  3. In case replacing the process fails, the file descriptors are reset to the original state. The file descriptors flags are restored, and the file descriptors 0-2 are overwritten again, with their backup copies. Then an IOError is thrown.
  4. In any IOError, the program is filled in as the file name (executeFile neglects this).
  5. The return type is a generic a, rather than ().

Also see HsShellScript.

unsafeWithHandleFd' :: Handle -> MVar Handle__ -> (Fd -> IO a) -> IO aSource

isattySource

Arguments

:: Handle

Handle to check

-> IO Bool

Whether the handle is connected to a terminal

Check if a handle is connected to a terminal.

This is a front end to the isatty(3) function (see man page). It is useful, for instance, to determine if color escape sequences should be generated.