turtle-1.5.25: Shell programming, Haskell-style
Safe HaskellNone
LanguageHaskell2010

Turtle.Prelude

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 => Line -> io () Source #

Print exactly one line to stdout

To print more than one line see printf, which also supports formatted output

err :: MonadIO io => Line -> io () Source #

Print exactly one line to stderr

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.

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

Note: This will change the current environment for all of your program's threads since this modifies the global state of the process

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

Note: This will change the current directory for all of your program's threads since this modifies the global state of the process

pwd :: MonadIO io => io FilePath Source #

Get the current directory

home :: MonadIO io => io FilePath Source #

Get the home directory

readlink :: MonadIO io => FilePath -> io FilePath Source #

Get the path pointed to by a symlink

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

cptree :: MonadIO io => FilePath -> FilePath -> io () Source #

Copy a directory tree and preserve symbolic links

cptreeL :: MonadIO io => FilePath -> FilePath -> io () Source #

Copy a directory tree and dereference symbolic links

symlink :: MonadIO io => FilePath -> FilePath -> io () Source #

Create a symlink from one FilePath to another

isNotSymbolicLink :: MonadIO io => FilePath -> io Bool Source #

Returns True if the given FilePath is not a symbolic link

This comes in handy in conjunction with lsif:

lsif isNotSymbolicLink

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

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

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 :: MonadIO io => Async a -> io a Source #

Wait for an Async action to complete

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

stdin :: Shell Line Source #

Read lines of Text from standard input

input :: FilePath -> Shell Line Source #

Read lines of Text from a file

inhandle :: Handle -> Shell Line Source #

Read lines of Text from a Handle

stdout :: MonadIO io => Shell Line -> io () Source #

Stream lines of Text to standard output

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

Stream lines of Text to a file

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

Stream lines of Text to a Handle

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

Stream lines of Text to append to a file

stderr :: MonadIO io => Shell Line -> io () Source #

Stream lines of Text to standard error

strict :: MonadIO io => Shell Line -> 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

lsdepth :: Int -> Int -> FilePath -> Shell FilePath Source #

Stream the recursive descendents of a given directory between a given minimum and maximum depth

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

Combine the output of multiple Shells, in order

grep :: Pattern a -> Shell Line -> Shell Line Source #

Keep all lines that match the given Pattern

grepText :: Pattern a -> Shell Text -> Shell Text Source #

Keep every Text element that matches the given Pattern

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 Patterns 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

onFiles :: (Shell Text -> Shell Text) -> Shell FilePath -> Shell FilePath Source #

Make a `Shell Text -> Shell Text` function work on FilePaths instead. | Ignores any paths which cannot be decoded as valid Text.

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

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

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

Like sedPrefix, but operates in place on a FilePath

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

Like sedSuffix, but operates in place on a FilePath

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

Like sedEntire, but operates in place on a FilePath

update :: MonadIO io => (Shell Line -> Shell Line) -> FilePath -> io () Source #

Update a file in place using a Shell transformation

For example, this is used to implement the inplace* family of utilities

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

yes :: Shell Line 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

NOTE: This is not lazy and will still consume the entire input stream. There is no way to implement a lazy version of this utility.

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

single :: MonadIO io => Shell a -> io a Source #

Returns the result of a Shell that outputs a single line. Note that if no lines / more than 1 line is produced by the Shell, this function will die with an error message.

main = do
  directory <- single (inshell "pwd" empty)
  print directory

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

nub :: Ord a => Shell a -> Shell a Source #

Return a new Shell that discards duplicates from the input Shell:

>>> view (nub (select [1, 1, 2, 3, 3, 4, 3]))
1
2
3
4

nubOn :: Ord b => (a -> b) -> Shell a -> Shell a Source #

Return a new Shell that discards duplicates determined via the given function from the input Shell:

>>> view (nubOn id (select [1, 1, 2, 3, 3, 4, 3]))
1
2
3
4

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')]

toLines :: Shell Text -> Shell Line Source #

Group an arbitrary stream of Text into newline-delimited Lines

