Safe Haskell | None |
---|---|
Language | Haskell2010 |
Flexible control of progress reporting for readCreateProcess and friends.
- type RunT text m = StateT (RunState text) m
- runT :: forall m text char a. (MonadIO m, ProcessText text char) => RunT text m a -> m a
- data RunState text = RunState {
- _output :: OutputStyle
- _outprefix :: text
- _errprefix :: text
- _echoStart :: Bool
- _echoEnd :: Bool
- _verbosity :: Int
- _lazy :: Bool
- _message :: text
- data OutputStyle
- class (MonadState (RunState text) m, ProcessText text char, ListLikeProcessIO text char, MonadIO m, IsString text, Eq char, Dot char) => RunM text char m
- echoStart :: MonadState (RunState t) m => m ()
- echoEnd :: MonadState (RunState t) m => m ()
- output :: MonadState (RunState t) m => m ()
- silent :: MonadState (RunState t) m => m ()
- dots :: MonadState (RunState t) m => Int -> m ()
- indent :: (MonadState (RunState t) m, ListLike t char) => (t -> t) -> (t -> t) -> m ()
- vlevel :: forall m text char. (IsString text, ListLike text char, MonadIO m, MonadState (RunState text) m) => Int -> m ()
- quieter :: RunM text char m => m ()
- noisier :: RunM text char m => m ()
- lazy :: RunM text char m => m ()
- strict :: RunM text char m => m ()
- message :: RunM text char m => (text -> text) -> m ()
- run :: forall m maker text char result. (RunM text char m, ProcessMaker maker, ProcessResult text result) => maker -> text -> m result
- module System.Process.ListLike
Monad transformer
This is the state record that controls the output style.
RunState | |
|
ProcessText text char => Default (RunState text) Source # | |
data OutputStyle Source #
Monad class
class (MonadState (RunState text) m, ProcessText text char, ListLikeProcessIO text char, MonadIO m, IsString text, Eq char, Dot char) => RunM text char m Source #
(MonadIO m, MonadState (RunState String) m) => RunM String Char m Source # | |
(MonadIO m, MonadState (RunState ByteString) m) => RunM ByteString Word8 m Source # | |
(MonadIO m, MonadState (RunState ByteString) m) => RunM ByteString Word8 m Source # | |
(MonadIO m, MonadState (RunState Text) m) => RunM Text Char m Source # | |
(MonadIO m, MonadState (RunState Text) m) => RunM Text Char m Source # | |
Modify moand RunM state parameters
echoStart :: MonadState (RunState t) m => m () Source #
echoEnd :: MonadState (RunState t) m => m () Source #
output :: MonadState (RunState t) m => m () Source #
silent :: MonadState (RunState t) m => m () Source #
indent :: (MonadState (RunState t) m, ListLike t char) => (t -> t) -> (t -> t) -> m () Source #
Modify the indentation prefixes for stdout and stderr in the progress monad.
vlevel :: forall m text char. (IsString text, ListLike text char, MonadIO m, MonadState (RunState text) m) => Int -> m () Source #
Set verbosity to a specific level from 0 to 3. vlevel :: (MonadIO m, Monoid text, MonadState (RunState text) m) => Int -> m () vlevel :: forall m text char. (IsString text, ListLike text char, MonadIO m) => Int -> m ()
Monadic process runner
run :: forall m maker text char result. (RunM text char m, ProcessMaker maker, ProcessResult text result) => maker -> text -> m result Source #
Re-exports
module System.Process.ListLike