Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Conduit.Shell.Process
Description
Reading from the process.
Synopsis
- run :: MonadIO m => Segment m r -> m r
- text :: forall r (m :: Type -> Type). (r ~ (), MonadThrow m) => ConduitT Text Text m r -> Segment m r
- bytes :: forall a (m :: Type -> Type) r. (a ~ ByteString, Monad m) => ConduitT a ByteString m r -> Segment m r
- conduit :: forall a (m :: Type -> Type) r. (a ~ ByteString, Monad m) => ConduitT a ByteString m r -> Segment m r
- conduitEither :: forall a (m :: Type -> Type) r. (a ~ ByteString, Monad m) => ConduitT a (Either ByteString ByteString) m r -> Segment m r
- shell :: forall (m :: Type -> Type). MonadIO m => String -> Segment m ()
- proc :: forall (m :: Type -> Type). MonadIO m => String -> [String] -> Segment m ()
- ($|) :: forall (m :: Type -> Type) b. MonadUnliftIO m => Segment m () -> Segment m b -> Segment m b
- data Segment (m :: Type -> Type) r
- data ProcessException
- class ToChunk a where
- toChunk :: a -> Either ByteString ByteString
- tryS :: forall e (m :: Type -> Type) r. (Exception e, MonadUnliftIO m) => Segment m r -> Segment m (Either e r)
Running scripts
Conduit types
text :: forall r (m :: Type -> Type). (r ~ (), MonadThrow m) => ConduitT Text Text m r -> Segment m r Source #
Work on the stream as Text
values from UTF-8.
bytes :: forall a (m :: Type -> Type) r. (a ~ ByteString, Monad m) => ConduitT a ByteString m r -> Segment m r Source #
Lift a conduit into a segment.
General conduits
conduit :: forall a (m :: Type -> Type) r. (a ~ ByteString, Monad m) => ConduitT a ByteString m r -> Segment m r Source #
Lift a conduit into a segment.
conduitEither :: forall a (m :: Type -> Type) r. (a ~ ByteString, Monad m) => ConduitT a (Either ByteString ByteString) m r -> Segment m r Source #
Lift a conduit into a segment, which can yield stderr.
Running processes
shell :: forall (m :: Type -> Type). MonadIO m => String -> Segment m () Source #
Run a shell command.
proc :: forall (m :: Type -> Type). MonadIO m => String -> [String] -> Segment m () Source #
Run a process command.
($|) :: forall (m :: Type -> Type) b. MonadUnliftIO m => Segment m () -> Segment m b -> Segment m b infixl 0 Source #
Fuse two segments (either processes or conduits).
data Segment (m :: Type -> Type) r Source #
A pipeable segment. Either a conduit or a process.
Instances
MonadIO m => MonadIO (Segment m) Source # | |
Defined in Data.Conduit.Shell.Process | |
MonadUnliftIO m => Alternative (Segment m) Source # | |
MonadIO m => Applicative (Segment m) Source # | |
Defined in Data.Conduit.Shell.Process | |
MonadIO m => Functor (Segment m) Source # | |
MonadIO m => Monad (Segment m) Source # | |
(r ~ (), MonadIO m) => ProcessType (Segment m r) Source # | |
data ProcessException Source #
Process running exception.
Constructors
ProcessException CreateProcess ExitCode | |
ProcessEmpty |
Instances
Exception ProcessException Source # | |
Defined in Data.Conduit.Shell.Process Methods toException :: ProcessException -> SomeException # | |
Show ProcessException Source # | |
Defined in Data.Conduit.Shell.Process Methods showsPrec :: Int -> ProcessException -> ShowS # show :: ProcessException -> String # showList :: [ProcessException] -> ShowS # |
class ToChunk a where Source #
Used to allow outputting stdout or stderr.
Methods
toChunk :: a -> Either ByteString ByteString Source #
Instances
ToChunk ByteString Source # | |
Defined in Data.Conduit.Shell.Process Methods toChunk :: ByteString -> Either ByteString ByteString Source # | |
ToChunk (Either ByteString ByteString) Source # | |
Defined in Data.Conduit.Shell.Process Methods toChunk :: Either ByteString ByteString -> Either ByteString ByteString Source # |