Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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 Shell
s using the Shell
constructor. Instead,
use these functions to generate primitive Shell
s:
empty
, to create aShell
that outputs nothingreturn
, to create aShell
that outputs a single valueselect
, to range over a list of values within aShell
liftIO
, to embed anIO
action within aShell
using
, to acquire aManaged
resource within aShell
Then use these classes to combine those primitive Shell
s into larger
Shell
s:
Alternative
, to concatenateShell
outputs using (<|>
)Monad
, to buildShell
comprehensions usingdo
notation
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
- newtype Shell a = Shell {
- _foldShell :: forall r. FoldShell a r -> IO r
- data FoldShell a b = FoldShell (x -> a -> IO x) x (x -> IO b)
- _foldIO :: Shell a -> FoldM IO a r -> IO r
- _Shell :: (forall r. FoldM IO a r -> IO r) -> Shell a
- foldIO :: MonadIO io => Shell a -> FoldM IO a r -> io r
- foldShell :: MonadIO io => Shell a -> FoldShell a b -> io b
- fold :: MonadIO io => Shell a -> Fold a b -> io b
- reduce :: MonadIO io => Fold a b -> Shell a -> io b
- sh :: MonadIO io => Shell a -> io ()
- view :: (MonadIO io, Show a) => Shell a -> io ()
- select :: Foldable f => f a -> Shell a
- liftIO :: MonadIO m => IO a -> m a
- using :: MonadManaged m => Managed a -> m a
Shell
A (Shell a)
is a protected stream of a
's with side effects
Shell | |
|
Instances
Monad Shell Source # | |
Functor Shell Source # | |
MonadFail Shell Source # | |
Defined in Turtle.Shell | |
Applicative Shell Source # | |
MonadIO Shell Source # | |
Defined in Turtle.Shell | |
Alternative Shell Source # | |
MonadPlus Shell Source # | |
MonadThrow Shell Source # | |
Defined in Turtle.Shell | |
MonadCatch Shell Source # | |
MonadManaged Shell Source # | |
Defined in Turtle.Shell | |
Monoid a => Num (Shell a) Source # | Shell forms a semiring, this is the closest approximation |
IsString a => IsString (Shell a) Source # | |
Defined in Turtle.Shell fromString :: String -> Shell a # | |
Monoid a => Semigroup (Shell a) Source # | |
Monoid a => Monoid (Shell a) Source # | |
This is similar to
except that the FoldM
IO
begin
field is pure
This small difference is necessary to implement a well-behaved MonadCatch
instance for Shell
_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
sh :: MonadIO io => Shell a -> io () Source #
Run a Shell
to completion, discarding 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
using :: MonadManaged m => Managed a -> m a #