ormolu-0.5.3.0: A formatter for Haskell source code
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ormolu.Printer.Combinators

Description

Printing combinators. The definitions here are presented in such an order so you can just go through the Haddocks and by the end of the file you should have a pretty good idea how to program rendering logic.

Synopsis

The R monad

data R a Source #

The R monad hosts combinators that allow us to describe how to render AST.

Instances

Instances details
Applicative R Source # 
Instance details

Defined in Ormolu.Printer.Internal

Methods

pure :: a -> R a #

(<*>) :: R (a -> b) -> R a -> R b #

liftA2 :: (a -> b -> c) -> R a -> R b -> R c #

(*>) :: R a -> R b -> R b #

(<*) :: R a -> R b -> R a #

Functor R Source # 
Instance details

Defined in Ormolu.Printer.Internal

Methods

fmap :: (a -> b) -> R a -> R b #

(<$) :: a -> R b -> R a #

Monad R Source # 
Instance details

Defined in Ormolu.Printer.Internal

Methods

(>>=) :: R a -> (a -> R b) -> R b #

(>>) :: R a -> R b -> R b #

return :: a -> R a #

runR Source #

Arguments

:: R ()

Monad to run

-> SpanStream

Span stream

-> CommentStream

Comment stream

-> SourceType

Whether the source is a signature or a regular module

-> EnumSet Extension

Enabled extensions

-> FixityMap

Fixity overrides

-> LazyFixityMap

Fixity map

-> Text

Resulting rendition

Run R monad.

getEnclosingSpan Source #

Arguments

:: (RealSrcSpan -> Bool)

Predicate to use

-> R (Maybe RealSrcSpan) 

Get the first enclosing SrcSpan that satisfies given predicate.

Combinators

Basic

txt Source #

Arguments

:: Text

Text to output

-> R () 

Output a fixed Text fragment. The argument may not contain any line breaks. txt is used to output all sorts of “fixed” bits of syntax like keywords and pipes | in functional dependencies.

To separate various bits of syntax with white space use space instead of txt " ". To output Outputable Haskell entities like numbers use atom.

atom :: Outputable a => a -> R () Source #

Output Outputable fragment of AST. This can be used to output numeric literals and similar. Everything that doesn't have inner structure but does have an Outputable instance.

space :: R () Source #

This primitive does not necessarily output a space. It just ensures that the next thing that will be printed on the same line will be separated by a single space from the previous output. Using this combinator twice results in at most one space.

In practice this design prevents trailing white space and makes it hard to output more than one delimiting space in a row, which is what we usually want.

newline :: R () Source #

Output a newline. First time newline is used after some non-newline output it gets inserted immediately. Second use of newline does not output anything but makes sure that the next non-white space output will be prefixed by a newline. Using newline more than twice in a row has no effect. Also, using newline at the very beginning has no effect, this is to avoid leading whitespace.

Similarly to space, this design prevents trailing newlines and makes it hard to output more than one blank newline in a row.

inci :: R () -> R () Source #

Increase indentation level by one indentation step for the inner computation. inci should be used when a part of code must be more indented relative to the parts outside of inci in order for the output to be valid Haskell. When layout is single-line there is no obvious effect, but with multi-line layout correct indentation levels matter.

inciIf Source #

Arguments

:: Bool

Whether to indent

-> R ()

The expression to indent

-> R () 

Indent the inner expression if the first argument is True.

inciHalf :: R () -> R () Source #

In rare cases, we have to indent by a positive amount smaller than indentStep.

askSourceType :: R SourceType Source #

Return the source type.

askFixityOverrides :: R FixityMap Source #

Retrieve fixity overrides map.

askFixityMap :: R LazyFixityMap Source #

Retrieve the lazy fixity map.

located Source #

Arguments

:: HasSrcSpan l 
=> GenLocated l a

Thing to enter

-> (a -> R ())

How to render inner value

-> R () 

Enter a GenLocated entity. This combinator handles outputting comments and sets layout (single-line vs multi-line) for the inner computation. Roughly, the rule for using located is that every time there is a Located wrapper, it should be “discharged” with a corresponding located invocation.

located' Source #

Arguments

:: HasSrcSpan l 
=> (a -> R ())

How to render inner value

-> GenLocated l a

Thing to enter

-> R () 

A version of located with arguments flipped.

switchLayout Source #

Arguments

:: [SrcSpan]

Span that controls layout

-> R ()

Computation to run with changed layout

-> R () 

Set layout according to combination of given SrcSpans for a given. Use this only when you need to set layout based on e.g. combined span of several elements when there is no corresponding Located wrapper provided by GHC AST. It is relatively rare that this one is needed.

