turtle-1.2.8: Shell programming, Haskell-style

Safe HaskellNone
LanguageHaskell2010

Turtle.Prelude

Contents

Description

This module provides a large suite of utilities that resemble Unix utilities.

Many of these commands are just existing Haskell commands renamed to match their Unix counterparts:

>>> :set -XOverloadedStrings
>>> cd "/tmp"
>>> pwd
FilePath "/tmp"

Some commands are Shells that emit streams of values. view prints all values in a Shell stream:

>>> view (ls "/usr")
FilePath "/usr/lib"
FilePath "/usr/src"
FilePath "/usr/sbin"
FilePath "/usr/include"
FilePath "/usr/share"
FilePath "/usr/games"
FilePath "/usr/local"
FilePath "/usr/bin"
>>> view (find (suffix "Browser.py") "/usr/lib")
FilePath "/usr/lib/python3.4/idlelib/ClassBrowser.py"
FilePath "/usr/lib/python3.4/idlelib/RemoteObjectBrowser.py"
FilePath "/usr/lib/python3.4/idlelib/PathBrowser.py"
FilePath "/usr/lib/python3.4/idlelib/ObjectBrowser.py"

Use fold to reduce the output of a Shell stream:

>>> import qualified Control.Foldl as Fold
>>> fold (ls "/usr") Fold.length
8
>>> fold (find (suffix "Browser.py") "/usr/lib") Fold.head
Just (FilePath "/usr/lib/python3.4/idlelib/ClassBrowser.py")

Create files using output:

>>> output "foo.txt" ("123" <|> "456" <|> "ABC")
>>> realpath "foo.txt"
FilePath "/tmp/foo.txt"

Read in files using input:

>>> stdout (input "foo.txt")
123
456
ABC

Format strings in a type safe way using format:

>>> dir <- pwd
>>> format ("I am in the "%fp%" directory") dir
"I am in the /tmp directory"

Commands like grep, sed and find accept arbitrary Patterns

>>> stdout (grep ("123" <|> "ABC") (input "foo.txt"))
123
ABC
>>> let exclaim = fmap (<> "!") (plus digit)
>>> stdout (sed exclaim (input "foo.txt"))
123!
456!
ABC

Note that grep and find differ from their Unix counterparts by requiring that the Pattern matches the entire line or file name by default. However, you can optionally match the prefix, suffix, or interior of a line:

>>> stdout (grep (has    "2") (input "foo.txt"))
123
>>> stdout (grep (prefix "1") (input "foo.txt"))
123
>>> stdout (grep (suffix "3") (input "foo.txt"))
123

You can also build up more sophisticated Shell programs using sh in conjunction with do notation:

