turtle-1.5.10: Shell programming, Haskell-style

Safe HaskellSafe
LanguageHaskell2010

Turtle.Shell

Contents

Description

You can think of Shell as [] + IO + Managed. In fact, you can embed all three of them within a Shell:

select ::        [a] -> Shell a
liftIO ::      IO a  -> Shell a
using  :: Managed a  -> Shell a

Those three embeddings obey these laws:

do { x <- select m; select (f x) } = select (do { x <- m; f x })
do { x <- liftIO m; liftIO (f x) } = liftIO (do { x <- m; f x })
do { x <- with   m; using  (f x) } = using  (do { x <- m; f x })

select (return x) = return x
liftIO (return x) = return x
using  (return x) = return x

... and select obeys these additional laws:

select xs <|> select ys = select (xs <|> ys)
select empty = empty

You typically won't build Shells using the Shell constructor. Instead, use these functions to generate primitive Shells:

Then use these classes to combine those primitive Shells into larger Shells:

If you still insist on building your own Shell from scratch, then the Shell you build must satisfy this law:

-- For every shell `s`:
_foldShell s (FoldShell step begin done) = do
    x' <- _foldShell s (FoldShell step begin return)
    done x'

... which is a fancy way of saying that your Shell must call 'begin' exactly once when it begins and call 'done' exactly once when it ends.

Synopsis

Shell

newtype Shell a Source #

A (Shell a) is a protected stream of a's with side effects

Constructors

Shell 

Fields

Instances
Monad Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

(>>=) :: Shell a -> (a -> Shell b) -> Shell b #

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

return :: a -> Shell a #

fail :: String -> Shell a #

Functor Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

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

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

MonadFail Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

fail :: String -> Shell a #

Applicative Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

pure :: a -> Shell a #

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

liftA2 :: (a -> b -> c) -> Shell a -> Shell b -> Shell c #

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

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

MonadIO Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

liftIO :: IO a -> Shell a #

Alternative Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

empty :: Shell a #

(<|>) :: Shell a -> Shell a -> Shell a #

some :: Shell a -> Shell [a] #

many :: Shell a -> Shell [a] #

MonadPlus Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

mzero :: Shell a #

mplus :: Shell a -> Shell a -> Shell a #

MonadThrow Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

throwM :: Exception e => e -> Shell a #

MonadCatch Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

catch :: Exception e => Shell a -> (e -> Shell a) -> Shell a #

MonadManaged Shell Source # 
Instance details

Defined in Turtle.Shell

Methods

using :: Managed a -> Shell a #

Monoid a => Num (Shell a) Source #

Shell forms a semiring, this is the closest approximation

Instance details

Defined in Turtle.Shell

Methods

(+) :: Shell a -> Shell a -> Shell a #

(-) :: Shell a -> Shell a -> Shell a #

(*) :: Shell a -> Shell a -> Shell a #

negate :: Shell a -> Shell a #

abs :: Shell a -> Shell a #

signum :: Shell a -> Shell a #

fromInteger :: Integer -> Shell a #

IsString a => IsString (Shell a) Source # 
Instance details

Defined in Turtle.Shell

Methods

fromString :: String -> Shell a #

Monoid a => Semigroup (Shell a) Source # 
Instance details

Defined in Turtle.Shell

Methods

(<>) :: Shell a -> Shell a -> Shell a #

sconcat :: NonEmpty (Shell a) -> Shell a #

stimes :: Integral b => b -> Shell a -> Shell a #

Monoid a => Monoid (Shell a) Source # 
Instance details

Defined in Turtle.Shell

Methods

mempty :: Shell a #

mappend :: Shell a -> Shell a -> Shell a #

mconcat :: [Shell a] -> Shell a #

data FoldShell a b Source #

This is similar to FoldM IO except that the begin field is pure

This small difference is necessary to implement a well-behaved MonadCatch instance for Shell

Constructors

FoldShell (x -> a -> IO x) x (x -> IO b) 

_foldIO :: Shell a -> FoldM IO a r -> IO r Source #

Provided for backwards compatibility with versions of turtle-1.4.* and older

_Shell :: (forall r. FoldM IO a r -> IO r) -> Shell a Source #

Provided for ease of migration from versions of turtle-1.4.* and older

foldIO :: MonadIO io => Shell a -> FoldM IO a r -> io r Source #

Use a FoldM IO to reduce the stream of a's produced by a Shell

foldShell :: MonadIO io => Shell a -> FoldShell a b -> io b Source #

Use a FoldShell to reduce the stream of a's produced by a Shell

fold :: MonadIO io => Shell a -> Fold a b -> io b Source #

Use a Fold to reduce the stream of a's produced by a Shell

sh :: MonadIO io => Shell a -> io () Source #

Run a Shell to completion, discarding any unused values

view :: (MonadIO io, Show a) => Shell a -> io () Source #

Run a Shell to completion, printing any unused values

Embeddings

select :: Foldable f => f a -> Shell a Source #

Convert a list to a Shell that emits each element of the list

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

using :: MonadManaged m => Managed a -> m a #