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.
Synopsis
- echo :: MonadIO io => Line -> io ()
- err :: MonadIO io => Line -> io ()
- readline :: MonadIO io => io (Maybe Line)
- readTextFile :: FilePath -> IO Text
- writeTextFile :: FilePath -> Text -> IO ()
- 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 ()
- cptree :: MonadIO io => FilePath -> FilePath -> io ()
- symlink :: 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
- which :: MonadIO io => FilePath -> io (Maybe FilePath)
- whichAll :: FilePath -> Shell FilePath
- 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 :: MonadManaged managed => FilePath -> managed Handle
- writeonly :: MonadManaged managed => FilePath -> managed Handle
- appendonly :: MonadManaged managed => FilePath -> managed Handle
- mktemp :: MonadManaged managed => FilePath -> Text -> managed (FilePath, Handle)
- mktempfile :: MonadManaged managed => FilePath -> Text -> managed FilePath
- mktempdir :: MonadManaged managed => FilePath -> Text -> managed FilePath
- fork :: MonadManaged managed => IO a -> managed (Async a)
- wait :: MonadIO io => Async a -> io a
- pushd :: MonadManaged managed => FilePath -> managed ()
- stdin :: Shell Line
- input :: FilePath -> Shell Line
- inhandle :: Handle -> Shell Line
- stdout :: MonadIO io => Shell Line -> io ()
- output :: MonadIO io => FilePath -> Shell Line -> io ()
- outhandle :: MonadIO io => Handle -> Shell Line -> io ()
- append :: MonadIO io => FilePath -> Shell Line -> io ()
- stderr :: MonadIO io => Shell Line -> io ()
- strict :: MonadIO io => Shell Line -> io Text
- ls :: FilePath -> Shell FilePath
- lsif :: (FilePath -> IO Bool) -> FilePath -> Shell FilePath
- lstree :: FilePath -> Shell FilePath
- lsdepth :: Int -> Int -> FilePath -> Shell FilePath
- cat :: [Shell a] -> Shell a
- grep :: Pattern a -> Shell Line -> Shell Line
- grepText :: Pattern a -> Shell Text -> Shell Text
- sed :: Pattern Text -> Shell Line -> Shell Line
- sedPrefix :: Pattern Text -> Shell Line -> Shell Line
- sedSuffix :: Pattern Text -> Shell Line -> Shell Line
- sedEntire :: Pattern Text -> Shell Line -> Shell Line
- onFiles :: (Shell Text -> Shell Text) -> Shell FilePath -> Shell FilePath
- inplace :: MonadIO io => Pattern Text -> FilePath -> io ()
- inplacePrefix :: MonadIO io => Pattern Text -> FilePath -> io ()
- inplaceSuffix :: MonadIO io => Pattern Text -> FilePath -> io ()
- inplaceEntire :: MonadIO io => Pattern Text -> FilePath -> io ()
- find :: Pattern a -> FilePath -> Shell FilePath
- findtree :: Pattern a -> Shell FilePath -> Shell FilePath
- yes :: Shell Line
- 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
- parallel :: [IO a] -> Shell a
- single :: MonadIO io => Shell a -> io a
- uniq :: Eq a => Shell a -> Shell a
- uniqOn :: Eq b => (a -> b) -> Shell a -> Shell a
- uniqBy :: (a -> a -> Bool) -> Shell a -> Shell a
- nub :: Ord a => Shell a -> Shell a
- nubOn :: Ord b => (a -> b) -> Shell a -> Shell a
- sort :: (Functor io, MonadIO io, Ord a) => Shell a -> io [a]
- sortOn :: (Functor io, MonadIO io, Ord b) => (a -> b) -> Shell a -> io [a]
- sortBy :: (Functor io, MonadIO io) => (a -> a -> Ordering) -> Shell a -> io [a]
- countChars :: Integral n => Fold Line n
- countWords :: Integral n => Fold Line n
- countLines :: Integral n => Fold Line n
- cut :: Pattern a -> Text -> [Text]
- proc :: MonadIO io => Text -> [Text] -> Shell Line -> io ExitCode
- shell :: MonadIO io => Text -> Shell Line -> io ExitCode
- procs :: MonadIO io => Text -> [Text] -> Shell Line -> io ()
- shells :: MonadIO io => Text -> Shell Line -> io ()
- inproc :: Text -> [Text] -> Shell Line -> Shell Line
- inshell :: Text -> Shell Line -> Shell Line
- inprocWithErr :: Text -> [Text] -> Shell Line -> Shell (Either Line Line)
- inshellWithErr :: Text -> Shell Line -> Shell (Either Line Line)
- procStrict :: MonadIO io => Text -> [Text] -> Shell Line -> io (ExitCode, Text)
- shellStrict :: MonadIO io => Text -> Shell Line -> io (ExitCode, Text)
- procStrictWithErr :: MonadIO io => Text -> [Text] -> Shell Line -> io (ExitCode, Text, Text)
- shellStrictWithErr :: MonadIO io => Text -> Shell Line -> io (ExitCode, Text, Text)
- system :: MonadIO io => CreateProcess -> Shell Line -> io ExitCode
- stream :: CreateProcess -> Shell Line -> Shell Line
- streamWithErr :: CreateProcess -> Shell Line -> Shell (Either Line Line)
- systemStrict :: MonadIO io => CreateProcess -> Shell Line -> io (ExitCode, Text)
- systemStrictWithErr :: MonadIO io => CreateProcess -> Shell Line -> io (ExitCode, Text, Text)
- data Permissions = Permissions {}
- chmod :: MonadIO io => (Permissions -> Permissions) -> FilePath -> io Permissions
- getmod :: MonadIO io => FilePath -> io Permissions
- setmod :: MonadIO io => Permissions -> FilePath -> io ()
- copymod :: MonadIO io => FilePath -> FilePath -> io ()
- readable :: Permissions -> Permissions
- nonreadable :: Permissions -> Permissions
- writable :: Permissions -> Permissions
- nonwritable :: Permissions -> Permissions
- executable :: Permissions -> Permissions
- nonexecutable :: Permissions -> Permissions
- ooo :: Permissions -> Permissions
- roo :: Permissions -> Permissions
- owo :: Permissions -> Permissions
- oox :: Permissions -> Permissions
- rwo :: Permissions -> Permissions
- rox :: Permissions -> Permissions
- owx :: Permissions -> Permissions
- rwx :: 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
- data FileStatus
- stat :: MonadIO io => FilePath -> io FileStatus
- lstat :: MonadIO io => FilePath -> io FileStatus
- fileSize :: FileStatus -> Size
- accessTime :: FileStatus -> POSIXTime
- modificationTime :: FileStatus -> POSIXTime
- statusChangeTime :: FileStatus -> POSIXTime
- isBlockDevice :: FileStatus -> Bool
- isCharacterDevice :: FileStatus -> Bool
- isNamedPipe :: FileStatus -> Bool
- isRegularFile :: FileStatus -> Bool
- isDirectory :: FileStatus -> Bool
- isSymbolicLink :: FileStatus -> Bool
- isSocket :: FileStatus -> Bool
- cmin :: MonadIO io => UTCTime -> FilePath -> io Bool
- cmax :: MonadIO io => UTCTime -> FilePath -> io Bool
- data WithHeader a
- header :: Shell a -> Shell (WithHeader a)
- data ProcFailed = ProcFailed {
- procCommand :: Text
- procArguments :: [Text]
- procExitCode :: ExitCode
- data ShellFailed = ShellFailed {}
IO
echo :: MonadIO io => Line -> io () Source #
Print exactly one line to stdout
To print more than one line see printf
, which also supports
formatted output
readline :: MonadIO io => io (Maybe Line) 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.
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
symlink :: MonadIO io => FilePath -> FilePath -> io () Source #
Create a symlink from one FilePath
to another
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
which :: MonadIO io => FilePath -> io (Maybe FilePath) Source #
Show the full path of an executable file
whichAll :: FilePath -> Shell FilePath Source #
Show all matching executables in PATH, not just the first
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
appendonly :: MonadManaged managed => FilePath -> managed Handle Source #
:: 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.
:: 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
:: 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
pushd :: MonadManaged managed => FilePath -> managed () Source #
Change the current directory. Once the current Shell
is done, it returns
back to the original directory.
>>>
:set -XOverloadedStrings
>>>
cd "/"
>>>
view (pushd "/tmp" >> pwd)
FilePath "/tmp">>>
pwd
FilePath "/"
Shell
append :: MonadIO io => FilePath -> Shell Line -> 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)
lstree :: FilePath -> Shell FilePath Source #
Stream all recursive descendents of the given directory
lsdepth :: Int -> Int -> FilePath -> Shell FilePath Source #
Stream the recursive descendents of a given directory between a given minimum and maximum depth
sed :: Pattern Text -> Shell Line -> Shell Line 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.
sedPrefix :: Pattern Text -> Shell Line -> Shell Line Source #
Like sed
, but the provided substitution must match the beginning of the
line
sedSuffix :: Pattern Text -> Shell Line -> Shell Line Source #
Like sed
, but the provided substitution must match the end of the line
sedEntire :: Pattern Text -> Shell Line -> Shell Line Source #
Like sed
, but the provided substitution must match the entire line
find :: Pattern a -> FilePath -> Shell FilePath Source #
Search a directory recursively for all files matching the given Pattern
findtree :: Pattern a -> Shell FilePath -> Shell FilePath Source #
Filter a shell of FilePaths according to a 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.
parallel :: [IO a] -> Shell a Source #
Run a list of IO actions in parallel using fork and wait.
>>>
view (parallel [(sleep 3) >> date, date, date])
2016-12-01 17:22:10.83296 UTC 2016-12-01 17:22:07.829876 UTC 2016-12-01 17:22:07.829963 UTC
uniq :: Eq a => Shell a -> Shell a Source #
Filter adjacent duplicate elements:
>>>
view (uniq (select [1,1,2,1,3]))
1 2 1 3
uniqOn :: Eq b => (a -> b) -> Shell a -> Shell a Source #
Filter adjacent duplicates determined after applying the function to the element:
>>>
view (uniqOn fst (select [(1,'a'),(1,'b'),(2,'c'),(1,'d'),(3,'e')]))
(1,'a') (2,'c') (1,'d') (3,'e')
uniqBy :: (a -> a -> Bool) -> Shell a -> Shell a Source #
Filter adjacent duplicate elements determined via the given function:
>>>
view (uniqBy (==) (select [1,1,2,1,3]))
1 2 1 3
sort :: (Functor io, MonadIO io, Ord a) => Shell a -> io [a] Source #
Return a list of the sorted elements of the given Shell
, keeping duplicates:
>>>
sort (select [1,4,2,3,3,7])
[1,2,3,3,4,7]
sortOn :: (Functor io, MonadIO io, Ord b) => (a -> b) -> Shell a -> io [a] Source #
Return a list of the elements of the given Shell
, sorted after applying the given function and keeping duplicates:
>>>
sortOn id (select [1,4,2,3,3,7])
[1,2,3,3,4,7]
sortBy :: (Functor io, MonadIO io) => (a -> a -> Ordering) -> Shell a -> io [a] Source #
Return a list of the elements of the given Shell
, sorted by the given function and keeping duplicates:
>>>
sortBy (comparing fst) (select [(1,'a'),(4,'b'),(2,'c'),(3,'d'),(3,'e'),(7,'f')])
[(1,'a'),(2,'c'),(3,'d'),(3,'e'),(4,'b'),(7,'f')]
Folds
countChars :: Integral n => Fold Line 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 Line n Source #
Count the number of words in the stream (like wc -w
)
countLines :: Integral n => Fold Line 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
Subprocess management
:: MonadIO io | |
=> Text | Command |
-> [Text] | Arguments |
-> Shell Line | 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
This function is identical to proc
except this throws ProcFailed
for
non-zero exit codes
This function is identical to shell
except this throws ShellFailed
for
non-zero exit codes
:: Text | Command |
-> [Text] | Arguments |
-> Shell Line | Lines of standard input |
-> Shell Line | Lines of standard output |
Run a command using execvp
, streaming stdout
as lines of Text
The command inherits stderr
for the current process
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
Throws an ExitCode
exception if the command returns a non-zero exit code
:: Text | Command line |
-> Shell Line | Lines of standard input |
-> Shell (Either Line Line) | Lines of either 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
Throws an ExitCode
exception if the command returns a non-zero exit code
:: MonadIO io | |
=> Text | Command |
-> [Text] | Arguments |
-> Shell Line | 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 Line | 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
:: MonadIO io | |
=> Text | Command |
-> [Text] | Arguments |
-> Shell Line | Lines of standard input |
-> io (ExitCode, Text, Text) | (Exit code, stdout, stderr) |
Run a command using execvp
, retrieving the exit code, stdout, and stderr
as a non-lazy blob of Text
:: MonadIO io | |
=> Text | Command line |
-> Shell Line | Lines of standard input |
-> io (ExitCode, Text, Text) | (Exit code, stdout, stderr) |
Run a command line using the shell, retrieving the exit code, stdout, and stderr 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
:: MonadIO io | |
=> CreateProcess | Command |
-> Shell Line | Lines of standard input |
-> io ExitCode | Exit code |
:: CreateProcess | Command |
-> Shell Line | Lines of standard input |
-> Shell Line | Lines of standard output |
:: CreateProcess | Command |
-> Shell Line | Lines of standard input |
-> Shell (Either Line Line) | Lines of standard output |
streamWithErr
generalizes inprocWithErr
and inshellWithErr
by allowing
you to supply your own custom CreateProcess
. This is for advanced users
who feel comfortable using the lower-level process
API
Throws an ExitCode
exception if the command returns a non-zero exit code
:: MonadIO io | |
=> CreateProcess | Command |
-> Shell Line | Lines of standard input |
-> io (ExitCode, Text) | Exit code and stdout |
systemStrict
generalizes shellStrict
and procStrict
by allowing you to
supply your own custom CreateProcess
. This is for advanced users who feel
comfortable using the lower-level process
API
:: MonadIO io | |
=> CreateProcess | Command |
-> Shell Line | Lines of standard input |
-> io (ExitCode, Text, Text) | Exit code and stdout |
systemStrictWithErr
generalizes shellStrictWithErr
and
procStrictWithErr
by allowing you to supply your own custom
CreateProcess
. This is for advanced users who feel comfortable using
the lower-level process
API
Permissions
data Permissions Source #
This type is the same as System.Directory.
type except combining the Permissions
executable
and
searchable
fields into a single executable
field for
consistency with the Unix chmod
. This simplification is still entirely
consistent with the behavior of System.Directory, which treats the two
fields as interchangeable.
Instances
Eq Permissions Source # | |
Defined in Turtle.Prelude (==) :: Permissions -> Permissions -> Bool # (/=) :: Permissions -> Permissions -> Bool # | |
Ord Permissions Source # | |
Defined in Turtle.Prelude compare :: Permissions -> Permissions -> Ordering # (<) :: Permissions -> Permissions -> Bool # (<=) :: Permissions -> Permissions -> Bool # (>) :: Permissions -> Permissions -> Bool # (>=) :: Permissions -> Permissions -> Bool # max :: Permissions -> Permissions -> Permissions # min :: Permissions -> Permissions -> Permissions # | |
Read Permissions Source # | |
Defined in Turtle.Prelude readsPrec :: Int -> ReadS Permissions # readList :: ReadS [Permissions] # readPrec :: ReadPrec Permissions # readListPrec :: ReadPrec [Permissions] # | |
Show Permissions Source # | |
Defined in Turtle.Prelude showsPrec :: Int -> Permissions -> ShowS # show :: Permissions -> String # showList :: [Permissions] -> ShowS # |
:: 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-w foo.txt
The meaning of each permission is:
readable
(+r
for short): For files, determines whether you can read from that file (such as withinput
). For directories, determines whether or not you can list the directory contents (such as withls
). Note: if a directory is not readable thenls
will stream an empty list of contentswritable
(+w
for short): For files, determines whether you can write to that file (such as withoutput
). For directories, determines whether you can create a new file underneath that directory.executable
(+x
for short): For files, determines whether or not that file is executable (such as withproc
). For directories, determines whether or not you can read or execute files underneath that directory (such as withinput
orproc
)
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
)
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
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
rwo :: Permissions -> Permissions Source #
+r +w -x
rox :: Permissions -> Permissions Source #
+r -w +x
owx :: Permissions -> Permissions Source #
-r +w +x
rwx :: Permissions -> Permissions Source #
+r +w +x
File size
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
File status
data FileStatus #
POSIX defines operations to get information, such as owner, permissions,
size and access times, about a file. This information is represented by the
FileStatus
type.
Note: see chmod
.
lstat :: MonadIO io => FilePath -> io FileStatus Source #
Get the status of a file, but don't follow symbolic links
fileSize :: FileStatus -> Size Source #
Size of the file in bytes. Does not follow symlinks
accessTime :: FileStatus -> POSIXTime Source #
Time of last access
modificationTime :: FileStatus -> POSIXTime Source #
Time of last modification
statusChangeTime :: FileStatus -> POSIXTime Source #
Time of last status change (i.e. owner, group, link count, mode, etc.)
isBlockDevice :: FileStatus -> Bool #
Checks if this file is a block device.
isCharacterDevice :: FileStatus -> Bool #
Checks if this file is a character device.
isNamedPipe :: FileStatus -> Bool #
Checks if this file is a named pipe device.
isRegularFile :: FileStatus -> Bool #
Checks if this file is a regular file device.
isDirectory :: FileStatus -> Bool #
Checks if this file is a directory device.
isSymbolicLink :: FileStatus -> Bool #
Checks if this file is a symbolic link device.
isSocket :: FileStatus -> Bool #
Checks if this file is a socket device.
cmin :: MonadIO io => UTCTime -> FilePath -> io Bool Source #
Check if a file was last modified after a given timestamp
cmax :: MonadIO io => UTCTime -> FilePath -> io Bool Source #
Check if a file was last modified before a given timestamp
Headers
data WithHeader a Source #
Header a | The first line with the header |
Row a a | Every other line: 1st element is header, 2nd element is original row |
Instances
Show a => Show (WithHeader a) Source # | |
Defined in Turtle.Prelude showsPrec :: Int -> WithHeader a -> ShowS # show :: WithHeader a -> String # showList :: [WithHeader a] -> ShowS # |
Exceptions
data ProcFailed Source #
ProcFailed | |
|
Instances
Show ProcFailed Source # | |
Defined in Turtle.Prelude showsPrec :: Int -> ProcFailed -> ShowS # show :: ProcFailed -> String # showList :: [ProcFailed] -> ShowS # | |
Exception ProcFailed Source # | |
Defined in Turtle.Prelude toException :: ProcFailed -> SomeException # fromException :: SomeException -> Maybe ProcFailed # displayException :: ProcFailed -> String # |
data ShellFailed Source #
Instances
Show ShellFailed Source # | |
Defined in Turtle.Prelude showsPrec :: Int -> ShellFailed -> ShowS # show :: ShellFailed -> String # showList :: [ShellFailed] -> ShowS # | |
Exception ShellFailed Source # | |
Defined in Turtle.Prelude |