fourmolu-0.8.2.0: A formatter for Haskell source code
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ormolu.Printer.Internal

Description

In most cases import Ormolu.Printer.Combinators instead, these functions are the low-level building blocks and should not be used on their own. The R monad is re-exported from Ormolu.Printer.Combinators as well.

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

-> PrinterOptsTotal 
-> 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.

Internal functions

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.

interferingTxt Source #

Arguments

:: Text

Text to output

-> R () 

Similar to txt but the text inserted this way is assumed to break the “link” between the preceding atom and its pending comments.

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.

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.

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.

inciBy :: Int -> R () -> R () Source #

Like inci, but indents by exactly the given number of steps.

inciByFrac :: Int -> R () -> R () Source #

Like inci, but indents by the given fraction of a full step.

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

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

inciByExact :: Int -> R () -> R () Source #

Like inci, but indents by exactly the given number of spaces.

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.

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

When using trailing commas, same as sitcc; when using leading commas, runs the input action unmodified.

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 #

enterLayout :: Layout -> R () -> R () Source #

Set Layout for internal computation.

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.

getPrinterOpt :: (forall f. PrinterOpts f -> f a) -> R a Source #

Get a particular PrinterOpts field from the environment.

Helpers for braces

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.

canUseBraces :: R Bool Source #

Return True if we can use braces in this context.

Special helpers for comment placement

data CommentPosition Source #

Modes for rendering of pending comments.

Constructors

OnTheSameLine

Put the comment on the same line

OnNextLine

Put the comment on next line

registerPendingCommentLine Source #

Arguments

:: CommentPosition

Comment position

-> Text

Text to output

-> R () 

Register a comment line for outputting. It will be inserted right before next newline. When the comment goes after something else on the same line, a space will be inserted between preceding text and the comment when necessary.

trimSpanStream Source #

Arguments

:: RealSrcSpan

Reference span

-> R () 

Drop elements that begin before or at the same place as given SrcSpan.

nextEltSpan :: R (Maybe RealSrcSpan) Source #

Get location of next element in AST.

popComment :: (RealLocated Comment -> Bool) -> R (Maybe (RealLocated Comment)) Source #

Pop a Comment from the CommentStream if given predicate is satisfied and there are comments in the stream.

getEnclosingSpan Source #

Arguments

:: (RealSrcSpan -> Bool)

Predicate to use

-> R (Maybe RealSrcSpan) 

Get the first enclosing SrcSpan that satisfies given predicate.

withEnclosingSpan :: RealSrcSpan -> R () -> R () Source #

Set SrcSpan of enclosing span for the given computation.

thisLineSpans :: R [RealSrcSpan] Source #

Get spans on this line so far.

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.

Extensions

data PrevTypeCtx Source #

What (if anything) precedes the current type on the same line Only used for the `function-arrows` setting

Instances

Instances details
Show PrevTypeCtx Source # 
Instance details

Defined in Ormolu.Printer.Internal

Eq PrevTypeCtx Source # 
Instance details

Defined in Ormolu.Printer.Internal