| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.PrettyPrint
Contents
Synopsis
- displayPlain :: Display a => Int -> a -> Text
 - displayWithColor :: (HasRunner env, Display a, HasAnsiAnn (Ann a), MonadReader env m, HasLogFunc env, HasCallStack) => a -> m Text
 - prettyDebug :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m ()
 - prettyInfo :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m ()
 - prettyNote :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m ()
 - prettyWarn :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m ()
 - prettyError :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m ()
 - prettyWarnNoIndent :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m ()
 - prettyErrorNoIndent :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m ()
 - prettyDebugL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m ()
 - prettyInfoL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m ()
 - prettyNoteL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m ()
 - prettyWarnL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m ()
 - prettyErrorL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m ()
 - prettyWarnNoIndentL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m ()
 - prettyErrorNoIndentL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m ()
 - prettyDebugS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m ()
 - prettyInfoS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m ()
 - prettyNoteS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m ()
 - prettyWarnS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m ()
 - prettyErrorS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m ()
 - prettyWarnNoIndentS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m ()
 - prettyErrorNoIndentS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m ()
 - styleWarning :: AnsiDoc -> AnsiDoc
 - styleError :: AnsiDoc -> AnsiDoc
 - styleGood :: AnsiDoc -> AnsiDoc
 - styleShell :: AnsiDoc -> AnsiDoc
 - styleFile :: AnsiDoc -> AnsiDoc
 - styleUrl :: AnsiDoc -> AnsiDoc
 - styleDir :: AnsiDoc -> AnsiDoc
 - styleModule :: AnsiDoc -> AnsiDoc
 - styleCurrent :: AnsiDoc -> AnsiDoc
 - styleTarget :: AnsiDoc -> AnsiDoc
 - styleRecommendation :: AnsiDoc -> AnsiDoc
 - displayMilliseconds :: Double -> AnsiDoc
 - bulletedList :: [AnsiDoc] -> AnsiDoc
 - spacedBulletedList :: [AnsiDoc] -> AnsiDoc
 - debugBracket :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m, MonadUnliftIO m) => Doc AnsiAnn -> m a -> m a
 - class Display a where
 - type AnsiDoc = Doc AnsiAnn
 - newtype AnsiAnn = AnsiAnn [SGR]
 - class HasAnsiAnn a where
- getAnsiAnn :: a -> AnsiAnn
 - toAnsiDoc :: Doc a -> AnsiDoc
 
 - data Doc a
 - nest :: Int -> Doc a -> Doc a
 - line :: Doc a
 - linebreak :: Doc a
 - group :: Doc a -> Doc a
 - softline :: Doc a
 - softbreak :: Doc a
 - align :: Doc a -> Doc a
 - hang :: Int -> Doc a -> Doc a
 - indent :: Int -> Doc a -> Doc a
 - encloseSep :: Doc a -> Doc a -> Doc a -> [Doc a] -> Doc a
 - (<+>) :: Doc a -> Doc a -> Doc a
 - hsep :: [Doc a] -> Doc a
 - vsep :: [Doc a] -> Doc a
 - fillSep :: [Doc a] -> Doc a
 - sep :: [Doc a] -> Doc a
 - hcat :: [Doc a] -> Doc a
 - vcat :: [Doc a] -> Doc a
 - fillCat :: [Doc a] -> Doc a
 - cat :: [Doc a] -> Doc a
 - punctuate :: Doc a -> [Doc a] -> [Doc a]
 - fill :: Int -> Doc a -> Doc a
 - fillBreak :: Int -> Doc a -> Doc a
 - enclose :: Doc a -> Doc a -> Doc a -> Doc a
 - squotes :: Doc a -> Doc a
 - dquotes :: Doc a -> Doc a
 - parens :: Doc a -> Doc a
 - angles :: Doc a -> Doc a
 - braces :: Doc a -> Doc a
 - brackets :: Doc a -> Doc a
 - indentAfterLabel :: Doc a -> Doc a
 - wordDocs :: String -> [Doc a]
 - flow :: String -> Doc a
 
Pretty printing functions
displayWithColor :: (HasRunner env, Display a, HasAnsiAnn (Ann a), MonadReader env m, HasLogFunc env, HasCallStack) => a -> m Text Source #
Logging based on pretty-print typeclass
prettyDebug :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m () Source #
prettyInfo :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m () Source #
prettyNote :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m () Source #
prettyWarn :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m () Source #
prettyError :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m () Source #
prettyWarnNoIndent :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m () Source #
prettyErrorNoIndent :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => Doc AnsiAnn -> m () Source #
prettyDebugL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m () Source #
prettyInfoL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m () Source #
prettyNoteL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m () Source #
prettyWarnL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m () Source #
prettyErrorL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m () Source #
prettyWarnNoIndentL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m () Source #
prettyErrorNoIndentL :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => [Doc AnsiAnn] -> m () Source #
prettyDebugS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyInfoS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyNoteS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyWarnS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyErrorS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyWarnNoIndentS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m () Source #
prettyErrorNoIndentS :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m) => String -> m () Source #
Semantic styling functions
These are preferred to styling or colors directly, so that we can encourage consistency.
styleWarning :: AnsiDoc -> AnsiDoc Source #
Style an AnsiDoc as a warning. Should be used sparingly, not to style
   entire long messages. For example, it's used to style the "Warning:"
   label for an error message, not the entire message.
