libcspm-1.0.0: A library providing a parser, type checker and evaluator for CSPM.

Safe HaskellSafe-Inferred

Util.MonadicPrettyPrint

Synopsis

Documentation

class (Applicative m, Monad m) => MonadicPrettyPrintable m a whereSource

Methods

prettyPrint :: a -> m DocSource

prettyPrintBrief :: a -> m DocSource

As prettyPrint, but yields a briefer description.

Instances

(Applicative m, Monad m) => MonadicPrettyPrintable m Name 
(Applicative m, Monad m) => MonadicPrettyPrintable m UnRenamedName 
(Applicative m, Monad m) => MonadicPrettyPrintable m OccName 
(Applicative m, Monad m, MonadicPrettyPrintable m TCExp, MonadicPrettyPrintable m UProc, MonadicPrettyPrintable m UProcOperator, MonadicPrettyPrintable m ValueSet) => MonadicPrettyPrintable m Value 
(Applicative m, Monad m, MonadicPrettyPrintable m Value) => MonadicPrettyPrintable m ScopeIdentifier 
(Applicative m, Monad m, MonadicPrettyPrintable m Value) => MonadicPrettyPrintable m ProcName 
(Applicative m, Monad m, MonadicPrettyPrintable m Value) => MonadicPrettyPrintable m Event 
(Applicative m, Monad m) => MonadicPrettyPrintable m TCExp 
(Applicative m, CSPMMonad m, MonadicPrettyPrintable EvaluationMonad a) => MonadicPrettyPrintable m a 
MonadicPrettyPrintable Identity ValueSet 
MonadicPrettyPrintable EvaluationMonad ValueSet 
(Applicative m, Monad m) => MonadicPrettyPrintable m (Exp Name) 
Foldable f => MonadicPrettyPrintable Identity (f Event) 
Foldable f => MonadicPrettyPrintable EvaluationMonad (f Event) 
(Applicative m, Foldable seq, Monad m, MonadicPrettyPrintable m evs) => MonadicPrettyPrintable m (ProcOperator seq evs) 
(Applicative m, Foldable seq, Functor seq, Monad m, MonadicPrettyPrintable m ev, MonadicPrettyPrintable m evs) => MonadicPrettyPrintable m (CSPOperator seq ev evs (seq (ev, ev))) 
(Foldable seq, Functor seq, MonadicPrettyPrintable m pn, MonadicPrettyPrintable m ev, MonadicPrettyPrintable m evs) => MonadicPrettyPrintable m (Proc seq CSPOperator pn ev evs (seq (ev, ev))) 

ppBinaryOp :: (MonadicPrettyPrintable m a, Precedence a) => a -> m Doc -> a -> a -> m DocSource

ppBinaryOp' :: (MonadicPrettyPrintable m a, Precedence a) => a -> m Doc -> a -> a -> m DocSource

tabWidth :: IntSource

The width, in spaces, of a tab character.

tabIndent :: (Monad m, Applicative m) => m Doc -> m DocSource

Indent a document by tabWidth characters, on each line (uses nest).

shortDouble :: (Monad m, Applicative m) => Int -> Double -> m DocSource

Show a double d printing only places places after the decimal place.

commaSeparatedInt :: (Monad m, Applicative m) => Int -> m DocSource

Pretty prints an integer and separates it into groups of 3, separated by commas.

angles :: (Monad m, Applicative m) => m Doc -> m DocSource

Surrounds a Doc with < and >.

bars :: (Monad m, Applicative m) => m Doc -> m DocSource

Surrounds a Doc with '|'.

list :: (Monad m, Applicative m) => m [Doc] -> m DocSource

Separates a list of Docs by ','.

dotSep :: (Monad m, Applicative m) => m [Doc] -> m DocSource

Separates a list of Docs by ..

speakNth :: (Monad m, Applicative m) => Int -> m DocSource

Converts a number into first, second etc.

punctuateFront :: (Monad m, Applicative m) => m Doc -> m [Doc] -> m [Doc]Source

Equivalent to [d1, sep d2, sep d3, ...].