Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Provides a typeclass for all monads that may scan text.
Synopsis
- 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
- type InRedir = InRedirT (HandleCloserT IO)
- 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?
Instances
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 | |
|
Instances
QuietT does not convey any input (much like <devnull in the shell)
Instances
InRedirT redirects all input to a given handle (much like <filename in the shell)
InRedir | |
|
Instances
runInRedirFT :: (Functor m, MonadIO m, ChFinalizer m) => InRedirT m a -> FilePath -> m a Source #
Run InRedirT 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.
(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (mt m)) => mt m a -> t -> m r Source #
Redirection
Instances
class RedirectionHeredoc t mt a r | t -> mt, t a -> r where Source #
Class for all Here-Documents
Instances
RedirectionHeredoc String HereStringT a a Source # | |
Defined in Text.Chatty.Scanner (.<<.) :: (Functor m, ChScanner (HereStringT m)) => HereStringT m a -> String -> m a Source # |