Safe Haskell | None |
---|---|
Language | Haskell98 |
Pretty printing.
- class (Annotated ast, Typeable ast) => Pretty ast
- pretty :: (Pretty ast, MonadState (PrintState s) m) => ast NodeInfo -> m ()
- prettyNoExt :: (Pretty ast, MonadState (PrintState s) m) => ast NodeInfo -> m ()
- getState :: Printer s s
- putState :: s -> Printer s ()
- modifyState :: (s -> s) -> Printer s ()
- write :: MonadState (PrintState s) m => Builder -> m ()
- newline :: MonadState (PrintState s) m => m ()
- space :: MonadState (PrintState s) m => m ()
- comma :: MonadState (PrintState s) m => m ()
- int :: (Integral n, MonadState (PrintState s) m) => n -> m ()
- string :: MonadState (PrintState s) m => String -> m ()
- maybeCtx :: MonadState (PrintState s) m => Maybe (Context NodeInfo) -> m ()
- printComment :: MonadState (PrintState s) m => Maybe SrcSpan -> ComInfo -> m ()
- printComments :: (Pretty ast, MonadState (PrintState s) m) => ComInfoLocation -> ast NodeInfo -> m ()
- withCaseContext :: MonadState (PrintState s) m => Bool -> m a -> m a
- rhsSeparator :: MonadState (PrintState s) m => m ()
- inter :: MonadState (PrintState s) m => m () -> [m ()] -> m ()
- spaced :: MonadState (PrintState s) m => [m ()] -> m ()
- lined :: MonadState (PrintState s) m => [m ()] -> m ()
- prefixedLined :: MonadState (PrintState s) m => Text -> [m ()] -> m ()
- commas :: MonadState (PrintState s) m => [m ()] -> m ()
- parens :: MonadState (PrintState s) m => m a -> m a
- brackets :: MonadState (PrintState s) m => m a -> m a
- braces :: MonadState (PrintState s) m => m a -> m a
- indented :: MonadState (PrintState s) m => Int64 -> m a -> m a
- column :: MonadState (PrintState s) m => Int64 -> m a -> m a
- getColumn :: MonadState (PrintState s) m => m Int64
- getLineNum :: MonadState (PrintState s) m => m Int64
- depend :: MonadState (PrintState s) m => m () -> m b -> m b
- dependBind :: MonadState (PrintState s) m => m a -> (a -> m b) -> m b
- swing :: MonadState (PrintState s) m => m () -> m b -> m b
- getIndentSpaces :: MonadState (PrintState s) m => m Int64
- getColumnLimit :: MonadState (PrintState s) m => m Int64
- nullBinds :: Binds NodeInfo -> Bool
- sandbox :: MonadState s m => m a -> m (a, s)
- pretty' :: (Pretty ast, Pretty (ast SrcSpanInfo), Functor ast, MonadState (PrintState s) m) => ast NodeInfo -> m ()
Printing
class (Annotated ast, Typeable ast) => Pretty ast Source
Pretty printing class.
prettyInternal
pretty :: (Pretty ast, MonadState (PrintState s) m) => ast NodeInfo -> m () Source
Pretty print using extenders.
prettyNoExt :: (Pretty ast, MonadState (PrintState s) m) => ast NodeInfo -> m () Source
Run the basic printer for the given node without calling an extension hook for this node, but do allow extender hooks in child nodes. Also auto-inserts comments.
User state
modifyState :: (s -> s) -> Printer s () Source
Modify the user state.
Insertion
write :: MonadState (PrintState s) m => Builder -> m () Source
Write out a string, updating the current position information.
newline :: MonadState (PrintState s) m => m () Source
Output a newline.
space :: MonadState (PrintState s) m => m () Source
Write a space.
comma :: MonadState (PrintState s) m => m () Source
Write a comma.
int :: (Integral n, MonadState (PrintState s) m) => n -> m () Source
Write an integral.
string :: MonadState (PrintState s) m => String -> m () Source
Write a string.
Common node types
maybeCtx :: MonadState (PrintState s) m => Maybe (Context NodeInfo) -> m () Source
Maybe render a class context.
printComment :: MonadState (PrintState s) m => Maybe SrcSpan -> ComInfo -> m () Source
Pretty print a comment.
printComments :: (Pretty ast, MonadState (PrintState s) m) => ComInfoLocation -> ast NodeInfo -> m () Source
Print comments of a node.
withCaseContext :: MonadState (PrintState s) m => Bool -> m a -> m a Source
Set the context to a case context, where RHS is printed with -> .
rhsSeparator :: MonadState (PrintState s) m => m () Source
Get the current RHS separator, either = or -> .
Interspersing
inter :: MonadState (PrintState s) m => m () -> [m ()] -> m () Source
Print all the printers separated by sep.
spaced :: MonadState (PrintState s) m => [m ()] -> m () Source
Print all the printers separated by spaces.
lined :: MonadState (PrintState s) m => [m ()] -> m () Source
Print all the printers separated by newlines.
prefixedLined :: MonadState (PrintState s) m => Text -> [m ()] -> m () Source
Print all the printers separated newlines and optionally a line prefix.
commas :: MonadState (PrintState s) m => [m ()] -> m () Source
Print all the printers separated by commas.
Wrapping
parens :: MonadState (PrintState s) m => m a -> m a Source
Wrap in parens.
brackets :: MonadState (PrintState s) m => m a -> m a Source
Wrap in brackets.
braces :: MonadState (PrintState s) m => m a -> m a Source
Wrap in braces.
Indentation
indented :: MonadState (PrintState s) m => Int64 -> m a -> m a Source
Increase indentation level by n spaces for the given printer.
column :: MonadState (PrintState s) m => Int64 -> m a -> m a Source
Set the (newline-) indent level to the given column for the given printer.
getColumn :: MonadState (PrintState s) m => m Int64 Source
Get the current indent level.
getLineNum :: MonadState (PrintState s) m => m Int64 Source
Get the current line number.
depend :: MonadState (PrintState s) m => m () -> m b -> m b Source
Make the latter's indentation depend upon the end column of the former.
dependBind :: MonadState (PrintState s) m => m a -> (a -> m b) -> m b Source
Make the latter's indentation depend upon the end column of the former.
swing :: MonadState (PrintState s) m => m () -> m b -> m b Source
Swing the second printer below and indented with respect to the first.
getIndentSpaces :: MonadState (PrintState s) m => m Int64 Source
Indent spaces, e.g. 2.
getColumnLimit :: MonadState (PrintState s) m => m Int64 Source
Column limit, e.g. 80
Predicates
Sandboxing
sandbox :: MonadState s m => m a -> m (a, s) Source
Play with a printer and then restore the state to what it was before.
Fallback
pretty' :: (Pretty ast, Pretty (ast SrcSpanInfo), Functor ast, MonadState (PrintState s) m) => ast NodeInfo -> m () Source
Pretty print using HSE's own printer. The Pretty
class here
is HSE's.