futhark-0.19.5: An optimising compiler for a functional, array-oriented language.
Safe HaskellTrustworthy
LanguageHaskell2010

Futhark.Util.Pretty

Description

A re-export of the prettyprinting library, along with some convenience functions.

Synopsis

Documentation

hPutDocLn :: Handle -> Doc -> IO () #

Render a document with a width of 80 and print it to the specified handle, followed by a newline.

hPutDoc :: Handle -> Doc -> IO () #

Render a document with a width of 80 and print it to the specified handle.

putDocLn :: Doc -> IO () #

Render a document with a width of 80 and print it to standard output, followed by a newline.

putDoc :: Doc -> IO () #

Render a document with a width of 80 and print it to standard output.

prettyPragmaLazyText :: Int -> Doc -> Text #

Render and convert a document to Text with #line pragmas. Uses a builder.

displayPragmaLazyText :: RDoc -> Text #

Display a rendered document with #line pragmas as Text. Uses a builder.

prettyLazyText :: Int -> Doc -> Text #

Render and display a document as Text. Uses a builder.

displayLazyText :: RDoc -> Text #

Display a rendered document as Text. Uses a builder.

prettyPragma :: Int -> Doc -> String #

Render and convert a document to a String with #line pragmas.

> let loc = Loc (Pos "filename" 3 5 7) (Pos "filename" 5 7 9)
> in  putStrLn $ prettyPragma 80 $ srcloc loc <> text "foo" </> text "bar" </> text "baz"

will be printed as

foo
#line 3 "filename"
bar
baz

prettyPragmaS :: Int -> Doc -> ShowS #

Render and display a document with #line pragmas.

displayPragmaS :: RDoc -> ShowS #

Display a rendered document with #line pragmas.

prettyCompact :: Doc -> String #

Render and convert a document to a String compactly.

prettyCompactS :: Doc -> ShowS #

Render and display a document compactly.

prettyS :: Int -> Doc -> ShowS #

Render and display a document.

displayS :: RDoc -> ShowS #

Display a rendered document.

renderCompact :: Doc -> RDoc #

Render a document without indentation on infinitely long lines. Since no 'pretty' printing is involved, this renderer is fast. The resulting output contains fewer characters.

render :: Int -> Doc -> RDoc #

Render a document given a maximum width.

errordoc :: Doc -> a #

Equivalent of error, but with a document instead of a string.

faildoc :: MonadFail m => Doc -> m a #

Equivalent of fail, but with a document instead of a string.

fillbreak :: Int -> Doc -> Doc #

The document fillbreak i d renders document d, appending spaces until the width is equal to i. If the width of d is already greater than i, the nesting level is increased by i and a line is appended.

fill :: Int -> Doc -> Doc #

The document fill i d renders document x, appending spaces until the width is equal to i. If the width of d is already greater than i, nothing is appended.

width :: Doc -> (Int -> Doc) -> Doc #

The document width d f is produced by concatenating d with the result of calling f with the width of the document d.

nesting :: (Int -> Doc) -> Doc #

The document column f is produced by calling f with the current nesting level.

column :: (Int -> Doc) -> Doc #

The document column f is produced by calling f with the current column.

nest :: Int -> Doc -> Doc #

The document nest i d renders the document d with the current indentation level increased by i.

indent :: Int -> Doc -> Doc #

The document indent i d renders d with a nesting level set to the current column plus i, including the first line.

hang :: Int -> Doc -> Doc #

The document hang i d renders d with a nesting level set to the current column plus i, not including the first line.

align :: Doc -> Doc #

The document align d renders d with a nesting level set to the current column.

list :: [Doc] -> Doc #

The document list ds separates ds with commas and encloses them with brackets.

tuple :: [Doc] -> Doc #

The document tuple ds separates ds with commas and encloses them with parentheses.

enclosesep :: Doc -> Doc -> Doc -> [Doc] -> Doc #

The document enclosesep l r p ds separates ds with the punctuation p and encloses the result using l and r. When wrapped, punctuation appears at the end of the line. The enclosed portion of the document is aligned one column to the right of the opening document.

