turtle-1.3.2: Shell programming, Haskell-style

Safe HaskellNone
LanguageHaskell2010

Turtle

Contents

Description

See Turtle.Tutorial to learn how to use this library or Turtle.Prelude for a quick-start guide.

Here is the recommended way to import this library:

{-# LANGUAGE OverloadedStrings #-}

import Turtle
import Prelude hiding (FilePath)

This module re-exports the rest of the library and also re-exports useful modules from base:

Turtle.Format provides type-safe string formatting

Turtle.Pattern provides Patterns, which are like more powerful regular expressions

Turtle.Shell provides a Shell abstraction for building streaming, exception-safe pipelines

Turtle.Prelude provides a library of Unix-like utilities to get you started with basic shell-like programming within Haskell

Control.Applicative provides two classes:

Control.Monad provides two classes:

Control.Monad.IO.Class provides one class:

Data.Monoid provides one class:

Control.Monad.Managed.Safe provides Managed resources

Filesystem.Path.CurrentOS provides FilePath-manipulation utilities

Additionally, you might also want to import the following modules qualified:

Synopsis

Modules

data Fold a b :: * -> * -> * where #

Efficient representation of a left fold that preserves the fold's step function, initial accumulator, and extraction function

This allows the Applicative instance to assemble derived folds that traverse the container only once

A 'Fold a b' processes elements of type a and results in a value of type b.

Constructors

Fold :: Fold a b

Fold step initial extract

Instances

Profunctor Fold 

Methods

dimap :: (a -> b) -> (c -> d) -> Fold b c -> Fold a d #

lmap :: (a -> b) -> Fold b c -> Fold a c #

rmap :: (b -> c) -> Fold a b -> Fold a c #

(#.) :: Coercible * c b => (b -> c) -> Fold a b -> Fold a c #

(.#) :: Coercible * b a => Fold b c -> (a -> b) -> Fold a c #

Functor (Fold a) 

Methods

fmap :: (a -> b) -> Fold a a -> Fold a b #

(<$) :: a -> Fold a b -> Fold a a #

Applicative (Fold a) 

Methods

pure :: a -> Fold a a #

(<*>) :: Fold a (a -> b) -> Fold a a -> Fold a b #

(*>) :: Fold a a -> Fold a b -> Fold a b #

(<*) :: Fold a a -> Fold a b -> Fold a a #

Comonad (Fold a) 

Methods

extract :: Fold a a -> a #

duplicate :: Fold a a -> Fold a (Fold a a) #

extend :: (Fold a a -> b) -> Fold a a -> Fold a b #

Floating b => Floating (Fold a b) 

Methods

pi :: Fold a b #

exp :: Fold a b -> Fold a b #

log :: Fold a b -> Fold a b #

sqrt :: Fold a b -> Fold a b #

(**) :: Fold a b -> Fold a b -> Fold a b #

logBase :: Fold a b -> Fold a b -> Fold a b #

sin :: Fold a b -> Fold a b #

cos :: Fold a b -> Fold a b #

tan :: Fold a b -> Fold a b #

asin :: Fold a b -> Fold a b #

acos :: Fold a b -> Fold a b #

atan :: Fold a b -> Fold a b #

sinh :: Fold a b -> Fold a b #

cosh :: Fold a b -> Fold a b #

tanh :: Fold a b -> Fold a b #

asinh :: Fold a b -> Fold a b #

acosh :: Fold a b -> Fold a b #

atanh :: Fold a b -> Fold a b #

log1p :: Fold a b -> Fold a b #

expm1 :: Fold a b -> Fold a b #

log1pexp :: Fold a b -> Fold a b #

log1mexp :: Fold a b -> Fold a b #

Fractional b => Fractional (Fold a b) 

Methods

(/) :: Fold a b -> Fold a b -> Fold a b #

recip :: Fold a b -> Fold a b #

fromRational :: Rational -> Fold a b #

Num b => Num (Fold a b) 

Methods

(+) :: Fold a b -> Fold a b -> Fold a b #

(-) :: Fold a b -> Fold a b -> Fold a b #

(*) :: Fold a b -> Fold a b -> Fold a b #

negate :: Fold a b -> Fold a b #

abs :: Fold a b -> Fold a b #

signum :: Fold a b -> Fold a b #

fromInteger :: Integer -> Fold a b #

Monoid b => Monoid (Fold a b) 

Methods

mempty :: Fold a b #

mappend :: Fold a b -> Fold a b -> Fold a b #

mconcat :: [Fold a b] -> Fold a b #

data FoldM m a b :: (* -> *) -> * -> * -> * where #

Like Fold, but monadic.

A 'FoldM m a b' processes elements of type a and results in a monadic value of type m b.

Constructors

FoldM :: FoldM m a b

FoldM step initial extract

Instances

Monad m => Profunctor (FoldM m) 

Methods

dimap :: (a -> b) -> (c -> d) -> FoldM m b c -> FoldM m a d #

lmap :: (a -> b) -> FoldM m b c -> FoldM m a c #

rmap :: (b -> c) -> FoldM m a b -> FoldM m a c #

(#.) :: Coercible * c b => (b -> c) -> FoldM m a b -> FoldM m a c #

(.#) :: Coercible * b a => FoldM m b c -> (a -> b) -> FoldM m a c #

Monad m => Functor (FoldM m a) 

Methods

fmap :: (a -> b) -> FoldM m a a -> FoldM m a b #

(<$) :: a -> FoldM m a b -> FoldM m a a #

Monad m => Applicative (FoldM m a) 

Methods

pure :: a -> FoldM m a a #

(<*>) :: FoldM m a (a -> b) -> FoldM m a a -> FoldM m a b #

(*>) :: FoldM m a a -> FoldM m a b -> FoldM m a b #

(<*) :: FoldM m a a -> FoldM m a b -> FoldM m a a #

(Monad m, Floating b) => Floating (FoldM m a b) 

Methods

pi :: FoldM m a b #

exp :: FoldM m a b -> FoldM m a b #

log :: FoldM m a b -> FoldM m a b #

sqrt :: FoldM m a b -> FoldM m a b #

(**) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

logBase :: FoldM m a b -> FoldM m a b -> FoldM m a b #

sin :: FoldM m a b -> FoldM m a b #

cos :: FoldM m a b -> FoldM m a b #

tan :: FoldM m a b -> FoldM m a b #

asin :: FoldM m a b -> FoldM m a b #

acos :: FoldM m a b -> FoldM m a b #

atan :: FoldM m a b -> FoldM m a b #

sinh :: FoldM m a b -> FoldM m a b #

cosh :: FoldM m a b -> FoldM m a b #

tanh :: FoldM m a b -> FoldM m a b #

asinh :: FoldM m a b -> FoldM m a b #

acosh :: FoldM m a b -> FoldM m a b #

atanh :: FoldM m a b -> FoldM m a b #

log1p :: FoldM m a b -> FoldM m a b #

expm1 :: FoldM m a b -> FoldM m a b #

log1pexp :: FoldM m a b -> FoldM m a b #

log1mexp :: FoldM m a b -> FoldM m a b #

(Monad m, Fractional b) => Fractional (FoldM m a b) 

Methods

(/) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

recip :: FoldM m a b -> FoldM m a b #

fromRational :: Rational -> FoldM m a b #

(Monad m, Num b) => Num (FoldM m a b) 

Methods

(+) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

(-) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

(*) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

negate :: FoldM m a b -> FoldM m a b #

abs :: FoldM m a b -> FoldM m a b #

signum :: FoldM m a b -> FoldM m a b #

fromInteger :: Integer -> FoldM m a b #

(Monoid b, Monad m) => Monoid (FoldM m a b) 

Methods

mempty :: FoldM m a b #

mappend :: FoldM m a b -> FoldM m a b -> FoldM m a b #

mconcat :: [FoldM m a b] -> FoldM m a b #

data Text :: * #

A space efficient, packed, unboxed Unicode text type.

Instances

type Item Text 
type Item Text = Char

data UTCTime :: * #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances

Eq UTCTime 

Methods

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

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

Data UTCTime 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime #

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) #

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

Ord UTCTime 
NFData UTCTime 

Methods

rnf :: UTCTime -> () #

ParseTime UTCTime 

data NominalDiffTime :: * #

This is a length of time, as measured by UTC. Conversion functions will treat it as seconds. It has a precision of 10^-12 s. It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), regardless of whether a leap-second intervened.

Instances

Enum NominalDiffTime 
Eq NominalDiffTime 
Fractional NominalDiffTime 
Data NominalDiffTime 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NominalDiffTime -> c NominalDiffTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NominalDiffTime #

toConstr :: NominalDiffTime -> Constr #

dataTypeOf :: NominalDiffTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NominalDiffTime) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NominalDiffTime) #

gmapT :: (forall b. Data b => b -> b) -> NominalDiffTime -> NominalDiffTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> NominalDiffTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NominalDiffTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

Num NominalDiffTime 
Ord NominalDiffTime 
Real NominalDiffTime 
RealFrac NominalDiffTime 
Show NominalDiffTime 
NFData NominalDiffTime 

Methods

rnf :: NominalDiffTime -> () #

data Handle :: * #

Haskell defines operations to read and write characters from and to files, represented by values of type Handle. Each value of this type is a handle: a record used by the Haskell run-time system to manage I/O with file system objects. A handle has at least the following properties:

  • whether it manages input or output or both;
  • whether it is open, closed or semi-closed;
  • whether the object is seekable;
  • whether buffering is disabled, or enabled on a line or block basis;
  • a buffer (whose length may be zero).

Most handles will also have a current I/O position indicating where the next input or output operation will occur. A handle is readable if it manages only input or both input and output; likewise, it is writable if it manages only output or both input and output. A handle is open when first allocated. Once it is closed it can no longer be used for either input or output, though an implementation cannot re-use its storage while references remain to it. Handles are in the Show and Eq classes. The string produced by showing a handle is system dependent; it should include enough information to identify the handle for debugging. A handle is equal according to == only to itself; no attempt is made to compare the internal state of different handles for equality.

Instances

Eq Handle 

Methods

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

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

Show Handle 

data ExitCode :: * #

Defines the exit codes that a program can return.

Constructors

ExitSuccess

indicates successful termination;

ExitFailure Int

indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system).

class IsString a where #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Minimal complete definition

fromString

Methods

fromString :: String -> a #

Instances

IsString Doc 

Methods

fromString :: String -> Doc #

IsString ByteString 
IsString CmdSpec

construct a ShellCommand from a string literal

Since: 1.2.1.0

Methods

fromString :: String -> CmdSpec #

IsString Line # 

Methods

fromString :: String -> Line #

IsString HelpMessage # 
IsString Description # 
IsString CommandName # 
IsString ArgName # 

Methods

fromString :: String -> ArgName #

(~) * a Char => IsString [a] 

Methods

fromString :: String -> [a] #

IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

IsString a => IsString (Optional a) 

Methods

fromString :: String -> Optional a #

IsString a => IsString (Shell a) # 

Methods

fromString :: String -> Shell a #

(~) * a Text => IsString (Pattern a) # 

Methods

fromString :: String -> Pattern a #

(~) * a b => IsString (Format a b) # 

Methods

fromString :: String -> Format a b #

IsString a => IsString (Const * a b) 

Methods

fromString :: String -> Const * a b #

IsString a => IsString (Tagged k s a) 

Methods

fromString :: String -> Tagged k s a #

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

Since: 4.8.0.0