>>> stdout (toLines ("ABC" <|> "DEF" <|> "GHI")
ABCDEFGHI
>>> stdout (toLines empty)  -- Note that this always emits at least 1 `Line`
>>> stdout (toLines ("ABC\nDEF" <|> "" <|> "GHI\nJKL"))
ABC
DEFGHI
JKL

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

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 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

shell Source #

Arguments

:: MonadIO io 
=> Text

Command line

-> Shell Line

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

procs Source #

Arguments

:: MonadIO io 
=> Text

Command

-> [Text]

Arguments

-> Shell Line

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 Line

Lines of standard input

-> io ()

Exit code

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

inproc Source #

Arguments

:: 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

inshell Source #

Arguments

:: Text

Command line

-> Shell Line

Lines of standard input

-> Shell Line

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

Throws an ExitCode exception if the command returns a non-zero exit code

inprocWithErr Source #

Arguments

:: Text

Command

-> [Text]

Arguments

-> Shell Line

Lines of standard input

-> Shell (Either Line Line)

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.

Throws an ExitCode exception if the command returns a non-zero exit code

inshellWithErr Source #

Arguments

:: Text

Command line

-> Shell Line

Lines of standard input

-> Shell (Either Line Line)

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 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

procStrict Source #

Arguments

:: 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

shellStrict Source #

Arguments

:: 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

procStrictWithErr Source #

Arguments

:: 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

shellStrictWithErr Source #

Arguments

:: 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

system Source #

Arguments

:: MonadIO io 
=> CreateProcess

Command

-> Shell Line

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

stream Source #

Arguments

:: CreateProcess

Command

-> Shell Line

Lines of standard input

-> Shell Line

Lines of standard output

stream generalizes inproc and inshell 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

streamWithErr Source #

Arguments

:: 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

systemStrict Source #

Arguments

:: 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

systemStrictWithErr Source #

Arguments

:: 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.Permissions type except combining the 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.

Constructors

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-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 with input). For directories, determines whether or not you can list the directory contents (such as with ls). Note: if a directory is not readable then ls will stream an empty list of contents
  • writable (+w for short): For files, determines whether you can write to that file (such as with output). 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 with proc). For directories, determines whether or not you can read or execute files underneath that directory (such as with input or proc)

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 where 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

Bundled Patterns

pattern B :: Integral n => n -> Size

Construct a Size from an integer in bytes

>>> format sz (B 42)
"42 B"
pattern KB :: Integral n => n -> Size

Construct a Size from an integer in kilobytes

>>> format sz (KB 42)
"42.0 KB"
>>> let B n = KB 1 in n
1000
pattern MB :: Integral n => n -> Size

Construct a Size from an integer in megabytes

>>> format sz (MB 42)
"42.0 MB"
>>> let KB n = MB 1 in n
1000
pattern GB :: Integral n => n -> Size

Construct a Size from an integer in gigabytes

>>> format sz (GB 42)
"42.0 GB"
>>> let MB n = GB 1 in n
1000
pattern TB :: Integral n => n -> Size

Construct a Size from an integer in terabytes

>>> format sz (TB 42)
"42.0 TB"
>>> let GB n = TB 1 in n
1000
pattern KiB :: Integral n => n -> Size

Construct a Size from an integer in kibibytes

>>> format sz (KiB 42)
"43.8 KB"
>>> let B n = KiB 1 in n
1024
pattern MiB :: Integral n => n -> Size

Construct a Size from an integer in mebibytes

>>> format sz (MiB 42)
"44.40 MB"
>>> let KiB n = MiB 1 in n
1024
pattern GiB :: Integral n => n -> Size

Construct a Size from an integer in gibibytes

>>> format sz (GiB 42)
"45.97 GB"
>>> let MiB n = GiB 1 in n
1024
pattern TiB :: Integral n => n -> Size

Construct a Size from an integer in tebibytes

>>> format sz (TiB 42)
"46.179 TB"
>>> let GiB n = TiB 1 in n
1024

Instances

Instances details
Eq Size Source # 
Instance details

Defined in Turtle.Prelude

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Num Size Source # 
Instance details

Defined in Turtle.Prelude

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 
Instance details

Defined in Turtle.Prelude

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Show Size Source # 
Instance details

Defined in Turtle.Prelude

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

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 KB"
>>> 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

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.

stat :: MonadIO io => FilePath -> io FileStatus Source #

Get the status of a file

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 #

Constructors

Header a

The first line with the header

Row a a

Every other line: 1st element is header, 2nd element is original row

Instances

Instances details
Show a => Show (WithHeader a) Source # 
Instance details

Defined in Turtle.Prelude

Exceptions