Agda-2.5.3.20180519: A dependently typed functional programming language and proof assistant

Safe HaskellSafe
LanguageHaskell2010

Agda.Utils.Pretty

Contents

Description

Pretty printing functions.

Synopsis

Pretty class

class Pretty a where Source #

While Show is for rendering data in Haskell syntax, Pretty is for displaying data to the world, i.e., the user and the environment.

Atomic data has no inner document structure, so just implement pretty as pretty a = text $ ... a ....

Methods

pretty :: a -> Doc Source #

prettyPrec :: Int -> a -> Doc Source #

prettyList :: [a] -> Doc Source #

Instances

Pretty Bool Source # 
Pretty Char Source # 
Pretty Int Source # 
Pretty Int32 Source # 
Pretty Integer Source # 
Pretty Doc Source # 
Pretty Polarity Source # 
Pretty Cmp Source # 
Pretty Flex Source # 
Pretty Rigid Source # 
Pretty Offset Source # 
Pretty CPUTime Source #

Print CPU time in milli (10^-3) seconds.

Pretty AbsolutePath Source # 
Pretty IntervalWithoutFile Source # 
Pretty PositionWithoutFile Source # 
Pretty ParseWarning Source # 
Pretty ParseError Source # 
Pretty MetaId Source # 
Pretty Access Source # 
Pretty TopLevelModuleName Source # 
Pretty QName Source # 
Pretty NamePart Source # 
Pretty Name Source # 
Pretty AmbiguousQName Source # 
Pretty ModuleName Source # 
Pretty QName Source # 
Pretty Name Source # 
Pretty Literal Source # 
Pretty Precedence Source # 
Pretty Label Source # 
Pretty Weight Source # 
Pretty Occurrence Source # 
Pretty Where Source # 
Pretty OccursWhere Source # 
Pretty Tel Source # 
Pretty Phase Source # 
Pretty ResolvedName Source # 
Pretty AbstractModule Source # 
Pretty AbstractName Source # 
Pretty NameSpace Source # 
Pretty LocalVar Source #

We show shadowed variables as prefixed by a ".", as not in scope.

Pretty ScopeInfo Source # 
Pretty NameSpaceId Source # 
Pretty Scope Source # 
Pretty Order Source # 
Pretty CallMatrix Source # 
Pretty DBPatVar Source # 
Pretty Clause Source # 
Pretty LevelAtom Source # 
Pretty PlusLevel Source # 
Pretty Level Source # 
Pretty Sort Source # 
Pretty Type Source # 
Pretty Term Source # 
Pretty ConHead Source # 
Pretty CompiledClauses Source # 
Pretty ScopeCopyInfo Source # 
Pretty DeclarationWarning Source # 
Pretty DeclarationException Source # 
Pretty CallInfo Source #

We only show the name of the callee.

Pretty Call Source # 
Pretty TermHead Source # 
Pretty Defn Source # 
Pretty Polarity Source # 
Pretty Definition Source # 
Pretty DisplayTerm Source # 
Pretty Section Source # 
Pretty NamedMeta Source # 
Pretty CompareDirection Source # 
Pretty Comparison Source # 
Pretty Interface Source # 
Pretty CheckpointId Source # 
Pretty ProblemId Source # 
Pretty AsBinding Source # 
Pretty Node Source # 
Pretty SplitTag Source # 
Pretty BlockingVar Source # 
Pretty SplitPatVar Source # 
Pretty SizeMeta Source # 
Pretty NamedRigid Source # 
Pretty Cl Source # 
Pretty CallPath Source #

Only show intermediate nodes. (Drop last CallInfo).

Pretty a => Pretty [a] Source # 

Methods

pretty :: [a] -> Doc Source #

prettyPrec :: Int -> [a] -> Doc Source #

prettyList :: [[a]] -> Doc Source #

Pretty a => Pretty (Maybe a) Source # 
Pretty a => Pretty (NonemptyList a) Source # 
Pretty flex => Pretty (PolarityAssignment flex) Source # 
Pretty a => Pretty (Lisp a) Source # 

Methods

pretty :: Lisp a -> Doc Source #

prettyPrec :: Int -> Lisp a -> Doc Source #

prettyList :: [Lisp a] -> Doc Source #

(Ord a, Pretty a) => Pretty (Benchmark a) Source #

Print benchmark as three-column table with totals.