{-# LANGUAGE OverloadedStrings #-}

import Turtle

main = sh example

example = do
    -- Read in file names from "files1.txt" and "files2.txt"
    file <- fmap fromText (input "files1.txt" <|> input "files2.txt")

    -- Stream each file to standard output only if the file exists
    True <- liftIO (testfile file)
    line <- input file
    liftIO (echo line)

See Turtle.Tutorial for an extended tutorial explaining how to use this library in greater detail.

Synopsis

IO

echo :: MonadIO io => Text -> io () Source

Print to stdout

err :: MonadIO io => Text -> io () Source

Print to stderr

readline :: MonadIO io => io (Maybe Text) Source

Read in a line from stdin

Returns Nothing if at end of input

readTextFile :: FilePath -> IO Text

Read in the entire content of a text file.

This computation throws IOError on failure. See “Classifying I/O errors” in the System.IO.Error documentation for information on why the failure occured.

writeTextFile :: FilePath -> Text -> IO ()

Replace the entire content of a text file with the provided Text.

This computation throws IOError on failure. See “Classifying I/O errors” in the System.IO.Error documentation for information on why the failure occured.

arguments :: MonadIO io => io [Text] Source

Get command line arguments in a list

export :: MonadIO io => Text -> Text -> io () Source

Set or modify an environment variable

unset :: MonadIO io => Text -> io () Source

Delete an environment variable

need :: MonadIO io => Text -> io (Maybe Text) Source

Look up an environment variable

env :: MonadIO io => io [(Text, Text)] Source

Retrieve all environment variables

cd :: MonadIO io => FilePath -> io () Source

Change the current directory

pwd :: MonadIO io => io FilePath Source

Get the current directory

home :: MonadIO io => io FilePath Source

Get the home directory

realpath :: MonadIO io => FilePath -> io FilePath Source

Canonicalize a path

mv :: MonadIO io => FilePath -> FilePath -> io () Source

Move a file or directory

Works if the two paths are on the same filesystem. If not, mv will still work when dealing with a regular file, but the operation will not be atomic

mkdir :: MonadIO io => FilePath -> io () Source

Create a directory

Fails if the directory is present

mktree :: MonadIO io => FilePath -> io () Source

Create a directory tree (equivalent to mkdir -p)

Does not fail if the directory is present

cp :: MonadIO io => FilePath -> FilePath -> io () Source

Copy a file

rm :: MonadIO io => FilePath -> io () Source

Remove a file

rmdir :: MonadIO io => FilePath -> io () Source

Remove a directory

rmtree :: MonadIO io => FilePath -> io () Source

Remove a directory tree (equivalent to rm -r)

Use at your own risk

testfile :: MonadIO io => FilePath -> io Bool Source

Check if a file exists

testdir :: MonadIO io => FilePath -> io Bool Source

Check if a directory exists

testpath :: MonadIO io => FilePath -> io Bool Source

Check if a path exists

date :: MonadIO io => io UTCTime Source

Get the current time

datefile :: MonadIO io => FilePath -> io UTCTime Source

Get the time a file was last modified

touch :: MonadIO io => FilePath -> io () Source

Touch a file, updating the access and modification times to the current time

Creates an empty file if it does not exist

time :: MonadIO io => io a -> io (a, NominalDiffTime) Source

Time how long a command takes in monotonic wall clock time

Returns the duration alongside the return value

hostname :: MonadIO io => io Text Source

Get the system's host name

sleep :: MonadIO io => NominalDiffTime -> io () Source

Sleep for the given duration

A numeric literal argument is interpreted as seconds. In other words, (sleep 2.0) will sleep for two seconds.

exit :: MonadIO io => ExitCode -> io a Source

Exit with the given exit code

An exit code of 0 indicates success

die :: MonadIO io => Text -> io a Source

Throw an exception using the provided Text message

(.&&.) :: Monad m => m ExitCode -> m ExitCode -> m ExitCode infixr 3 Source

Analogous to && in Bash

Runs the second command only if the first one returns ExitSuccess

(.||.) :: Monad m => m ExitCode -> m ExitCode -> m ExitCode infixr 2 Source

Analogous to || in Bash

Run the second command only if the first one returns ExitFailure

Managed

readonly :: MonadManaged managed => FilePath -> managed Handle Source

Acquire a Managed read-only Handle from a FilePath

writeonly :: MonadManaged managed => FilePath -> managed Handle Source

Acquire a Managed write-only Handle from a FilePath

appendonly :: MonadManaged managed => FilePath -> managed Handle Source

Acquire a Managed append-only Handle from a FilePath

mktemp Source

Arguments

:: MonadManaged managed 
=> FilePath

Parent directory

-> Text

File name template

-> managed (FilePath, Handle) 

Create a temporary file underneath the given directory

Deletes the temporary file when done

Note that this provides the Handle of the file in order to avoid a potential race condition from the file being moved or deleted before you have a chance to open the file. The mktempfile function provides a simpler API if you don't need to worry about that possibility.

mktempfile Source

Arguments

:: MonadManaged managed 
=> FilePath

Parent directory

-> Text

File name template

-> managed FilePath 

Create a temporary file underneath the given directory

Deletes the temporary file when done

mktempdir Source

Arguments

:: MonadManaged managed 
=> FilePath

Parent directory

-> Text

Directory name template

-> managed FilePath 

Create a temporary directory underneath the given directory

Deletes the temporary directory when done

fork :: MonadManaged managed => IO a -> managed (Async a) Source

Fork a thread, acquiring an Async value

wait :: Async a -> IO a

Wait for an asynchronous action to complete, and return its value. If the asynchronous action threw an exception, then the exception is re-thrown by wait.

wait = atomically . waitSTM

Shell

inproc Source

Arguments

:: Text

Command

-> [Text]

Arguments

-> Shell Text

Lines of standard input

-> Shell Text

Lines of standard output

Run a command using execvp, streaming stdout as lines of Text

The command inherits stderr for the current process

inshell Source

Arguments

:: Text

Command line

-> Shell Text

Lines of standard input

-> Shell Text

Lines of standard output

Run a command line using the shell, streaming stdout as lines of Text

This command is more powerful than inproc, but highly vulnerable to code injection if you template the command line with untrusted input

The command inherits stderr for the current process

inprocWithErr Source

Arguments

:: Text

Command

-> [Text]

Arguments

-> Shell Text

Lines of standard input

-> Shell (Either Text Text)

Lines of either standard output (Right) or standard error (Left)

Run a command using the shell, streaming stdout and stderr as lines of Text. Lines from stdout are wrapped in Right and lines from stderr are wrapped in Left. This does not throw an exception if the command returns a non-zero exit code

inshellWithErr Source

Arguments

:: Text

Command line

-> Shell Text

Lines of standard input

-> Shell (Either Text Text)

Lines of either standard output (Right) or standard error (Left)

Run a command line using the shell, streaming stdout and stderr as lines of Text. Lines from stdout are wrapped in Right and lines from stderr are wrapped in Left. This does not throw an exception if the command returns a non-zero exit code

This command is more powerful than inprocWithErr, but highly vulnerable to code injection if you template the command line with untrusted input

stdin :: Shell Text Source

Read lines of Text from standard input

input :: FilePath -> Shell Text Source

Read lines of Text from a file

inhandle :: Handle -> Shell Text Source

Read lines of Text from a Handle

stdout :: MonadIO io => Shell Text -> io () Source

Stream lines of Text to standard output

output :: MonadIO io => FilePath -> Shell Text -> io () Source

Stream lines of Text to a file

outhandle :: MonadIO io => Handle -> Shell Text -> io () Source

Stream lines of Text to a Handle

append :: MonadIO io => FilePath -> Shell Text -> io () Source

Stream lines of Text to append to a file

stderr :: MonadIO io => Shell Text -> io () Source

Stream lines of Text to standard error

strict :: MonadIO io => Shell Text -> io Text Source

Read in a stream's contents strictly

ls :: FilePath -> Shell FilePath Source

Stream all immediate children of the given directory, excluding "." and ".."

lsif :: (FilePath -> IO Bool) -> FilePath -> Shell FilePath Source

Stream all recursive descendents of the given directory

This skips any directories that fail the supplied predicate

lstree = lsif (\_ -> return True)

lstree :: FilePath -> Shell FilePath Source

Stream all recursive descendents of the given directory

cat :: [Shell a] -> Shell a Source

Combine the output of multiple Shells, in order

grep :: Pattern a -> Shell Text -> Shell Text Source

Keep all lines that match the given Pattern

sed :: Pattern Text -> Shell Text -> Shell Text Source

Replace all occurrences of a Pattern with its Text result

sed performs substitution on a line-by-line basis, meaning that substitutions may not span multiple lines. Additionally, substitutions may occur multiple times within the same line, like the behavior of s....../g.

Warning: Do not use a Pattern that matches the empty string, since it will match an infinite number of times. sed tries to detect such Patterns and die with an error message if they occur, but this detection is necessarily incomplete.

inplace :: MonadIO io => Pattern Text -> FilePath -> io () Source

Like sed, but operates in place on a FilePath (analogous to sed -i)

find :: Pattern a -> FilePath -> Shell FilePath Source

Search a directory recursively for all files matching the given Pattern

yes :: Shell Text Source

A Stream of "y"s

nl :: Num n => Shell a -> Shell (n, a) Source

Number each element of a Shell (starting at 0)

paste :: Shell a -> Shell b -> Shell (a, b) Source

Merge two Shells together, element-wise

If one Shell is longer than the other, the excess elements are truncated

endless :: Shell () Source

A Shell that endlessly emits ()

limit :: Int -> Shell a -> Shell a Source

Limit a Shell to a fixed number of values

limitWhile :: (a -> Bool) -> Shell a -> Shell a Source

Limit a Shell to values that satisfy the predicate

This terminates the stream on the first value that does not satisfy the predicate

cache :: (Read a, Show a) => FilePath -> Shell a -> Shell a Source

Cache a Shell's output so that repeated runs of the script will reuse the result of previous runs. You must supply a FilePath where the cached result will be stored.

The stored result is only reused if the Shell successfully ran to completion without any exceptions. Note: on some platforms Ctrl-C will flush standard input and signal end of file before killing the program, which may trick the program into "successfully" completing.

Folds

countChars :: Integral n => Fold Text n Source

Count the number of characters in the stream (like wc -c)

This uses the convention that the elements of the stream are implicitly ended by newlines that are one character wide

countWords :: Integral n => Fold Text n Source

Count the number of words in the stream (like wc -w)

countLines :: Integral n => Fold Text n Source

Count the number of lines in the stream (like wc -l)

This uses the convention that each element of the stream represents one line

Text

cut :: Pattern a -> Text -> [Text] Source

Split a line into chunks delimited by the given Pattern

Subprocess management

proc Source

Arguments

:: MonadIO io 
=> Text

Command

-> [Text]

Arguments

-> Shell Text

Lines of standard input

-> io ExitCode

Exit code

Run a command using execvp, retrieving the exit code

The command inherits stdout and stderr for the current process

shell Source

Arguments

:: MonadIO io 
=> Text

Command line

-> Shell Text

Lines of standard input

-> io ExitCode

Exit code

Run a command line using the shell, retrieving the exit code

This command is more powerful than proc, but highly vulnerable to code injection if you template the command line with untrusted input

The command inherits stdout and stderr for the current process

system Source

Arguments

:: MonadIO io 
=> CreateProcess

Command

-> Shell Text

Lines of standard input

-> io ExitCode

Exit code

system generalizes shell and proc by allowing you to supply your own custom CreateProcess. This is for advanced users who feel comfortable using the lower-level process API

procs Source

Arguments

:: MonadIO io 
=> Text

Command

-> [Text]

Arguments

-> Shell Text

Lines of standard input

-> io () 

This function is identical to proc except this throws ProcFailed for non-zero exit codes

shells Source

Arguments

:: MonadIO io 
=> Text

Command line

-> Shell Text

Lines of standard input

-> io ()

Exit code

This function is identical to shell except this throws ShellFailed for non-zero exit codes

procStrict Source

Arguments

:: MonadIO io 
=> Text

Command

-> [Text]

Arguments

-> Shell Text

Lines of standard input

-> io (ExitCode, Text)

Exit code and stdout

Run a command using execvp, retrieving the exit code and stdout as a non-lazy blob of Text

The command inherits stderr for the current process

shellStrict Source

Arguments

:: MonadIO io 
=> Text

Command line

-> Shell Text

Lines of standard input

-> io (ExitCode, Text)

Exit code and stdout

Run a command line using the shell, retrieving the exit code and stdout as a non-lazy blob of Text

This command is more powerful than proc, but highly vulnerable to code injection if you template the command line with untrusted input

The command inherits stderr for the current process

Permissions

chmod Source

Arguments

:: MonadIO io 
=> (Permissions -> Permissions)

Permissions update function

-> FilePath

Path

-> io Permissions

Updated permissions

Update a file or directory's user permissions

chmod rwo        "foo.txt"  -- chmod u=rw foo.txt
chmod executable "foo.txt"  -- chmod u+x foo.txt
chmod nonwritable "foo.txt" -- chmod u-x foo.txt

getmod :: MonadIO io => FilePath -> io Permissions Source

Get a file or directory's user permissions

setmod :: MonadIO io => Permissions -> FilePath -> io () Source

Set a file or directory's user permissions

copymod :: MonadIO io => FilePath -> FilePath -> io () Source

Copy a file or directory's permissions (analogous to chmod --reference)

File size

du :: MonadIO io => FilePath -> io Size Source

Get the size of a file or a directory

data Size Source

An abstract file size

Specify the units you want by using an accessor like kilobytes

The Num instance for Size interprets numeric literals as bytes

sz :: Format r (Size -> r) Source

Format a Size using a human readable representation

>>> format sz 42
"42 B"
>>> format sz 2309
"2.309 KB"
>>> format sz 949203
"949.203 MB"
>>> format sz 1600000000
"1.600 GB"
>>> format sz 999999999999999999
"999999.999 TB"

bytes :: Integral n => Size -> n Source

Extract a size in bytes

kilobytes :: Integral n => Size -> n Source

1 kilobyte = 1000 bytes

megabytes :: Integral n => Size -> n Source

1 megabyte = 1000 kilobytes

gigabytes :: Integral n => Size -> n Source

1 gigabyte = 1000 megabytes

terabytes :: Integral n => Size -> n Source

1 terabyte = 1000 gigabytes

kibibytes :: Integral n => Size -> n Source

1 kibibyte = 1024 bytes

mebibytes :: Integral n => Size -> n Source

1 mebibyte = 1024 kibibytes

gibibytes :: Integral n => Size -> n Source

1 gibibyte = 1024 mebibytes

tebibytes :: Integral n => Size -> n Source

1 tebibyte = 1024 gibibytes

Exceptions