Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Provides a typeclass for all monads that may scan text.
- class Monad m => ChScanner m where
- newtype HereStringT m a = HereString {
- runHereStringT :: String -> m (a, String)
- newtype QuietT m a = Quiet {
- runQuietT :: m a
- newtype InRedirT m a = InRedir {
- runInRedirT' :: Handle -> m (a, Handle)
- type InRedir = InRedirT (HandleCloserT IO)
- runInRedirT :: Functor m => InRedirT m a -> Handle -> m a
- runInRedir :: InRedir a -> Handle -> IO a
- runInRedirFT :: (Functor m, MonadIO m, ChFinalizer m) => InRedirT m a -> FilePath -> m a
- runInRedirF :: InRedir a -> FilePath -> IO a
- mscanLn :: ChScanner m => m String
- mscanN :: ChScanner m => Int -> m String
- data EmptyI = EmptyI
- class RedirectionSource t mt a r | t -> mt, t a -> r where
- (.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (mt m)) => mt m a -> t -> m r
- class RedirectionHeredoc t mt a r | t -> mt, t a -> r where
Documentation
class Monad m => ChScanner m where Source
A typeclass for all monads that may read input.
Read one single character
Lazily read all the input.
mscannable :: m Bool Source
Input readable? (not EOF)
mscanh :: m (Maybe Handle) Source
Return FD handle, if available
Input available yet?
newtype HereStringT m a Source
HereStringT holds a given string and uses it as input for the function (much like here-strings in the shell)
HereString | |
|
QuietT does not convey any input (much like <devnull in the shell)
MonadTrans QuietT | |
RedirectionSource EmptyI QuietT a a | |
ChChannelPrinter Bool m0 => ChChannelPrinter Bool (QuietT m) | |
ChChannelPrinter Int m0 => ChChannelPrinter Int (QuietT m) | |
ChChannelPrinter Handle m0 => ChChannelPrinter Handle (QuietT m) | |
Monad m => Monad (QuietT m) | |
Functor m => Functor (QuietT m) | |
(Functor m, Monad m) => Applicative (QuietT m) | |
ChAtoms m0 => ChAtoms (QuietT m) | |
ChCounter m0 => ChCounter (QuietT m) | |
ChRandom m0 => ChRandom (QuietT m) | |
ChClock m0 => ChClock (QuietT m) | |
Monad m => ChScanner (QuietT m) | |
ChPrinter m0 => ChPrinter (QuietT m) | |
ChSpawn m0 => ChSpawn (QuietT m) | |
(ChAtoms (QuietT m0), ChFilesystem m0) => ChFilesystem (QuietT m) | |
ChExtendedPrinter m0 => ChExtendedPrinter (QuietT m) | |
ChExpand m0 => ChExpand (QuietT m) | |
ChExpanderEnv m0 => ChExpanderEnv (QuietT m) | |
ChHistoryEnv m0 => ChHistoryEnv (QuietT m) | |
CanMount m0 n0 => CanMount (QuietT m) n | |
CanSave m0 n0 => CanSave (QuietT m) n | |
CanLoad m0 n0 => CanLoad (QuietT m) n |
InRedirT redirects all input to a given handle (much like <filename in the shell)
InRedir | |
|
type InRedir = InRedirT (HandleCloserT IO) Source
InRedirT on an IO monad
runInRedirT :: Functor m => InRedirT m a -> Handle -> m a Source
Run InRedirT with handle
runInRedir :: InRedir a -> Handle -> IO a Source
Run InRedir with handle
runInRedirFT :: (Functor m, MonadIO m, ChFinalizer m) => InRedirT m a -> FilePath -> m a Source
Run InRedirT with a filename
runInRedirF :: InRedir a -> FilePath -> IO a Source
Run InRedir with a filename
Redirection source that does not provide any output
class RedirectionSource t mt a r | t -> mt, t a -> r where Source
Class for all primitive redirection sources.
class RedirectionHeredoc t mt a r | t -> mt, t a -> r where Source
Class for all Here-Documents