(Pretty a, HasRange a) => Pretty (PrintRange a) Source # 
Pretty a => Pretty (Range' (Maybe a)) Source # 

Methods

pretty :: Range' (Maybe a) -> Doc Source #

prettyPrec :: Int -> Range' (Maybe a) -> Doc Source #

prettyList :: [Range' (Maybe a)] -> Doc Source #

Pretty a => Pretty (Interval' (Maybe a)) Source # 

Methods

pretty :: Interval' (Maybe a) -> Doc Source #

prettyPrec :: Int -> Interval' (Maybe a) -> Doc Source #

prettyList :: [Interval' (Maybe a)] -> Doc Source #

Pretty a => Pretty (Position' (Maybe a)) Source # 

Methods

pretty :: Position' (Maybe a) -> Doc Source #

prettyPrec :: Int -> Position' (Maybe a) -> Doc Source #

prettyList :: [Position' (Maybe a)] -> Doc Source #

Pretty a => Pretty (QNamed a) Source # 
Pretty cinfo => Pretty (CMSet cinfo) Source # 

Methods

pretty :: CMSet cinfo -> Doc Source #

prettyPrec :: Int -> CMSet cinfo -> Doc Source #

prettyList :: [CMSet cinfo] -> Doc Source #

Pretty cinfo => Pretty (CallMatrixAug cinfo) Source # 
Pretty cinfo => Pretty (CallGraph cinfo) Source #

Displays the recursion behaviour corresponding to a call graph.

Methods

pretty :: CallGraph cinfo -> Doc Source #

prettyPrec :: Int -> CallGraph cinfo -> Doc Source #

prettyList :: [CallGraph cinfo] -> Doc Source #

Pretty a => Pretty (Substitution' a) Source # 
Pretty a => Pretty (Pattern' a) Source # 
Pretty a => Pretty (Tele (Dom a)) Source # 

Methods

pretty :: Tele (Dom a) -> Doc Source #

prettyPrec :: Int -> Tele (Dom a) -> Doc Source #

prettyList :: [Tele (Dom a)] -> Doc Source #

Pretty tm => Pretty (Elim' tm) Source # 

Methods

pretty :: Elim' tm -> Doc Source #

prettyPrec :: Int -> Elim' tm -> Doc Source #

prettyList :: [Elim' tm] -> Doc Source #

Pretty a => Pretty (Case a) Source # 

Methods

pretty :: Case a -> Doc Source #

prettyPrec :: Int -> Case a -> Doc Source #

prettyList :: [Case a] -> Doc Source #

Pretty a => Pretty (WithArity a) Source # 
Pretty a => Pretty (SplitTreeLabel a) Source # 
Pretty a => Pretty (SplitTree' a) Source # 
(Pretty r, Pretty f) => Pretty (Solution r f) Source # 
(Pretty r, Pretty f) => Pretty (Constraint' r f) Source # 
(Pretty r, Pretty f) => Pretty (SizeExpr' r f) Source # 
(Pretty n, Pretty e) => Pretty (Edge n e) Source # 

Methods

pretty :: Edge n e -> Doc Source #

prettyPrec :: Int -> Edge n e -> Doc Source #

prettyList :: [Edge n e] -> Doc Source #

(Ord n, Pretty n, Pretty e) => Pretty (Graph n e) Source # 

Methods

pretty :: Graph n e -> Doc Source #

prettyPrec :: Int -> Graph n e -> Doc Source #

prettyList :: [Graph n e] -> Doc Source #

(Pretty rigid, Pretty flex) => Pretty (Node rigid flex) Source # 

Methods

pretty :: Node rigid flex -> Doc Source #

prettyPrec :: Int -> Node rigid flex -> Doc Source #

prettyList :: [Node rigid flex] -> Doc Source #

(Integral i, HasZero b, Pretty b) => Pretty (Matrix i b) Source # 

Methods

pretty :: Matrix i b -> Doc Source #

prettyPrec :: Int -> Matrix i b -> Doc Source #

prettyList :: [Matrix i b] -> Doc Source #

(Pretty a, Pretty b) => Pretty (OutputConstraint' a b) Source # 

prettyShow :: Pretty a => a -> String Source #

Use instead of show when printing to world.

Pretty instances

Doc utilities

prettyList_ :: Pretty a => [a] -> Doc Source #

Comma separated list, without the brackets.

mparens :: Bool -> Doc -> Doc Source #

Apply parens to Doc if boolean is true.

align :: Int -> [(String, Doc)] -> Doc Source #

align max rows lays out the elements of rows in two columns, with the second components aligned. The alignment column of the second components is at most max characters to the right of the left-most column.

Precondition: max > 0.

multiLineText :: String -> Doc Source #

Handles strings with newlines properly (preserving indentation)

(<?>) :: Doc -> Doc -> Doc infixl 6 Source #

a ? b = hang a 2 b

pshow :: Show a => a -> Doc Source #

pshow = text . pretty

Orphan instances

Data Doc Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Doc -> c Doc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Doc #

toConstr :: Doc -> Constr #

dataTypeOf :: Doc -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Doc) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc) #

gmapT :: (forall b. Data b => b -> b) -> Doc -> Doc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r #

gmapQ :: (forall d. Data d => d -> u) -> Doc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Doc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Doc -> m Doc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc -> m Doc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc -> m Doc #