| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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">>>pwdFilePath "/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 "Browser.py" "/usr/lib")FilePath "lib/python3.2/idlelib/ObjectBrowser.py" FilePath "lib/python3.2/idlelib/PathBrowser.py" FilePath "lib/python3.2/idlelib/RemoteObjectBrowser.py" FilePath "lib/python3.2/idlelib/ClassBrowser.py"
Use fold to reduce the output of a Shell stream:
>>>import qualified Control.Foldl as Fold>>>fold (ls "/usr") Fold.length8>>>fold (find "Browser.py" "/usr/lib") Fold.headJust (FilePath "/usr/lib/python3.2/idlelib/ObjectBrowser.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
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.
- proc :: Text -> [Text] -> Shell Text -> IO ExitCode
- shell :: Text -> Shell Text -> IO ExitCode
- echo :: Text -> IO ()
- err :: Text -> IO ()
- readline :: IO (Maybe Text)
- export :: Text -> Text -> IO ()
- unset :: Text -> IO ()
- need :: Text -> IO (Maybe Text)
- env :: IO [(Text, Text)]
- cd :: FilePath -> IO ()
- pwd :: IO FilePath
- home :: IO FilePath
- realpath :: FilePath -> IO FilePath
- mv :: FilePath -> FilePath -> IO ()
- mkdir :: FilePath -> IO ()
- mktree :: FilePath -> IO ()
- cp :: FilePath -> FilePath -> IO ()
- rm :: FilePath -> IO ()
- rmdir :: FilePath -> IO ()
- rmtree :: FilePath -> IO ()
- du :: FilePath -> IO Integer
- testfile :: FilePath -> IO Bool
- testdir :: FilePath -> IO Bool
- date :: IO UTCTime
- datefile :: FilePath -> IO UTCTime
- touch :: FilePath -> IO ()
- time :: IO a -> IO (a, NominalDiffTime)
- sleep :: NominalDiffTime -> IO ()
- exit :: Int -> IO ()
- die :: Text -> IO ()
- readonly :: FilePath -> Managed Handle
- writeonly :: FilePath -> Managed Handle
- appendonly :: FilePath -> Managed Handle
- mktemp :: FilePath -> Text -> Managed (FilePath, Handle)
- 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
- stdin :: Shell Text
- input :: FilePath -> Shell Text
- inhandle :: Handle -> Shell Text
- stdout :: Shell Text -> IO ()
- stderr :: Shell Text -> IO ()
- output :: FilePath -> Shell Text -> IO ()
- append :: FilePath -> Shell Text -> IO ()
- ls :: 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
- find :: Pattern a -> FilePath -> Shell FilePath
- yes :: Shell Text
- limit :: Int -> Shell a -> Shell a
- limitWhile :: (a -> Bool) -> Shell a -> Shell a
IO
Arguments
| :: 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
mktree :: FilePath -> IO () Source
Create a directory tree (equivalent to mkdir -p)
Does not fail if the directory is present
touch :: 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 :: 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 :: 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.
Managed
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
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
ls :: FilePath -> Shell FilePath Source
Stream all immediate children of the given directory, excluding "." and
".."