| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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:
empty, to create aShellthat outputs nothingreturn, to create aShellthat outputs a single valueselect, to range over a list of values within aShellliftIO, to embed anIOaction within aShellusing, to acquire aManagedresource within aShell
Then use these classes to combine those primitive Shells into larger
Shells:
Alternative, to concatenateShelloutputs using (<|>)Monad, to buildShellcomprehensions usingdonotation
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 = forall x. 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
- fromIO :: IO (Maybe a) -> Shell a
Shell
A (Shell a) is a protected stream of a's with side effects
Constructors
| Shell | |
Fields
| |
Instances
| MonadFail Shell Source # | |
Defined in Turtle.Shell | |
| MonadIO Shell Source # | |
Defined in Turtle.Shell | |
| Alternative Shell Source # | |
| Applicative Shell Source # | |
| Functor Shell Source # | |
| Monad Shell Source # | |
| MonadPlus Shell Source # | |
| MonadCatch Shell Source # | |
| MonadThrow Shell Source # | |
Defined in Turtle.Shell | |
| MonadManaged Shell Source # | |
Defined in Turtle.Shell | |
| IsString a => IsString (Shell a) Source # | |
Defined in Turtle.Shell Methods fromString :: String -> Shell a # | |
| Monoid a => Monoid (Shell a) Source # | |
| Monoid a => Semigroup (Shell a) Source # | |
| Monoid a => Num (Shell a) Source # | Shell forms a semiring, this is the closest approximation |
This is similar to except that the FoldM IObegin
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
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted , we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO () and .IO ()
Luckily, we know of a function that takes an and returns an IO a(m a): ,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
using :: MonadManaged m => Managed a -> m a #