hindent-4.6.0: Extensible Haskell pretty printer

Safe HaskellNone
LanguageHaskell98

HIndent.Pretty

Contents

Description

Pretty printing.

Synopsis

Printing

class (Annotated ast, Typeable ast) => Pretty ast Source #

Pretty printing class.

Minimal complete definition

prettyInternal

Instances

Pretty ModuleName Source # 
Pretty SpecialCon Source # 
Pretty QName Source # 
Pretty Name Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Name NodeInfo -> m ()

Pretty QOp Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => QOp NodeInfo -> m ()

Pretty Module Source # 
Pretty ModuleHead Source # 
Pretty ExportSpecList Source # 
Pretty ExportSpec Source # 
Pretty ImportDecl Source # 
Pretty ImportSpecList Source # 
Pretty ImportSpec Source # 
Pretty Decl Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Decl NodeInfo -> m ()

Pretty DataOrNew Source # 
Pretty DeclHead Source # 
Pretty InstRule Source # 
Pretty InstHead Source # 
Pretty Deriving Source # 
Pretty Binds Source # 
Pretty IPBind Source # 
Pretty Match Source # 
Pretty QualConDecl Source # 
Pretty ConDecl Source # 
Pretty FieldDecl Source # 
Pretty ClassDecl Source # 
Pretty InstDecl Source # 
Pretty BangType Source # 
Pretty Rhs Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Rhs NodeInfo -> m ()

Pretty GuardedRhs Source # 
Pretty Type Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Type NodeInfo -> m ()

Pretty TyVarBind Source # 
Pretty Kind Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Kind NodeInfo -> m ()

Pretty FunDep Source # 
Pretty Context Source # 
Pretty Asst Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Asst NodeInfo -> m ()

Pretty Literal Source # 
Pretty Sign Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Sign NodeInfo -> m ()

Pretty Exp Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Exp NodeInfo -> m ()

Pretty Bracket Source # 
Pretty Splice Source # 
Pretty ModulePragma Source # 
Pretty Overlap Source # 
Pretty WarningText Source # 
Pretty Pat Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Pat NodeInfo -> m ()

Pretty PatField Source # 
Pretty Stmt Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Stmt NodeInfo -> m ()

Pretty QualStmt Source # 
Pretty FieldUpdate Source # 
Pretty Alt Source # 

Methods

prettyInternal :: MonadState (PrintState s) m => Alt NodeInfo -> m ()

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

getState :: Printer s s Source #

Get the user state.

putState :: s -> Printer s () Source #

Put the 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 -> Comment -> 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.

swingBy :: MonadState (PrintState s) m => Int64 -> m () -> m b -> m b Source #

Swing the second printer below and indented with respect to the first by the specified amount.

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.