Given empty list this function will set layout to single line.

data Layout Source #

Layout options.

Constructors

SingleLine

Put everything on single line

MultiLine

Use multiple lines

Instances

Instances details
Show Layout Source # 
Instance details

Defined in Ormolu.Printer.Internal

Eq Layout Source # 
Instance details

Defined in Ormolu.Printer.Internal

Methods

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

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

vlayout Source #

Arguments

:: R a

Single line

-> R a

Multi line

-> R a 

Do one or another thing depending on current Layout.

getLayout :: R Layout Source #

Get current Layout.

breakpoint :: R () Source #

Insert a space if enclosing layout is single-line, or newline if it's multiline.

breakpoint = vlayout space newline

breakpoint' :: R () Source #

Similar to breakpoint but outputs nothing in case of single-line layout.

breakpoint' = vlayout (return ()) newline

Formatting lists

sep Source #

Arguments

:: R ()

Separator

-> (a -> R ())

How to render an element

-> [a]

Elements to render

-> R () 

Render a collection of elements inserting a separator between them.

sepSemi Source #

Arguments

:: (a -> R ())

How to render an element

-> [a]

Elements to render

-> R () 

Render a collection of elements layout-sensitively using given printer, inserting semicolons if necessary and respecting useBraces and dontUseBraces combinators.

useBraces $ sepSemi txt ["foo", "bar"]
  == vlayout (txt "{ foo; bar }") (txt "foo\nbar")
dontUseBraces $ sepSemi txt ["foo", "bar"]
  == vlayout (txt "foo; bar") (txt "foo\nbar")

canUseBraces :: R Bool Source #

Return True if we can use braces in this context.

useBraces :: R () -> R () Source #

Make the inner computation use braces around single-line layouts.

dontUseBraces :: R () -> R () Source #

Make the inner computation omit braces around single-line layouts.

Wrapping

data BracketStyle Source #

BracketStyle controlling how closing bracket is rendered.

Constructors

N

Normal

S

Shifted one level

Instances

Instances details
Show BracketStyle Source # 
Instance details

Defined in Ormolu.Printer.Combinators

Eq BracketStyle Source # 
Instance details

Defined in Ormolu.Printer.Combinators

sitcc :: R () -> R () Source #

Set indentation level for the inner computation equal to current column. This makes sure that the entire inner block is uniformly "shifted" to the right.

backticks :: R () -> R () Source #

Surround given entity by backticks.

banana :: BracketStyle -> R () -> R () Source #

Surround given entity by banana brackets (i.e., from arrow notation.)

braces :: BracketStyle -> R () -> R () Source #

Surround given entity by curly braces { and }.

brackets :: BracketStyle -> R () -> R () Source #

Surround given entity by square brackets [ and ].

parens :: BracketStyle -> R () -> R () Source #

Surround given entity by parentheses ( and ).

parensHash :: BracketStyle -> R () -> R () Source #

Surround given entity by (# and #).

pragmaBraces :: R () -> R () Source #

Braces as used for pragmas: {-# and #-}.

pragma Source #

Arguments

:: Text

Pragma text

-> R ()

Pragma body

-> R () 

Surround the body with a pragma name and pragmaBraces.

Literals

comma :: R () Source #

Print ,.

commaDel :: R () Source #

Delimiting combination with comma. To be used with sep.

equals :: R () Source #

Print =. Do not use txt "=".

Stateful markers

data SpanMark Source #

An auxiliary marker for keeping track of last output element.

Constructors

HaddockSpan HaddockStyle RealSrcSpan

Haddock comment

CommentSpan RealSrcSpan

Non-haddock comment

StatementSpan RealSrcSpan

A statement in a do-block and such span

data HaddockStyle Source #

Haddock string style.

Constructors

Pipe
-- |
Caret
-- ^
Asterisk Int
-- *
Named String
-- $

setSpanMark Source #

Arguments

:: SpanMark

Span mark to set

-> R () 

Set span of last output comment.

getSpanMark :: R (Maybe SpanMark) Source #

Get span of last output comment.

Placement

data Placement Source #

Expression placement. This marks the places where expressions that implement handing forms may use them.

Constructors

Normal

Multi-line layout should cause insertion of a newline and indentation bump

Hanging

Expressions that have hanging form should use it and avoid bumping one level of indentation

Instances

Instances details
Show Placement Source # 
Instance details

Defined in Ormolu.Printer.Combinators

Eq Placement Source # 
Instance details

Defined in Ormolu.Printer.Combinators

placeHanging :: Placement -> R () -> R () Source #

Place a thing that may have a hanging form. This function handles how to separate it from preceding expressions and whether to bump indentation depending on what sort of expression we have.