Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
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
- data R a
- runR :: R () -> SpanStream -> CommentStream -> SourceType -> EnumSet Extension -> FixityMap -> LazyFixityMap -> Text
- txt :: Text -> R ()
- interferingTxt :: Text -> R ()
- atom :: Outputable a => a -> R ()
- space :: R ()
- newline :: R ()
- askSourceType :: R SourceType
- askFixityOverrides :: R FixityMap
- askFixityMap :: R LazyFixityMap
- inci :: R () -> R ()
- inciHalf :: R () -> R ()
- sitcc :: R () -> R ()
- data Layout
- enterLayout :: Layout -> R () -> R ()
- vlayout :: R a -> R a -> R a
- getLayout :: R Layout
- useBraces :: R () -> R ()
- dontUseBraces :: R () -> R ()
- canUseBraces :: R Bool
- data CommentPosition
- registerPendingCommentLine :: CommentPosition -> Text -> R ()
- trimSpanStream :: RealSrcSpan -> R ()
- nextEltSpan :: R (Maybe RealSrcSpan)
- popComment :: (RealLocated Comment -> Bool) -> R (Maybe (RealLocated Comment))
- getEnclosingSpan :: (RealSrcSpan -> Bool) -> R (Maybe RealSrcSpan)
- withEnclosingSpan :: RealSrcSpan -> R () -> R ()
- thisLineSpans :: R [RealSrcSpan]
- data SpanMark
- spanMarkSpan :: SpanMark -> RealSrcSpan
- data HaddockStyle
- setSpanMark :: SpanMark -> R ()
- getSpanMark :: R (Maybe SpanMark)
- isExtensionEnabled :: Extension -> R Bool
The R
monad
The R
monad hosts combinators that allow us to describe how to render
AST.
:: 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.
Internal functions
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
. To output txt
" "Outputable
Haskell entities like numbers use
atom
.
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.
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.
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.
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.
inciHalf :: R () -> R () Source #
In rare cases, we have to indent by a positive amount smaller
than indentStep
.
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.
Layout
options.
SingleLine | Put everything on single line |
MultiLine | Use multiple lines |
Do one or another thing depending on current Layout
.
Helpers for braces
dontUseBraces :: R () -> R () Source #
Make the inner computation omit braces around single-line layouts.
Special helpers for comment placement
data CommentPosition Source #
Modes for rendering of pending comments.
OnTheSameLine | Put the comment on the same line |
OnNextLine | Put the comment on next line |
Instances
Show CommentPosition Source # | |
Defined in Ormolu.Printer.Internal showsPrec :: Int -> CommentPosition -> ShowS # show :: CommentPosition -> String # showList :: [CommentPosition] -> ShowS # | |
Eq CommentPosition Source # | |
Defined in Ormolu.Printer.Internal (==) :: CommentPosition -> CommentPosition -> Bool # (/=) :: CommentPosition -> CommentPosition -> Bool # |
registerPendingCommentLine Source #
:: CommentPosition | Comment position |
-> Text |
|
-> 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.
:: 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.
:: (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
An auxiliary marker for keeping track of last output element.
HaddockSpan HaddockStyle RealSrcSpan | Haddock comment |
CommentSpan RealSrcSpan | Non-haddock comment |
StatementSpan RealSrcSpan | A statement in a do-block and such span |
spanMarkSpan :: SpanMark -> RealSrcSpan Source #