styleError :: AnsiDoc -> AnsiDoc Source #
Style an AnsiDoc as an error. Should be used sparingly, not to style
   entire long messages. For example, it's used to style the "Error:"
   label for an error message, not the entire message.
styleGood :: AnsiDoc -> AnsiDoc Source #
Style an AnsiDoc in a way to emphasize that it is a particularly good
   thing.
styleShell :: AnsiDoc -> AnsiDoc Source #
Style an AnsiDoc as a shell command, i.e. when suggesting something
   to the user that should be typed in directly as written.
styleUrl :: AnsiDoc -> AnsiDoc Source #
Style an AsciDoc as a URL.  For now using the same style as files.
styleCurrent :: AnsiDoc -> AnsiDoc Source #
Style an AnsiDoc in a way that emphasizes that it is related to
   a current thing. For example, could be used when talking about the
   current package we're processing when outputting the name of it.
styleTarget :: AnsiDoc -> AnsiDoc Source #
styleRecommendation :: AnsiDoc -> AnsiDoc Source #
Style used to highlight part of a recommended course of action.
displayMilliseconds :: Double -> AnsiDoc Source #
Formatting utils
spacedBulletedList :: [AnsiDoc] -> AnsiDoc Source #
Display a bulleted list of AnsiDoc with a blank line between
 each.
debugBracket :: (HasCallStack, HasRunner env, MonadReader env m, MonadIO m, MonadUnliftIO m) => Doc AnsiAnn -> m a -> m a Source #
Re-exports from Text.PrettyPrint.Leijen.Extended
class Display a where Source #
Minimal complete definition
Nothing
Instances
| Display ModuleName Source # | |
Defined in Stack.PrettyPrint Associated Types type Ann ModuleName :: Type Source # Methods display :: ModuleName -> Doc (Ann ModuleName) Source #  | |
| Display PackageName Source # | |
Defined in Stack.PrettyPrint Associated Types type Ann PackageName :: Type Source # Methods display :: PackageName -> Doc (Ann PackageName) Source #  | |
| Display Version Source # | |
| Display PackageIdentifier Source # | |
Defined in Stack.PrettyPrint Associated Types type Ann PackageIdentifier :: Type Source # Methods display :: PackageIdentifier -> Doc (Ann PackageIdentifier) Source #  | |
| Display (Doc a) Source # | |
| Display (PackageName, NamedComponent) Source # | |
Defined in Stack.PrettyPrint Associated Types type Ann (PackageName, NamedComponent) :: Type Source # Methods display :: (PackageName, NamedComponent) -> Doc (Ann (PackageName, NamedComponent)) Source #  | |
| Display (Path b Dir) Source # | |
| Display (Path b File) Source # | |
class HasAnsiAnn a where Source #
Minimal complete definition
Instances
| HasAnsiAnn () Source # | |
Defined in Text.PrettyPrint.Leijen.Extended  | |
| HasAnsiAnn AnsiAnn Source # | |
The abstract data type Doc a represents pretty documents.
Doc a is an instance of the Show class. (show doc) pretty
 prints document doc with a page width of 100 characters and a
 ribbon width of 40 characters.
show (text "hello" <$> text "world")
Which would return the string "hello\nworld", i.e.
hello world
The line document advances to the next line and indents to the
 current nesting level. Doc aument line behaves like (text " ")
 if the line break is undone by group.
The group combinator is used to specify alternative
 layouts. The document (group x) undoes all line breaks in
 document x. The resulting line is added to the current line if
 that fits the page. Otherwise, the document x is rendered without
 any changes.
The document (align x) renders document x with the nesting
 level set to the current column. It is used for example to
 implement hang.
As an example, we will put a document right above another one, regardless of the current nesting level:
x $$ y = align (x <$> y)
test = text "hi" <+> (text "nice" $$ text "world")
which will be layed out as:
hi nice world
hang :: Int -> Doc a -> Doc a #
The hang combinator implements hanging indentation. The document
 (hang i x) renders document x with a nesting level set to the
 current column plus i. The following example uses hanging
 indentation for some text:
test  = hang 4 (fillSep (map text
        (words "the hang combinator indents these words !")))Which lays out on a page with a width of 20 characters as:
the hang combinator
    indents these
    words !
The hang combinator is implemented as:
hang i x = align (nest i x)
indent :: Int -> Doc a -> Doc a #
The document (indent i x) indents document x with i spaces.
test  = indent 4 (fillSep (map text
        (words "the indent combinator indents these words !")))Which lays out with a page width of 20 as:
    the indent
    combinator
    indents these
    words !
encloseSep :: Doc a -> Doc a -> Doc a -> [Doc a] -> Doc a #
The document (encloseSep l r sep xs) concatenates the documents
 xs separated by sep and encloses the resulting document by l
 and r. The documents are rendered horizontally if that fits the
 page. Otherwise they are aligned vertically. All separators are put
 in front of the elements. For example, the combinator list can be
 defined with encloseSep:
