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

Text.Chatty.Interactor

Description

Provides a bunch of derived instances for the various typeclasses.

Synopsis

Documentation

type IgnorantT m = QuietT (DeafT m) Source #

IgnorantT ignores all output and does not provide any input.

type Ignorant = IgnorantT Identity Source #

Ignorant is IgnorantT on the identity

type ChattyT m = HereStringT (RecorderT m) Source #

ChattyT simulates a console, actually taking input as a string and recording output.

type Chatty = ChattyT Identity Source #

Chatty is ChattyT on the identity

runIgnorantT :: Monad m => IgnorantT m a -> m a Source #

Run IgnorantT (does not take anything)

runIgnorant :: Ignorant a -> a Source #

Run Ignorant (does not take anything)

runChattyT :: (Monad m, Functor m) => ChattyT m a -> String -> m (a, String, Replayable) Source #

Run ChattyT. Takes input as a string and returns (result, remaining input, output).

runChatty :: Chatty a -> String -> (a, String, Replayable) Source #

Run Chatty. Takes input as a string and returns (result, remaining input, output).

(.|.) :: (Monad m, Functor m) => RecorderT m a -> HereStringT m b -> m b Source #

Connect the output of some function to the input of another one. Compare with a pipe (cmd1 | cmd2).

(.<$.) :: (Functor m, Monad m) => (String -> m b) -> RecorderT m a -> m b Source #

Runs the second function and feeds its output as an argument to the first one. Compare with process expansion ($(cmd)).

Orphan instances

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

newAtom :: HistoryT m (Atom v) #

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

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

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

getAtom :: Atom v -> HistoryT m v #

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

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

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

Methods

newAtom :: ExpanderT m (Atom v) #

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

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

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

getAtom :: Atom v -> ExpanderT m v #

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

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

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

Methods

newAtom :: HandleCloserT m (Atom v) #

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

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

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

getAtom :: Atom v -> HandleCloserT m v #

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

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

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

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

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

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

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

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

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

Methods

newAtom :: HtmlPrinterT m (Atom v) #

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

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

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

getAtom :: Atom v -> HtmlPrinterT m v #

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

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

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

Methods

newAtom :: AnsiPrinterT m (Atom v) #

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

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

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

getAtom :: Atom v -> AnsiPrinterT m v #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

newAtom :: ScannerBufferT m (Atom v) #

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

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

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

getAtom :: Atom v -> ScannerBufferT m v #

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

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

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

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

Methods

countOn :: HistoryT m Int #

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

Methods

countOn :: ExpanderT m Int #

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

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

Methods

countOn :: RecorderT m Int #

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

Methods

countOn :: OutRedirT m Int #

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

Methods

countOn :: DeafT m Int #

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

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

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

Methods

countOn :: JoinerT m Int #

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

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

Methods

countOn :: BoolFilterT m Int #

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

Methods

countOn :: IntFilterT m Int #

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

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

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

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

Methods

countOn :: InRedirT m Int #

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

Methods

countOn :: QuietT m Int #

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

Methods

countOn :: HereStringT m Int #

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

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

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

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

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

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

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

Methods

expand :: String -> DeafT m String Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

mgetv :: String -> DeafT m EnvVar Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

mfin :: CounterT m () Source #

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

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

Methods

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

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

mfin :: HistoryT m () Source #

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

Methods

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

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

mfin :: ExpanderT m () Source #

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

Methods

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

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

mfin :: RecorderT m () Source #

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

Methods

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

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

mfin :: OutRedirT m () Source #

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

Methods

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

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

mfin :: DeafT m () Source #

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

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

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

Methods

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

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

mfin :: JoinerT m () Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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