| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Data.Text.Prettyprint.Doc.Extra
Contents
Synopsis
- type Doc = Doc ()
 - layoutOneLine :: Doc ann -> SimpleDocStream ann
 - renderOneLine :: Doc ann -> Text
 - int :: Applicative f => Int -> f Doc
 - integer :: Applicative f => Integer -> f Doc
 - char :: Applicative f => Char -> f Doc
 - lbrace :: Applicative f => f Doc
 - rbrace :: Applicative f => f Doc
 - colon :: Applicative f => f Doc
 - semi :: Applicative f => f Doc
 - equals :: Applicative f => f Doc
 - comma :: Applicative f => f Doc
 - dot :: Applicative f => f Doc
 - lparen :: Applicative f => f Doc
 - rparen :: Applicative f => f Doc
 - space :: Applicative f => f Doc
 - brackets :: Functor f => f Doc -> f Doc
 - braces :: Functor f => f Doc -> f Doc
 - tupled :: Functor f => f [Doc] -> f Doc
 - (<+>) :: Applicative f => f Doc -> f Doc -> f Doc
 - vcat :: Functor f => f [Doc] -> f Doc
 - hcat :: Functor f => f [Doc] -> f Doc
 - nest :: Functor f => Int -> f Doc -> f Doc
 - indent :: Functor f => Int -> f Doc -> f Doc
 - parens :: Functor f => f Doc -> f Doc
 - emptyDoc :: Applicative f => f Doc
 - punctuate :: Applicative f => f Doc -> f [Doc] -> f [Doc]
 - encloseSep :: Applicative f => f Doc -> f Doc -> f Doc -> f [Doc] -> f Doc
 - line :: Applicative f => f Doc
 - line' :: Applicative f => f Doc
 - softline :: Applicative f => f Doc
 - softline' :: Applicative f => f Doc
 - pretty :: (Applicative f, Pretty a) => a -> f Doc
 - stringS :: Applicative f => Text -> f Doc
 - string :: Applicative f => Text -> f Doc
 - squotes :: Applicative f => f Doc -> f Doc
 - dquotes :: Functor f => f Doc -> f Doc
 - align :: Functor f => f Doc -> f Doc
 - hsep :: Functor f => f [Doc] -> f Doc
 - vsep :: Functor f => f [Doc] -> f Doc
 - isEmpty :: Doc -> Bool
 - fill :: Applicative f => Int -> f Doc -> f Doc
 - column :: Functor f => f (Int -> Doc) -> f Doc
 - nesting :: Functor f => f (Int -> Doc) -> f Doc
 - flatAlt :: Applicative f => f Doc -> f Doc -> f Doc
 - newtype LayoutOptions = LayoutOptions {}
 - data PageWidth
 - layoutCompact :: Doc ann -> SimpleDocStream ann
 - layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann
 - renderLazy :: SimpleDocStream ann -> Text
 
Documentation
layoutOneLine :: Doc ann -> SimpleDocStream ann Source #
renderOneLine :: Doc ann -> Text Source #
lbrace :: Applicative f => f Doc Source #
rbrace :: Applicative f => f Doc Source #
colon :: Applicative f => f Doc Source #
semi :: Applicative f => f Doc Source #
equals :: Applicative f => f Doc Source #
comma :: Applicative f => f Doc Source #
dot :: Applicative f => f Doc Source #
lparen :: Applicative f => f Doc Source #
rparen :: Applicative f => f Doc Source #
space :: Applicative f => f Doc Source #
emptyDoc :: Applicative f => f Doc Source #
encloseSep :: Applicative f => f Doc -> f Doc -> f Doc -> f [Doc] -> f Doc Source #
line :: Applicative f => f Doc Source #
line' :: Applicative f => f Doc Source #
softline :: Applicative f => f Doc Source #
softline' :: Applicative f => f Doc Source #
newtype LayoutOptions #
Options to influence the layout algorithms.
Constructors
| LayoutOptions | |
Fields  | |
Instances
| Eq LayoutOptions | |
Defined in Data.Text.Prettyprint.Doc.Internal Methods (==) :: LayoutOptions -> LayoutOptions -> Bool # (/=) :: LayoutOptions -> LayoutOptions -> Bool #  | |
| Ord LayoutOptions | |
Defined in Data.Text.Prettyprint.Doc.Internal Methods compare :: LayoutOptions -> LayoutOptions -> Ordering # (<) :: LayoutOptions -> LayoutOptions -> Bool # (<=) :: LayoutOptions -> LayoutOptions -> Bool # (>) :: LayoutOptions -> LayoutOptions -> Bool # (>=) :: LayoutOptions -> LayoutOptions -> Bool # max :: LayoutOptions -> LayoutOptions -> LayoutOptions # min :: LayoutOptions -> LayoutOptions -> LayoutOptions #  | |
| Show LayoutOptions | |
Defined in Data.Text.Prettyprint.Doc.Internal Methods showsPrec :: Int -> LayoutOptions -> ShowS # show :: LayoutOptions -> String # showList :: [LayoutOptions] -> ShowS #  | |
Maximum number of characters that fit in one line. The layout algorithms
 will try not to exceed the set limit by inserting line breaks when applicable
 (e.g. via softline').
Constructors
| AvailablePerLine Int Double | Layouters should not exceed the specified space per line. 
  | 
| Unbounded | Layouters should not introduce line breaks on their own.  | 
Instances
| Eq PageWidth | |
| Ord PageWidth | |
Defined in Data.Text.Prettyprint.Doc.Internal  | |
| Show PageWidth | |
layoutCompact :: Doc ann -> SimpleDocStream ann #
(layoutCompact x) lays out the document x without adding any
 indentation. Since no 'pretty' printing is involved, this layouter is very
 fast. The resulting output contains fewer characters than a prettyprinted
 version and can be used for output that is read by other programs.
>>>let doc = hang 4 (vsep ["lorem", "ipsum", hang 4 (vsep ["dolor", "sit"])])>>>doclorem ipsum dolor sit
>>>let putDocCompact = renderIO System.IO.stdout . layoutCompact>>>putDocCompact doclorem ipsum dolor sit
layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann #
This is the default layout algorithm, and it is used by show, putDoc
 and hPutDoc.
 commits to rendering something in a certain way if the next
 element fits the layout constraints; in other words, it has one
 layoutPrettySimpleDocStream element lookahead when rendering. Consider using the
 smarter, but a bit less performant,  algorithm if the results
 seem to run off to the right before having lots of line breaks.layoutSmart
renderLazy :: SimpleDocStream ann -> Text #
( takes the output renderLazy sdoc)sdoc from a rendering function
 and transforms it to lazy text.
>>>let render = TL.putStrLn . renderLazy . layoutPretty defaultLayoutOptions>>>let doc = "lorem" <+> align (vsep ["ipsum dolor", parens "foo bar", "sit amet"])>>>render doclorem ipsum dolor (foo bar) sit amet
Orphan instances
| Applicative f => IsString (f Doc) Source # | |
Methods fromString :: String -> f Doc #  | |