Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 Shell
s 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 Pattern
s
>>>
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.
- proc :: MonadIO io => Text -> [Text] -> Shell Text -> io ExitCode
- shell :: MonadIO io => Text -> Shell Text -> io ExitCode
- procStrict :: MonadIO io => Text -> [Text] -> Shell Text -> io (ExitCode, Text)
- shellStrict :: MonadIO io => Text -> Shell Text -> io (ExitCode, Text)
- echo :: MonadIO io => Text -> io ()
- err :: MonadIO io => Text -> io ()
- readline :: MonadIO io => io (Maybe Text)
- arguments :: MonadIO io => io [Text]
- export :: MonadIO io => Text -> Text -> io ()
- unset :: MonadIO io => Text -> io ()
- need :: MonadIO io => Text -> io (Maybe Text)
- env :: MonadIO io => io [(Text, Text)]
- cd :: MonadIO io => FilePath -> io ()
- pwd :: MonadIO io => io FilePath
- home :: MonadIO io => io FilePath
- realpath :: MonadIO io => FilePath -> io FilePath
- mv :: MonadIO io => FilePath -> FilePath -> io ()
- mkdir :: MonadIO io => FilePath -> io ()
- mktree :: MonadIO io => FilePath -> io ()
- cp :: MonadIO io => FilePath -> FilePath -> io ()
- rm :: MonadIO io => FilePath -> io ()
- rmdir :: MonadIO io => FilePath -> io ()
- rmtree :: MonadIO io => FilePath -> io ()
- testfile :: MonadIO io => FilePath -> io Bool
- testdir :: MonadIO io => FilePath -> io Bool
- testpath :: MonadIO io => FilePath -> io Bool
- date :: MonadIO io => io UTCTime
- datefile :: MonadIO io => FilePath -> io UTCTime
- touch :: MonadIO io => FilePath -> io ()
- time :: MonadIO io => io a -> io (a, NominalDiffTime)
- hostname :: MonadIO io => io Text
- sleep :: MonadIO io => NominalDiffTime -> io ()
- exit :: MonadIO io => ExitCode -> io a
- die :: MonadIO io => Text -> io a
- (.&&.) :: Monad m => m ExitCode -> m ExitCode -> m ExitCode
- (.||.) :: Monad m => m ExitCode -> m ExitCode -> m ExitCode
- readonly :: FilePath -> Managed Handle
- writeonly :: FilePath -> Managed Handle
- appendonly :: FilePath -> Managed Handle
- mktemp :: FilePath -> Text -> Managed (FilePath, Handle)
- mktempfile :: FilePath -> Text -> Managed FilePath
- mktempdir :: FilePath -> Text -> Managed FilePath
- fork :: IO a -> Managed (Async a)
- wait :: Async a -> IO a
- inproc :: Text -> [Text] -> Shell Text -> Shell Text
- inshell :: Text -> Shell Text -> Shell Text
- inprocWithErr :: Text -> [Text] -> Shell Text -> Shell (Either Text Text)
- inshellWithErr :: Text -> Shell Text -> Shell (Either Text Text)
- stdin :: Shell Text
- input :: FilePath -> Shell Text
- inhandle :: Handle -> Shell Text
- stdout :: MonadIO io => Shell Text -> io ()
- output :: MonadIO io => FilePath -> Shell Text -> io ()
- outhandle :: MonadIO io => Handle -> Shell Text -> io ()
- append :: MonadIO io => FilePath -> Shell Text -> io ()
- stderr :: MonadIO io => Shell Text -> io ()
- strict :: MonadIO io => Shell Text -> io Text
- ls :: FilePath -> Shell FilePath
- lsif :: (FilePath -> IO Bool) -> FilePath -> Shell FilePath
- lstree :: FilePath -> Shell FilePath
- cat :: [Shell a] -> Shell a
- grep :: Pattern a -> Shell Text -> Shell Text
- sed :: Pattern Text -> Shell Text -> Shell Text
- inplace :: MonadIO io => Pattern Text -> FilePath -> io ()
- find :: Pattern a -> FilePath -> Shell FilePath
- yes :: Shell Text
- nl :: Num n => Shell a -> Shell (n, a)
- paste :: Shell a -> Shell b -> Shell (a, b)
- endless :: Shell ()
- limit :: Int -> Shell a -> Shell a
- limitWhile :: (a -> Bool) -> Shell a -> Shell a
- cache :: (Read a, Show a) => FilePath -> Shell a -> Shell a
- countChars :: Integral n => Fold Text n
- countWords :: Integral n => Fold Text n
- countLines :: Integral n => Fold Text n
- cut :: Pattern a -> Text -> [Text]
- data Permissions :: *
- chmod :: MonadIO io => (Permissions -> Permissions) -> FilePath -> io Permissions
- getmod :: MonadIO io => FilePath -> io Permissions
- setmod :: MonadIO io => Permissions -> FilePath -> io ()
- readable :: Permissions -> Permissions
- nonreadable :: Permissions -> Permissions
- writable :: Permissions -> Permissions
- nonwritable :: Permissions -> Permissions
- executable :: Permissions -> Permissions
- nonexecutable :: Permissions -> Permissions
- searchable :: Permissions -> Permissions
- nonsearchable :: Permissions -> Permissions
- ooo :: Permissions -> Permissions
- roo :: Permissions -> Permissions
- owo :: Permissions -> Permissions
- oox :: Permissions -> Permissions
- oos :: Permissions -> Permissions
- rwo :: Permissions -> Permissions
- rox :: Permissions -> Permissions
- ros :: Permissions -> Permissions
- owx :: Permissions -> Permissions
- rwx :: Permissions -> Permissions
- rws :: Permissions -> Permissions
- du :: MonadIO io => FilePath -> io Size
- data Size
- sz :: Format r (Size -> r)
- bytes :: Integral n => Size -> n
- kilobytes :: Integral n => Size -> n
- megabytes :: Integral n => Size -> n
- gigabytes :: Integral n => Size -> n
- terabytes :: Integral n => Size -> n
- kibibytes :: Integral n => Size -> n
- mebibytes :: Integral n => Size -> n
- gibibytes :: Integral n => Size -> n
- tebibytes :: Integral n => Size -> n
IO
:: 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
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
:: 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
:: 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
readline :: MonadIO io => io (Maybe Text) Source
Read in a line from stdin
Returns Nothing
if at end of input
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
mktree :: MonadIO io => FilePath -> io () Source
Create a directory tree (equivalent to mkdir -p
)
Does not fail if the directory is present
rmtree :: MonadIO io => FilePath -> io () Source
Remove a directory tree (equivalent to rm -r
)
Use at your own risk
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
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
(.&&.) :: 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
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.
Create a temporary file underneath the given directory
Deletes the temporary file when done
Create a temporary directory underneath the given directory
Deletes the temporary directory when done
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
:: 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
:: Text | Command line |
-> Shell Text | Lines of standard input |
-> Shell (Either Text Text) | Lines of standard output |
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 command is more powerful than inprocWithErr
, but highly vulnerable to
code injection if you template the command line with untrusted input
append :: MonadIO io => FilePath -> Shell Text -> io () Source
Stream lines of Text
to append to a file
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)
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 Pattern
s
and die
with an error message if they occur, but this detection is
necessarily incomplete.
find :: Pattern a -> FilePath -> Shell FilePath Source
Search a directory recursively for all files matching the given Pattern
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
Permissions
data Permissions :: *
:: 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
readable :: Permissions -> Permissions Source
+r
nonreadable :: Permissions -> Permissions Source
-r
writable :: Permissions -> Permissions Source
+w
nonwritable :: Permissions -> Permissions Source
-w
executable :: Permissions -> Permissions Source
+x
nonexecutable :: Permissions -> Permissions Source
-x
searchable :: Permissions -> Permissions Source
+s
nonsearchable :: Permissions -> Permissions Source
-s
ooo :: Permissions -> Permissions Source
-r -w -x
roo :: Permissions -> Permissions Source
+r -w -x
owo :: Permissions -> Permissions Source
-r +w -x
oox :: Permissions -> Permissions Source
-r -w +x
oos :: Permissions -> Permissions Source
-r -w +s
rwo :: Permissions -> Permissions Source
+r +w -x
rox :: Permissions -> Permissions Source
+r -w +x
ros :: Permissions -> Permissions Source
+r -w +s
owx :: Permissions -> Permissions Source
-r +w +x
rwx :: Permissions -> Permissions Source
+r +w +x
rws :: Permissions -> Permissions Source
+r +w +s