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

Text.Chatty.Channel.Printer

Description

Provides a printer class that offers several channels.

Synopsis

Documentation

class (ChPrinter m, Eq c) => ChChannelPrinter c m where Source #

Typeclass for all printers that offer several channels.

Minimal complete definition

cstart, cfin, cthis

Methods

cbracket :: c -> m a -> m a Source #

Run the function with the given channel.

cstart :: c -> m () Source #

Switch to the given channel

cfin :: c -> m () Source #

Return to the previous channel. The argument is bogus (just for type inference).

cprint :: c -> String -> m () Source #

Print the string to the given channel.

cthis :: m c Source #

Return the current channel.

Instances

Instances details
ChChannelPrinter Bool m => ChChannelPrinter Bool (AtomStoreT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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 Bool m => ChChannelPrinter Bool (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

ChChannelPrinter Int m => ChChannelPrinter Int (AnsiPrinterT 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 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 Int m => ChChannelPrinter Int (HereStringT m) Source # 
Instance details

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Channel.Printer

Methods

cbracket :: c -> JoinerT m a -> JoinerT m a Source #

cstart :: c -> JoinerT m () Source #

cfin :: c -> JoinerT m () Source #

cprint :: c -> String -> JoinerT m () Source #

cthis :: JoinerT m c Source #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Channel.Printer

Methods

cbracket :: c -> FilterT c m a -> FilterT c m a Source #

cstart :: c -> FilterT c m () Source #

cfin :: c -> FilterT c m () Source #

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

cthis :: FilterT c m c Source #

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

Defined in Text.Chatty.Channel.Printer

Methods

cbracket :: c -> ArchiverT c m a -> ArchiverT c m a Source #

cstart :: c -> ArchiverT c m () Source #

cfin :: c -> ArchiverT c m () Source #

cprint :: c -> String -> ArchiverT c m () Source #

cthis :: ArchiverT c m c Source #

newtype ArchiverT c m a Source #

Catches all output on multiple channels.

Constructors

Archiver 

Fields

Instances

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

Defined in Text.Chatty.Channel.Printer

Methods

cbracket :: c -> ArchiverT c m a -> ArchiverT c m a Source #

cstart :: c -> ArchiverT c m () Source #

cfin :: c -> ArchiverT c m () Source #

cprint :: c -> String -> ArchiverT c m () Source #

cthis :: ArchiverT c m c Source #

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: HandleArchiverT m (Atom v) #

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

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

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

getAtom :: Atom v -> HandleArchiverT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: BoolArchiverT m (Atom v) #

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

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

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

getAtom :: Atom v -> BoolArchiverT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: IntArchiverT m (Atom v) #

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

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

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

getAtom :: Atom v -> IntArchiverT m v #

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

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

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

MonadTrans (ArchiverT c) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

lift :: Monad m => m a -> ArchiverT c m a #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

ChFinalizer m => ChFinalizer (IntArchiverT 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

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

Defined in Text.Chatty.Channel.Printer

Methods

(>>=) :: ArchiverT c m a -> (a -> ArchiverT c m b) -> ArchiverT c m b #

(>>) :: ArchiverT c m a -> ArchiverT c m b -> ArchiverT c m b #

return :: a -> ArchiverT c m a #

Monad m => Functor (ArchiverT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

fmap :: (a -> b) -> ArchiverT c m a -> ArchiverT c m b #

(<$) :: a -> ArchiverT c m b -> ArchiverT c m a #

Monad m => Applicative (ArchiverT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

pure :: a -> ArchiverT c m a #

(<*>) :: ArchiverT c m (a -> b) -> ArchiverT c m a -> ArchiverT c m b #

liftA2 :: (a -> b -> c0) -> ArchiverT c m a -> ArchiverT c m b -> ArchiverT c m c0 #

(*>) :: ArchiverT c m a -> ArchiverT c m b -> ArchiverT c m b #

(<*) :: ArchiverT c m a -> ArchiverT c m b -> ArchiverT c m a #

MonadIO m => MonadIO (ArchiverT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

liftIO :: IO a -> ArchiverT c m a #

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

Defined in Text.Chatty.Channel.Printer

runArchiverT :: (Eq c, Monad m) => c -> ArchiverT c m a -> m (a, [(c, Replayable)]) Source #

newtype FilterT c m a Source #

Forwards output only on a specific channel.

Constructors

Filter 

Fields

Instances

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

Defined in Text.Chatty.Channel.Printer

Methods

cbracket :: c -> FilterT c m a -> FilterT c m a Source #

cstart :: c -> FilterT c m () Source #

cfin :: c -> FilterT c m () Source #

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

cthis :: FilterT c m c Source #

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: HandleFilterT m (Atom v) #

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

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

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

getAtom :: Atom v -> HandleFilterT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: BoolFilterT m (Atom v) #

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

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

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

getAtom :: Atom v -> BoolFilterT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: IntFilterT m (Atom v) #

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

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

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

getAtom :: Atom v -> IntFilterT m v #

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

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

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Methods

countOn :: BoolFilterT m Int #

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

Defined in Text.Chatty.Interactor

Methods

countOn :: IntFilterT m Int #

MonadTrans (FilterT c) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

lift :: Monad m => m a -> FilterT c m a #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

ChFinalizer m => ChFinalizer (IntFilterT 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

Monad m => Monad (FilterT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

(>>=) :: FilterT c m a -> (a -> FilterT c m b) -> FilterT c m b #

(>>) :: FilterT c m a -> FilterT c m b -> FilterT c m b #

return :: a -> FilterT c m a #

Monad m => Functor (FilterT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

fmap :: (a -> b) -> FilterT c m a -> FilterT c m b #

(<$) :: a -> FilterT c m b -> FilterT c m a #

Monad m => Applicative (FilterT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

pure :: a -> FilterT c m a #

(<*>) :: FilterT c m (a -> b) -> FilterT c m a -> FilterT c m b #

liftA2 :: (a -> b -> c0) -> FilterT c m a -> FilterT c m b -> FilterT c m c0 #

(*>) :: FilterT c m a -> FilterT c m b -> FilterT c m b #

(<*) :: FilterT c m a -> FilterT c m b -> FilterT c m a #

MonadIO m => MonadIO (FilterT c m) Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

liftIO :: IO a -> FilterT c m a #

(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 #

newtype JoinerT m a Source #

Joins all output regardless of its channel.

Constructors

Joiner 

Fields

Instances

Instances details
MonadTrans JoinerT Source # 
Instance details

Defined in Text.Chatty.Channel.Printer

Methods

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

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

Defined in Text.Chatty.Channel.Printer

Methods

cbracket :: c -> JoinerT m a -> JoinerT m a Source #

cstart :: c -> JoinerT m () Source #

cfin :: c -> JoinerT m () Source #

cprint :: c -> String -> JoinerT m () Source #

cthis :: JoinerT m c Source #

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

Defined in Text.Chatty.Channel.Printer

Methods

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

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

return :: a -> JoinerT m a #

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

Defined in Text.Chatty.Channel.Printer

Methods

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

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

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

Defined in Text.Chatty.Channel.Printer

Methods

pure :: a -> JoinerT m a #

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

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

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

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

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

Defined in Text.Chatty.Channel.Printer

Methods

liftIO :: IO a -> JoinerT m a #

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: JoinerT m (Atom v) #

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

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

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

getAtom :: Atom v -> JoinerT m v #

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

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

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

Defined in Text.Chatty.Interactor

Methods

countOn :: JoinerT m Int #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Methods

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

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

mfin :: JoinerT m () Source #

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

Defined in Text.Chatty.Channel.Printer

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

Defined in Text.Chatty.Interactor