> ws = map text (words "The quick brown fox jumps over the lazy dog")
> test = pretty 15 (enclosesep lparen rparen comma ws)

will be layed out as:

(The, quick,
 brown, fox,
 jumps, over,
 the, lazy,
 dog)

semisep :: [Doc] -> Doc #

The document semisep ds semicolon-space separates ds, aligning the resulting document to the current nesting level.

commasep :: [Doc] -> Doc #

The document commasep ds comma-space separates ds, aligning the resulting document to the current nesting level.

punctuate :: Doc -> [Doc] -> [Doc] #

The document punctuate p ds obeys the law:

punctuate p [d1, d2, ..., dn] = [d1 <> p, d2 <> p, ..., dn]

sep :: [Doc] -> Doc #

The document sep ds concatenates the documents ds with the space document as long as there is room, and uses line when there isn't.

cat :: [Doc] -> Doc #

The document cat ds concatenates the documents ds with the empty document as long as there is room, and uses line when there isn't.

stack :: [Doc] -> Doc #

The document stack ds concatenates the documents ds with line.

spread :: [Doc] -> Doc #

The document spread ds concatenates the documents ds with space.

folddoc :: (Doc -> Doc -> Doc) -> [Doc] -> Doc #

The document folddoc f ds obeys the laws:

parensIf :: Bool -> Doc -> Doc #

The document parensIf p d encloses the document d in parenthesis if p is True, and otherwise yields just d.

parens :: Doc -> Doc #

The document parens d encloses the aligned document d in (...).

brackets :: Doc -> Doc #

The document brackets d encloses the aligned document d in [...].

braces :: Doc -> Doc #

The document braces d encloses the aligned document d in {...}.

backquotes :: Doc -> Doc #

The document backquotes d encloses the aligned document d in `...`.

angles :: Doc -> Doc #

The document angles d encloses the aligned document d in <...>.

dquotes :: Doc -> Doc #

The document dquotes d encloses the aligned document d in "...".

squotes :: Doc -> Doc #

The document squotes d encloses the alinged document d in '...'.

enclose :: Doc -> Doc -> Doc -> Doc #

The document enclose l r d encloses the document d between the documents l and r using <>. It obeys the law

enclose l r d = l <> d <> r

flatten :: Doc -> Doc #

The document flatten d will flatten d to one line.

group :: Doc -> Doc #

The document group d will flatten d to one line if there is room for it, otherwise the original d.

(<|>) :: Doc -> Doc -> Doc infixl 3 #

Provide alternative layouts of the same content. Invariant: both arguments must flatten to the same document.

