shellish-0.1.4: shell-/perl- like (systems) programming in Haskell

Shellish

Contents

Description

A module for shell-like / perl-like programming in Haskell. The stuff in here is not pretty, but it does get job done. The functionality provided by this module is (unlike standard Haskell filesystem functionality) thread-safe: each ShIO maintains its own environment and its own working directory.

Synopsis

Entering ShIO.

type ShIO a = ReaderT (IORef St) IO aSource

shellish :: MonadIO m => ShIO a -> m aSource

Enter a ShIO from (Monad)IO. The environment and working directories are inherited from the current process-wide values. Any subsequent changes in processwide working directory or environment are not reflected in the running ShIO.

sub :: ShIO a -> ShIO aSource

Enter a sub-ShIO. The new ShIO inherits the environment and working directory from the current one, but the sub-ShIO cannot affect the current one. Exceptions are propagated normally.

silently :: ShIO a -> ShIO aSource

Create a sub-ShIO in which external command outputs are not echoed. See sub.

verbosely :: ShIO a -> ShIO aSource

Create a sub-ShIO in which external command outputs are echoed. See sub.

Modifying and querying environment.

setenv :: String -> String -> ShIO ()Source

Set an environment variable. The environment is maintained in ShIO internally, and is passed to any external commands to be executed.

getenv :: String -> ShIO StringSource

Fetch the current value of an environment variable. Both empty and non-existent variables give empty string as a result.

cd :: FilePath -> ShIO ()Source

Change current working directory of ShIO. This does *not* change the working directory of the process we are running it. Instead, ShIO keeps track of its own workking directory and builds absolute paths internally instead of passing down relative paths. This may have performance repercussions if you are doing hundreds of thousands of filesystem operations. You will want to handle these issues differently in those cases.

pwd :: ShIO StringSource

Obtain the current (ShIO) working directory.

Printing & stuff.

echo_n :: String -> ShIO ()Source

Echo string to standard (error, when using _err variants) output. The _n variants do not print a final newline.

Querying filesystem.

ls :: FilePath -> ShIO [String]Source

List directory contents. Does *not* include "." and "..", but it does include (other) hidden files.

test_e :: FilePath -> ShIO BoolSource

Does a path point to an existing filesystem object?

test_f :: FilePath -> ShIO BoolSource

Does a path point to an existing file?

test_d :: FilePath -> ShIO BoolSource

Does a path point to an existing directory?

test_s :: FilePath -> ShIO BoolSource

Does a path point to a symlink?

which :: String -> ShIO (Maybe FilePath)Source

Get a full path to an executable on PATH, if exists. FIXME does not respect setenv'd environment and uses PATH inherited from the process environment.

find :: FilePath -> ShIO [String]Source

List directory recursively (like the POSIX utility find).

Manipulating filesystem.

mv :: FilePath -> FilePath -> ShIO ()Source

Currently a renameFile wrapper. TODO: Support cross-filesystem move. TODO: Support directory paths in the second parameter, like in cp.

rm_f :: FilePath -> ShIO ()Source

Remove a file. Does not fail if the file already is not there. Does fail if the file is not a file.

rm_rf :: FilePath -> ShIO ()Source

A swiss army cannon for removing things. Actually this goes farther than a normal rm -rf, as it will circumvent permission problems for the files we own. Use carefully.

cp :: FilePath -> FilePath -> ShIO ()Source

Copy a file. The second path could be a directory, in which case the original file name is used, in that directory.

cp_r :: FilePath -> FilePath -> ShIO ()Source

Copy a file, or a directory recursively.

mkdir :: FilePath -> ShIO ()Source

Create a new directory (fails if the directory exists).

mkdir_p :: FilePath -> ShIO ()Source

Create a new directory, including parents (succeeds if the directory already exists).

readfile :: FilePath -> ShIO StringSource

(Strictly) read file into a String.

writefile :: FilePath -> String -> ShIO ()Source

Write a String to a file.

appendfile :: FilePath -> String -> ShIO ()Source

Append a String to a file.

withTmpDir :: (FilePath -> ShIO a) -> ShIO aSource

Create a temporary directory and pass it as a parameter to a ShIO computation. The directory is nuked afterwards.

Running external commands.

run :: String -> [String] -> ShIO StringSource

Execute an external command. Takes the command name (no shell allowed, just a name of something that can be found via PATH; FIXME: setenv'd PATH is not taken into account, only the one inherited from the actual outside environment). Nothing is provided on stdin of the process, and stdout and stderr are collected and stored. The stdout is returned as a result of run, and complete outputs are available after the fact using lastStdout, lastStderr and lastOutput with the last giving an interleaving of both, approximately reflecting the times of their arrival -- basically what 2>&1 would give you in a shell.

(#) :: String -> [String] -> ShIO StringSource

An infix shorthand for run. Write "command" # [ "argument" ... ].

lastStderr :: ShIO ByteStringSource

The output of last external command. See run.

Utilities.

(</>) :: FilePath -> FilePath -> FilePath

A nice alias for combine.

(<.>) :: FilePath -> String -> FilePath

Alias to addExtension, for people who like that sort of thing.

(<$>) :: Functor f => (a -> b) -> f a -> f b

An infix synonym for fmap.

(<$$>) :: Functor m => (b -> c) -> (a -> m b) -> a -> m cSource

A functor-lifting function composition.

grep :: PredicateLike pattern hay => pattern -> [hay] -> [hay]Source

Like filter, but more conveniently used with String lists, where a substring match (TODO: also provide regexps, and maybe globs) is expressed as grep "needle" [ "the", "stack", "of", "hay" ]. Boolean predicates just like with filter are supported too: grep ("fun" isPrefixOf) [...].

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

A monadic-conditional version of the when guard.

canonic :: FilePath -> ShIO FilePathSource

Obtain a (reasonably) canonic file path to a filesystem object. Based on canonicalizePath in System.FilePath.

catch_sh :: Exception e => ShIO a -> (e -> ShIO a) -> ShIO aSource

Catch an exception in the ShIO monad.

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

time :: ShIO a -> ShIO (MemTime, a)Source

Run a ShIO computation and collect timing (TODO: and memory) information.

catchany :: IO a -> (SomeException -> IO a) -> IO aSource

A helper to catch any exception (same as ... catch (e :: SomeException) -> ...).