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

Text.Chatty.Expansion

Description

Provides generic string expansion

Synopsis

Documentation

class Monad e => ChExpand e where Source #

Typeclass for all string-expanding monads.

Methods

expand :: String -> e String Source #

Expand the given string.

Instances

Instances details
ChExpand IO Source # 
Instance details

Defined in Text.Chatty.Expansion.Vars

Methods

expand :: String -> IO String Source #

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Monad m => ChExpand (NullExpanderT m) Source # 
Instance details

Defined in Text.Chatty.Expansion

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

Defined in Text.Chatty.Expansion.History

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

Defined in Text.Chatty.Expansion.Vars

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

Methods

expand :: String -> DeafT m String Source #

(Functor m, ChExpand m) => ChExpand (HtmlPrinterT m) Source # 
Instance details

Defined in Text.Chatty.Extended.HTML

(Functor m, ChExpand m) => ChExpand (AnsiPrinterT m) Source # 
Instance details

Defined in Text.Chatty.Extended.ANSI

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

Defined in Text.Chatty.Interactor

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

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

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

newtype NullExpanderT m a Source #

Constructors

NullExpander 

Fields

Instances

Instances details
MonadTrans NullExpanderT Source # 
Instance details

Defined in Text.Chatty.Expansion

Methods

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

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Expansion

Methods

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

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

return :: a -> NullExpanderT m a #

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

Defined in Text.Chatty.Expansion

Methods

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

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

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

Defined in Text.Chatty.Expansion

Methods

pure :: a -> NullExpanderT m a #

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

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

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

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

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

Defined in Text.Chatty.Expansion

Methods

liftIO :: IO a -> NullExpanderT m a #

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

Defined in Text.Chatty.Interactor

Methods

newAtom :: NullExpanderT m (Atom v) #

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

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

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

getAtom :: Atom v -> NullExpanderT m v #

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

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

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

Defined in Text.Chatty.Interactor

Monad m => ChExpand (NullExpanderT m) Source # 
Instance details

Defined in Text.Chatty.Expansion

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor

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

Defined in Text.Chatty.Interactor