list xs = encloseSep lbracket rbracket comma xs test = text "list" <+> (list (map int [10,200,3000]))
Which is layed out with a page width of 20 as:
list [10,200,3000]
But when the page width is 15, it is layed out as:
list [10
     ,200
     ,3000]
(<+>) :: Doc a -> Doc a -> Doc a infixr 6 #
The document (x <+> y) concatenates document x and y with a
 space in between.  (infixr 6)
The document (hsep xs) concatenates all documents xs
 horizontally with (<+>).
The document (vsep xs) concatenates all documents xs
 vertically with (<$>). If a group undoes the line breaks
 inserted by vsep, all documents are separated with a space.
someText = map text (words ("text to lay out"))
test     = text "some" <+> vsep someTextThis is layed out as:
some text to lay out
The align combinator can be used to align the documents under
 their first element
test = text "some" <+> align (vsep someText)
Which is printed as:
some text
     to
     lay
     out
The document (fillSep xs) concatenates documents xs
 horizontally with (<+>) as long as its fits the page, than
 inserts a line and continues doing that for all documents in
 xs.
fillSep xs = foldr (</>) empty xs
The document (sep xs) concatenates all documents xs either
 horizontally with (<+>), if it fits the page, or vertically with
 (<$>).
sep xs = group (vsep xs)
The document (hcat xs) concatenates all documents xs
 horizontally with (<>).
The document (vcat xs) concatenates all documents xs
 vertically with (<$$>). If a group undoes the line breaks
 inserted by vcat, all documents are directly concatenated.
The document (fillCat xs) concatenates documents xs
 horizontally with (<>) as long as its fits the page, than inserts
 a linebreak and continues doing that for all documents in xs.
fillCat xs = foldr (\<\/\/\>) empty xs
The document (cat xs) concatenates all documents xs either
 horizontally with (<>), if it fits the page, or vertically with
 (<$$>).
cat xs = group (vcat xs)
punctuate :: Doc a -> [Doc a] -> [Doc a] #
(punctuate p xs) concatenates all documents in xs with
 document p except for the last document.
someText = map text ["words","in","a","tuple"] test = parens (align (cat (punctuate comma someText)))
This is layed out on a page width of 20 as:
(words,in,a,tuple)
But when the page width is 15, it is layed out as:
(words, in, a, tuple)
(If you want put the commas in front of their elements instead of
 at the end, you should use tupled or, in general, encloseSep.)
fill :: Int -> Doc a -> Doc a #
The document (fill i x) renders document x. It than appends
 spaces until the width is equal to i. If the width of x is
 already larger, nothing is appended. This combinator is quite
 useful in practice to output a list of bindings. The following
 example demonstrates this.
types  = [("empty","Doc a")
         ,("nest","Int -> Doc a -> Doc a")
         ,("linebreak","Doc a")]
ptype (name,tp)
       = fill 6 (text name) <+> text "::" <+> text tp
test   = text "let" <+> align (vcat (map ptype types))Which is layed out as:
let empty  :: Doc a
    nest   :: Int -> Doc a -> Doc a
    linebreak :: Doc a
fillBreak :: Int -> Doc a -> Doc a #
The document (fillBreak i x) first renders document x. It
 than appends spaces until the width is equal to i. If the
 width of x is already larger than i, the nesting level is
 increased by i and a line is appended. When we redefine ptype
 in the previous example to use fillBreak, we get a useful
 variation of the previous output:
ptype (name,tp)
       = fillBreak 6 (text name) <+> text "::" <+> text tpThe output will now be:
let empty  :: Doc a
    nest   :: Int -> Doc a -> Doc a
    linebreak
           :: Doc a
enclose :: Doc a -> Doc a -> Doc a -> Doc a #
The document (enclose l r x) encloses document x between
 documents l and r using (<>).
enclose l r x = l <> x <> r
Document (brackets x) encloses document x in square brackets,
 "[" and "]".
indentAfterLabel :: Doc a -> Doc a Source #
Use after a label and before the rest of what's being labelled for consistent spacingindentingetc.
For example this is used after "Warning:" in warning messages.
Orphan instances
| Display ModuleName Source # | |
Associated Types type Ann ModuleName :: Type Source # Methods display :: ModuleName -> Doc (Ann ModuleName) Source #  | |
| Display PackageName Source # | |
Associated Types type Ann PackageName :: Type Source # Methods display :: PackageName -> Doc (Ann PackageName) Source #  | |
| Display Version Source # | |
| Display PackageIdentifier Source # | |
Associated Types type Ann PackageIdentifier :: Type Source # Methods display :: PackageIdentifier -> Doc (Ann PackageIdentifier) Source #  | |
| Display (PackageName, NamedComponent) Source # | |
Associated Types type Ann (PackageName, NamedComponent) :: Type Source # Methods display :: (PackageName, NamedComponent) -> Doc (Ann (PackageName, NamedComponent)) Source #  | |
| Display (Path b Dir) Source # | |
| Display (Path b File) Source # | |