wl-pprint-terminfo-3.7.1.4: A color pretty printer with terminfo support

Safe HaskellSafe
LanguageHaskell98

System.Console.Terminfo.PrettyPrint

Contents

Synopsis

Raw Effect (requires the effect be present)

data Effect Source #

Constructors

Push ScopedEffect 
Pop 
Ring Bell 

Instances

Eq Effect Source # 

Methods

(==) :: Effect -> Effect -> Bool #

(/=) :: Effect -> Effect -> Bool #

Graceful degradation

Effects (built with soft)

Colors (built with soft)

Ringing bells

data Bell Source #

Instances

Enum Bell Source # 

Methods

succ :: Bell -> Bell #

pred :: Bell -> Bell #

toEnum :: Int -> Bell #

fromEnum :: Bell -> Int #

enumFrom :: Bell -> [Bell] #

enumFromThen :: Bell -> Bell -> [Bell] #

enumFromTo :: Bell -> Bell -> [Bell] #

enumFromThenTo :: Bell -> Bell -> Bell -> [Bell] #

Eq Bell Source # 

Methods

(==) :: Bell -> Bell -> Bool #

(/=) :: Bell -> Bell -> Bool #

Ord Bell Source # 

Methods

compare :: Bell -> Bell -> Ordering #

(<) :: Bell -> Bell -> Bool #

(<=) :: Bell -> Bell -> Bool #

(>) :: Bell -> Bell -> Bool #

(>=) :: Bell -> Bell -> Bool #

max :: Bell -> Bell -> Bell #

min :: Bell -> Bell -> Bell #

Show Bell Source # 

Methods

showsPrec :: Int -> Bell -> ShowS #

show :: Bell -> String #

showList :: [Bell] -> ShowS #

A Color Pretty Printer

display :: (MonadIO m, PrettyTerm t) => t -> m () Source #

displayLn :: MonadIO m => PrettyTerm t => t -> m () Source #

Progressively less magical formatting

displayDoc :: (MonadIO m, PrettyTerm t) => Float -> t -> m () Source #

displayDoc' :: (MonadIO m, PrettyTerm t) => Terminal -> Float -> t -> m () Source #

displayDoc'' :: (MonadIO m, PrettyTerm t) => Terminal -> Float -> Int -> t -> m () Source #

A Classy Interface

class Pretty t => PrettyTerm t where Source #

Instances

PrettyTerm Bool Source # 
PrettyTerm Char Source # 
PrettyTerm Double Source # 
PrettyTerm Float Source # 
PrettyTerm Int Source # 
PrettyTerm Int8 Source # 
PrettyTerm Int16 Source # 
PrettyTerm Int32 Source # 
PrettyTerm Int64 Source # 
PrettyTerm Integer Source # 
PrettyTerm Word Source # 
PrettyTerm Word8 Source # 
PrettyTerm Word16 Source # 
PrettyTerm Word32 Source # 
PrettyTerm Word64 Source # 
PrettyTerm () Source # 
PrettyTerm Natural Source # 
PrettyTerm ByteString Source # 
PrettyTerm ByteString Source # 
PrettyTerm Text Source # 
PrettyTerm Text Source # 
PrettyTerm t => PrettyTerm [t] Source # 

Methods

prettyTerm :: [t] -> TermDoc Source #

prettyTermList :: [[t]] -> TermDoc Source #

PrettyTerm a => PrettyTerm (Maybe a) Source # 
PrettyTerm a => PrettyTerm (NonEmpty a) Source # 
PrettyTerm a => PrettyTerm (Seq a) Source # 
(~) * e Effect => PrettyTerm (Doc e) Source # 
(PrettyTerm a, PrettyTerm b) => PrettyTerm (a, b) Source # 

Methods

prettyTerm :: (a, b) -> TermDoc Source #

prettyTermList :: [(a, b)] -> TermDoc Source #

(PrettyTerm a, PrettyTerm b, PrettyTerm c) => PrettyTerm (a, b, c) Source # 

Methods

prettyTerm :: (a, b, c) -> TermDoc Source #

prettyTermList :: [(a, b, c)] -> TermDoc Source #

Evaluation

evalTermState :: Monad m => StateT TermState m a -> m a Source #