chatty-0.8.0.0: Some monad transformers and typeclasses for text in- and output abstraction.
Safe HaskellSafe
LanguageHaskell2010

Text.Chatty.Scanner

Description

Provides a typeclass for all monads that may scan text.

Synopsis

Documentation

class Monad m => ChScanner m where Source #

A typeclass for all monads that may read input.

Minimal complete definition

mscan1, mscanL, mscannable, mready

Methods

mscan1 :: m Char Source #

Read one single character

mscanL :: m String Source #

Lazily read all the input.

mscannable :: m Bool Source #

Input readable? (not EOF)

mscanh :: m (Maybe Handle) Source #

Return FD handle, if available

mready :: m Bool Source #

Input available yet?

Instances

Instances details
ChScanner IO Source # 
Instance details

Defined in Text.Chatty.Scanner

ChScanner m => ChScanner (AtomStoreT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (CounterT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (NullExpanderT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (HistoryT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (ExpanderT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (HandleCloserT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (RecorderT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (OutRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (DeafT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (HtmlPrinterT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (AnsiPrinterT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (JoinerT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (HandleFilterT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (BoolFilterT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (IntFilterT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (HandleArchiverT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (BoolArchiverT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChScanner m => ChScanner (IntArchiverT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

MonadIO m => ChScanner (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Monad m => ChScanner (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Monad m => ChScanner (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

ChScanner m => ChScanner (ScannerBufferT m) Source # 
Instance details

Defined in Text.Chatty.Scanner.Buffered

Monad m => ChScanner (StateT String m) Source # 
Instance details

Defined in Text.Chatty.Scanner

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)

Constructors

HereString 

Fields

Instances

Instances details
MonadTrans HereStringT Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

RedirectionHeredoc String HereStringT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<<.) :: (Functor m, ChScanner (HereStringT m)) => HereStringT m a -> String -> m a Source #

ChChannelPrinter Bool m => ChChannelPrinter Bool (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChChannelPrinter Int m => ChChannelPrinter Int (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChChannelPrinter Handle m => ChChannelPrinter Handle (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Monad m => Monad (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

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

return :: a -> HereStringT m a #

Monad m => Functor (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

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

Monad m => Applicative (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

pure :: a -> HereStringT m a #

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

liftA2 :: (a -> b -> c) -> HereStringT m a -> HereStringT m b -> HereStringT m c #

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

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

MonadIO m => MonadIO (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

liftIO :: IO a -> HereStringT m a #

ChAtoms m => ChAtoms (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

newAtom :: HereStringT m (Atom v) #

funAtom :: Atom b -> (b -> a) -> (b -> a -> b) -> HereStringT m (Atom a) #

funAtom2 :: Atom b -> Atom c -> ((b, c) -> a) -> ((b, c) -> a -> (b, c)) -> HereStringT m (Atom a) #

putAtom :: Atom v -> v -> HereStringT m () #

getAtom :: Atom v -> HereStringT m v #

dispAtom :: Atom v -> HereStringT m () #

cloneAtom :: Atom v -> HereStringT m (Atom v) #

ChCounter m => ChCounter (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

countOn :: HereStringT m Int #

ChExpand m => ChExpand (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChHistoryEnv m => ChHistoryEnv (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChExpanderEnv m => ChExpanderEnv (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChFinalizer m => ChFinalizer (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

ChPrinter m => ChPrinter (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChExtendedPrinter m => ChExtendedPrinter (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Monad m => ChScanner (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Monad m => ChBufferedScanner (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Scanner.Buffered

newtype QuietT m a Source #

QuietT does not convey any input (much like <devnull in the shell)

Constructors

Quiet 

Fields

Instances

Instances details
MonadTrans QuietT Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

RedirectionSource EmptyI QuietT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (QuietT m)) => QuietT m a -> EmptyI -> m a Source #

ChChannelPrinter Bool m => ChChannelPrinter Bool (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

cbracket :: Bool -> QuietT m a -> QuietT m a Source #

cstart :: Bool -> QuietT m () Source #

cfin :: Bool -> QuietT m () Source #

cprint :: Bool -> String -> QuietT m () Source #

cthis :: QuietT m Bool Source #

ChChannelPrinter Int m => ChChannelPrinter Int (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

cbracket :: Int -> QuietT m a -> QuietT m a Source #

cstart :: Int -> QuietT m () Source #

cfin :: Int -> QuietT m () Source #

cprint :: Int -> String -> QuietT m () Source #

cthis :: QuietT m Int Source #

ChChannelPrinter Handle m => ChChannelPrinter Handle (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Monad m => Monad (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

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

return :: a -> QuietT m a #

Functor m => Functor (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

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

(Functor m, Monad m) => Applicative (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

pure :: a -> QuietT m a #

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

liftA2 :: (a -> b -> c) -> QuietT m a -> QuietT m b -> QuietT m c #

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

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

ChAtoms m => ChAtoms (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

newAtom :: QuietT m (Atom v) #

funAtom :: Atom b -> (b -> a) -> (b -> a -> b) -> QuietT m (Atom a) #

funAtom2 :: Atom b -> Atom c -> ((b, c) -> a) -> ((b, c) -> a -> (b, c)) -> QuietT m (Atom a) #

putAtom :: Atom v -> v -> QuietT m () #

getAtom :: Atom v -> QuietT m v #

dispAtom :: Atom v -> QuietT m () #

cloneAtom :: Atom v -> QuietT m (Atom v) #

ChCounter m => ChCounter (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

countOn :: QuietT m Int #

ChExpand m => ChExpand (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChHistoryEnv m => ChHistoryEnv (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChExpanderEnv m => ChExpanderEnv (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChPrinter m => ChPrinter (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChExtendedPrinter m => ChExtendedPrinter (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Monad m => ChScanner (QuietT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

newtype InRedirT m a Source #

InRedirT redirects all input to a given handle (much like <filename in the shell)

Constructors

InRedir 

Fields

Instances

Instances details
MonadTrans InRedirT Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

RedirectionSource Handle InRedirT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (InRedirT m)) => InRedirT m a -> Handle -> m a Source #

RedirectionSource FilePath InRedirT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (InRedirT m)) => InRedirT m a -> FilePath -> m a Source #

ChChannelPrinter Bool m => ChChannelPrinter Bool (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChChannelPrinter Int m => ChChannelPrinter Int (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChChannelPrinter Handle m => ChChannelPrinter Handle (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Monad m => Monad (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

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

return :: a -> InRedirT m a #

Monad m => Functor (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

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

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

Monad m => Applicative (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

pure :: a -> InRedirT m a #

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

liftA2 :: (a -> b -> c) -> InRedirT m a -> InRedirT m b -> InRedirT m c #

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

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

MonadIO m => MonadIO (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

liftIO :: IO a -> InRedirT m a #

ChAtoms m => ChAtoms (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

newAtom :: InRedirT m (Atom v) #

funAtom :: Atom b -> (b -> a) -> (b -> a -> b) -> InRedirT m (Atom a) #

funAtom2 :: Atom b -> Atom c -> ((b, c) -> a) -> ((b, c) -> a -> (b, c)) -> InRedirT m (Atom a) #

putAtom :: Atom v -> v -> InRedirT m () #

getAtom :: Atom v -> InRedirT m v #

dispAtom :: Atom v -> InRedirT m () #

cloneAtom :: Atom v -> InRedirT m (Atom v) #

ChCounter m => ChCounter (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

Methods

countOn :: InRedirT m Int #

ChExpand m => ChExpand (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChHistoryEnv m => ChHistoryEnv (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChExpanderEnv m => ChExpanderEnv (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChFinalizer m => ChFinalizer (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

mqfh :: Handle -> InRedirT m () Source #

mqfhs :: [Handle] -> InRedirT m () Source #

mfin :: InRedirT m () Source #

ChPrinter m => ChPrinter (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

ChExtendedPrinter m => ChExtendedPrinter (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

MonadIO m => ChScanner (InRedirT m) Source # 
Instance details

Defined in Text.Chatty.Scanner

type InRedir = InRedirT (HandleCloserT IO) Source #

InRedirT on an IO monad

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

mscanLn :: ChScanner m => m String Source #

Line-scanning alternative to mscan1/L

mscanN :: ChScanner m => Int -> m String Source #

Scan a fixed number of chars

data EmptyI Source #

Redirection source that does not provide any output

Constructors

EmptyI 

Instances

Instances details
RedirectionSource EmptyI QuietT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (QuietT m)) => QuietT m a -> EmptyI -> m a Source #

class RedirectionSource t mt a r | t -> mt, t a -> r where Source #

Class for all primitive redirection sources.

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (mt m)) => mt m a -> t -> m r Source #

Redirection

Instances

Instances details
RedirectionSource Handle InRedirT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (InRedirT m)) => InRedirT m a -> Handle -> m a Source #

RedirectionSource FilePath InRedirT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (InRedirT m)) => InRedirT m a -> FilePath -> m a Source #

RedirectionSource EmptyI QuietT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<.) :: (ChFinalizer m, Functor m, MonadIO m, ChScanner (QuietT m)) => QuietT m a -> EmptyI -> m a Source #

class RedirectionHeredoc t mt a r | t -> mt, t a -> r where Source #

Class for all Here-Documents

Methods

(.<<.) :: (Functor m, ChScanner (mt m)) => mt m a -> t -> m r Source #

Redirection

Instances

Instances details
RedirectionHeredoc String HereStringT a a Source # 
Instance details

Defined in Text.Chatty.Scanner

Methods

(.<<.) :: (Functor m, ChScanner (HereStringT m)) => HereStringT m a -> String -> m a Source #