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

Text.Chatty.Printer

Description

Provides a typeclass for all monads that may print text.

Synopsis

Documentation

class Monad m => ChPrinter m where Source #

A typeclass for all monads that may output strings.

Minimal complete definition

mprint

Methods

mprint :: String -> m () Source #

Just print it!

mnoecho :: String -> m () Source #

Print it, except you are IO.

mflush :: m () Source #

Flush the buffer.

mnomask :: String -> m () Source #

Alternative to mprint that does not mask any characters (depends on the carrier).

Instances

Instances details
ChPrinter IO Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

mprint :: String -> IO () Source #

mnoecho :: String -> IO () Source #

mflush :: IO () Source #

mnomask :: String -> IO () Source #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Monad m => ChPrinter (RecorderT m) Source # 
Instance details

Defined in Text.Chatty.Printer

MonadIO m => ChPrinter (OutRedirT m) Source # 
Instance details

Defined in Text.Chatty.Printer

Monad m => ChPrinter (DeafT m) Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

mprint :: String -> DeafT m () Source #

mnoecho :: String -> DeafT m () Source #

mflush :: DeafT m () Source #

mnomask :: String -> DeafT m () Source #

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

Defined in Text.Chatty.Extended.HTML

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

Defined in Text.Chatty.Extended.ANSI

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

Defined in Text.Chatty.Channel.Printer

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

(Eq c, ChPrinter m) => ChPrinter (FilterT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

mprint :: String -> FilterT c m () Source #

mnoecho :: String -> FilterT c m () Source #

mflush :: FilterT c m () Source #

mnomask :: String -> FilterT c m () Source #

(Eq c, Monad m) => ChPrinter (ArchiverT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

newtype DeafT m a Source #

DeafT discards all output (much like >/dev/null in the shell)

Constructors

Deaf 

Fields

Instances

Instances details
MonadTrans DeafT Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

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

RedirectionTarget DiscardO DeafT a a Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (DeafT m)) => DeafT m a -> DiscardO -> m a Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (DeafT m)) => DeafT m a -> DiscardO -> m a Source #

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

Defined in Text.Chatty.Printer

Methods

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

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

return :: a -> DeafT m a #

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

Defined in Text.Chatty.Printer

Methods

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

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

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

Defined in Text.Chatty.Printer

Methods

pure :: a -> DeafT m a #

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

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

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

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

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

Defined in Text.Chatty.Printer

Methods

liftIO :: IO a -> DeafT m a #

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: DeafT m (Atom v) #

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

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

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

getAtom :: Atom v -> DeafT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

countOn :: DeafT m Int #

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

Defined in Text.Chatty.Interactor

Methods

expand :: String -> DeafT m String Source #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Methods

mgetv :: String -> DeafT m EnvVar Source #

mputv :: String -> EnvVar -> DeafT m () Source #

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

Defined in Text.Chatty.Interactor

Methods

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

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

mfin :: DeafT m () Source #

Monad m => ChPrinter (DeafT m) Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

mprint :: String -> DeafT m () Source #

mnoecho :: String -> DeafT m () Source #

mflush :: DeafT m () Source #

mnomask :: String -> DeafT m () Source #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

newtype OutRedirT m a Source #

Redirects all output to a given handle (much like >filename in the shell)

Constructors

OutRedir 

Fields

Instances

Instances details
MonadTrans OutRedirT Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

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

RedirectionTarget Handle OutRedirT a a Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> Handle -> m a Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> Handle -> m a Source #

RedirectionTarget FilePath OutRedirT a a Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> FilePath -> m a Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> FilePath -> m a Source #

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

Defined in Text.Chatty.Printer

Methods

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

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

return :: a -> OutRedirT m a #

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

Defined in Text.Chatty.Printer

Methods

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

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

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

Defined in Text.Chatty.Printer

Methods

pure :: a -> OutRedirT m a #

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

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

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

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

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

Defined in Text.Chatty.Printer

Methods

liftIO :: IO a -> OutRedirT m a #

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: OutRedirT m (Atom v) #

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

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

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

getAtom :: Atom v -> OutRedirT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

countOn :: OutRedirT m Int #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Methods

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

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

mfin :: OutRedirT m () Source #

MonadIO m => ChPrinter (OutRedirT m) Source # 
Instance details

Defined in Text.Chatty.Printer

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

type OutRedir = OutRedirT IO Source #

OutRedirT on a blank IO monad

newtype RecorderT m a Source #

Catches all output (much like VAR=$(...) in the shell)

Constructors

Recorder 

Fields

Instances

Instances details
MonadTrans RecorderT Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

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

RedirectionTarget RecordO RecorderT a (a, Replayable) Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #

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

Defined in Text.Chatty.Printer

Methods

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

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

return :: a -> RecorderT m a #

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

Defined in Text.Chatty.Printer

Methods

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

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

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

Defined in Text.Chatty.Printer

Methods

pure :: a -> RecorderT m a #

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

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

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

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

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

Defined in Text.Chatty.Printer

Methods

liftIO :: IO a -> RecorderT m a #

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: RecorderT m (Atom v) #

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

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

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

getAtom :: Atom v -> RecorderT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

countOn :: RecorderT m Int #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Methods

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

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

mfin :: RecorderT m () Source #

Monad m => ChPrinter (RecorderT m) Source # 
Instance details

Defined in Text.Chatty.Printer

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

newtype Replayable Source #

The recorder state. Use this together with replay, replayM or replay_.

Constructors

Replayable [String] 

Instances

Instances details
Show Replayable Source # 
Instance details

Defined in Text.Chatty.Printer

RedirectionTarget RecordO RecorderT a (a, Replayable) Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #

replay :: Replayable -> String Source #

Replay a recorder state in a pure context.

runRecorder :: Recorder a -> (a, Replayable) Source #

Run Recorder and also return its state.

runRecorderT :: (Functor m, Monad m) => RecorderT m a -> m (a, Replayable) Source #

Run RecorderT and also return its state.

mprintLn :: ChPrinter m => String -> m () Source #

Line-terminating alternative to mprint

mnomaskLn :: ChPrinter m => String -> m () Source #

Line-terminating alternative to mnomask

data DiscardO Source #

Redirection target that discards input.

Constructors

DiscardO 

Instances

Instances details
RedirectionTarget DiscardO DeafT a a Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (DeafT m)) => DeafT m a -> DiscardO -> m a Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (DeafT m)) => DeafT m a -> DiscardO -> m a Source #

data RecordO Source #

Redirection target that records input.

Constructors

RecordO 

Instances

Instances details
RedirectionTarget RecordO RecorderT a (a, Replayable) Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #

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

Class for all redirection targets.

Minimal complete definition

(.>.)

Methods

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

Overwriting redirection.

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

Appending redirection.

Instances

Instances details
RedirectionTarget Handle OutRedirT a a Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> Handle -> m a Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> Handle -> m a Source #

RedirectionTarget FilePath OutRedirT a a Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> FilePath -> m a Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (OutRedirT m)) => OutRedirT m a -> FilePath -> m a Source #

RedirectionTarget DiscardO DeafT a a Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (DeafT m)) => DeafT m a -> DiscardO -> m a Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (DeafT m)) => DeafT m a -> DiscardO -> m a Source #

RedirectionTarget RecordO RecorderT a (a, Replayable) Source # 
Instance details

Defined in Text.Chatty.Printer

Methods

(.>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #

(.>>.) :: (Functor m, MonadIO m, ChPrinter (RecorderT m)) => RecorderT m a -> RecordO -> m (a, Replayable) Source #