(<//>) :: Doc -> Doc -> Doc infixr 5 #

Concatenates two documents with a softbreak in between.

(<+/>) :: Doc -> Doc -> Doc infixr 5 #

Concatenates two documents with a softline in between, with identity empty.

(</>) :: Doc -> Doc -> Doc infixr 5 #

Concatenates two documents with a line in between, with identity empty.

(<+>) :: Doc -> Doc -> Doc infixr 6 #

Concatenates two documents with a space in between, with identity empty.

softbreak :: Doc #

Becomes empty if there is room, otherwise line.

softline :: Doc #

Becomes space if there is room, otherwise line.

pretty 11 $ text "foo" <+/> text "bar" <+/> text "baz" =="foo bar baz"
pretty  7 $ text "foo" <+/> text "bar" <+/> text "baz" == "foo bar\nbaz"
pretty  6 $ text "foo" <+/> text "bar" <+/> text "baz" == "foo\nbar\nbaz"

line :: Doc #

The document line advances to the next line and indents to the current indentation level. When undone by group, it behaves like space.

srcloc :: Located a => a -> Doc #

The document srcloc x tags the current line with locOf x. Only shown when running prettyPragma and friends.

empty :: Doc #

The empty document.

rparen :: Doc #

The document rparen consists of a right brace, ")".

lparen :: Doc #

The document lparen consists of a right brace, "(".

rbracket :: Doc #

The document rbracket consists of a right brace, "]".

lbracket :: Doc #

The document lbracket consists of a right brace, "[".

rbrace :: Doc #

The document rbrace consists of a right brace, "}".

lbrace :: Doc #

The document lbrace consists of a left brace, "{".

rangle :: Doc #

The document rangle consists of a greater-than sign, ">".

langle :: Doc #

The document langle consists of a less-than sign, "<".

dquote :: Doc #

The document dquote consists of a double quote, "\"".

squote :: Doc #

The document squote consists of a single quote, "\'".

backquote :: Doc #

The document backquote consists of a backquote, "`".

spaces :: Int -> Doc #

The document space n consists of n spaces.

space :: Doc #

The document space consists of a space, " ".

semi :: Doc #

The document semi consists of a semicolon, ";".

equals :: Doc #

The document equals consists of an equals sign, "=".

dot :: Doc #

The document dot consists of a period, ".".

comma :: Doc #

The document comma consists of a comma, ",".

colon :: Doc #

The document colon consists of a colon, ":".

star :: Doc #

The document star consists of an asterisk, "*".

lazyText :: Text -> Doc #

The document lazyText s consists of the Text s, which should not contain any newlines.

strictText :: Text -> Doc #

The document strictText s consists of the Text s, which should not contain any newlines.

rational :: Rational -> Doc #

The document rational r is equivalent to text (show r).

double :: Double -> Doc #

The document double d is equivalent to text (show d).

float :: Float -> Doc #

The document float f is equivalent to text (show f).

integer :: Integer -> Doc #

The document integer i is equivalent to text (show i). text.

int :: Int -> Doc #

The document int i is equivalent to text (show i).

string :: String -> Doc #

The document string s consists of all the characters in s but with newlines replaced by line.

char :: Char -> Doc #

The document char c consists the single character c.

bool :: Bool -> Doc #

The document bool b is equivalent to text (show b).

text :: String -> Doc #

The document text s consists of the string s, which should not contain any newlines. For a string that may include newlines, use string.

data Doc #

The abstract type of documents.

Instances

Instances details
IsString Doc 
Instance details

Defined in Text.PrettyPrint.Mainland

Methods

fromString :: String -> Doc #

Semigroup Doc 
Instance details

Defined in Text.PrettyPrint.Mainland

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.Mainland

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Pretty Doc 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Doc -> Doc #

pprPrec :: Int -> Doc -> Doc #

pprList :: [Doc] -> Doc #

data RDoc #

A rendered document.

Constructors

REmpty

The empty document

RChar !Char RDoc

A single character

RString !Int String RDoc

String with associated length (to avoid recomputation)

RText Text RDoc

Text

RLazyText Text RDoc

Text

RPos Pos RDoc

Tag output with source location

RLine !Int RDoc

A newline with the indentation of the subsequent line. If this is followed by a RPos, output an appropriate #line pragma before the newline.

pretty :: Pretty a => a -> String Source #

Prettyprint a value, wrapped to 80 characters.

prettyDoc :: Int -> Doc -> String Source #

Re-export of pretty.

prettyTuple :: Pretty a => [a] -> String Source #

Prettyprint a list enclosed in curly braces.

prettyText :: Pretty a => a -> Text Source #

Prettyprint a value to a Text, wrapped to 80 characters.

prettyTextOneLine :: Pretty a => a -> Text Source #

Prettyprint a value to a Text without any width restriction.

prettyOneLine :: Pretty a => a -> String Source #

Prettyprint a value without any width restriction.

apply :: [Doc] -> Doc Source #

The document apply ds separates ds with commas and encloses them with parentheses.

oneLine :: Doc -> Doc Source #

Make sure that the given document is printed on just a single line.

annot :: [Doc] -> Doc -> Doc Source #

Stack and prepend a list of Docs to another Doc, separated by a linebreak. If the list is empty, the second Doc will be returned without a preceding linebreak.

nestedBlock :: String -> String -> Doc -> Doc Source #

Surround the given document with enclosers and add linebreaks and indents.

textwrap :: String -> Doc Source #

Like text, but splits the string into words and permits line breaks between all of them.

shorten :: Pretty a => a -> Doc Source #

Prettyprint on a single line up to at most some appropriate number of characters, with trailing ... if necessary. Used for error messages.

commastack :: [Doc] -> Doc Source #

Like commasep, but a newline after every comma.