shell-conduit-4.6.1: Write shell scripts with Conduit

Safe HaskellNone
LanguageHaskell98

Data.Conduit.Shell.Types

Description

All types.

Synopsis

Documentation

newtype ShellT m a Source #

Shell transformer.

Constructors

ShellT 

Fields

Instances

MonadTrans ShellT Source # 

Methods

lift :: Monad m => m a -> ShellT m a #

(MonadThrow m, MonadIO m, MonadBaseControl IO m) => MonadBaseControl IO (ShellT m) Source #

Dumb instance.

Associated Types

type StM (ShellT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ShellT m) IO -> IO a) -> ShellT m a #

restoreM :: StM (ShellT m) a -> ShellT m a #

MonadResourceBase m => MonadBase IO (ShellT m) Source # 

Methods

liftBase :: IO α -> ShellT m α #

Monad m => Monad (ShellT m) Source # 

Methods

(>>=) :: ShellT m a -> (a -> ShellT m b) -> ShellT m b #

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

return :: a -> ShellT m a #

fail :: String -> ShellT m a #

Functor m => Functor (ShellT m) Source # 

Methods

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

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

Applicative m => Applicative (ShellT m) Source # 

Methods

pure :: a -> ShellT m a #

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

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

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

MonadIO m => MonadIO (ShellT m) Source # 

Methods

liftIO :: IO a -> ShellT m a #

MonadThrow m => MonadThrow (ShellT m) Source # 

Methods

throwM :: Exception e => e -> ShellT m a #

MonadResourceBase m => MonadResource (ShellT m) Source # 

Methods

liftResourceT :: ResourceT IO a -> ShellT m a #

(MonadBaseControl IO (ShellT m), Applicative m, MonadThrow m) => Alternative (ConduitM i o (ShellT m)) Source #

Intentionally only handles ShellException. Use normal exception handling to handle usual exceptions.

Methods

empty :: ConduitM i o (ShellT m) a #

(<|>) :: ConduitM i o (ShellT m) a -> ConduitM i o (ShellT m) a -> ConduitM i o (ShellT m) a #

some :: ConduitM i o (ShellT m) a -> ConduitM i o (ShellT m) [a] #

many :: ConduitM i o (ShellT m) a -> ConduitM i o (ShellT m) [a] #

type StM (ShellT m) a Source # 
type StM (ShellT m) a = StMShell m a

newtype StMShell m a Source #

Constructors

StMShell 

Fields