tpdb-1.3.3: Data Type for Rewriting Systems

Safe HaskellSafe
LanguageHaskell98

TPDB.Pretty

Contents

Synopsis

Documentation

data Doc :: * #

The abstract data type Doc represents pretty documents.

Doc 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
  

Instances

Show Doc 

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc 

Methods

fromString :: String -> Doc #

Monoid Doc 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Pretty Doc 

Methods

pretty :: Doc -> Doc #

prettyList :: [Doc] -> Doc #

data SimpleDoc :: * #

The data type SimpleDoc represents rendered documents and is used by the display functions.

The Int in SText contains the length of the string. The Int in SLine contains the indentation for that line. The library provides two default display functions displayS and displayIO. You can provide your own display function by writing a function from a SimpleDoc to your own output format.

renderCompact :: Doc -> SimpleDoc #

(renderCompact x) renders document x without adding any indentation. Since no 'pretty' printing is involved, this renderer is very fast. The resulting output contains fewer characters than a pretty printed version and can be used for output that is read by other programs.

displayIO :: Handle -> SimpleDoc -> IO () #

(displayIO handle simpleDoc) writes simpleDoc to the file handle handle. This function is used for example by hPutDoc:

hPutDoc handle doc = displayIO handle (renderPretty 0.4 100 doc)

class Pretty a where #

The member prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

Minimal complete definition

pretty

Instances

Pretty Bool 

Methods

pretty :: Bool -> Doc #

prettyList :: [Bool] -> Doc #

Pretty Char 

Methods

pretty :: Char -> Doc #

prettyList :: [Char] -> Doc #

Pretty Double 

Methods

pretty :: Double -> Doc #

prettyList :: [Double] -> Doc #

Pretty Float 

Methods

pretty :: Float -> Doc #

prettyList :: [Float] -> Doc #

Pretty Int 

Methods

pretty :: Int -> Doc #

prettyList :: [Int] -> Doc #

Pretty Integer 

Methods

pretty :: Integer -> Doc #

prettyList :: [Integer] -> Doc #

Pretty () 

Methods

pretty :: () -> Doc #

prettyList :: [()] -> Doc #

Pretty Text 

Methods

pretty :: Text -> Doc #

prettyList :: [Text] -> Doc #

Pretty Doc 

Methods

pretty :: Doc -> Doc #

prettyList :: [Doc] -> Doc #

Pretty Attributes # 
Pretty a => Pretty [a] 

Methods

pretty :: [a] -> Doc #

prettyList :: [[a]] -> Doc #

Pretty a => Pretty (Maybe a) 

Methods

pretty :: Maybe a -> Doc #

prettyList :: [Maybe a] -> Doc #

Pretty a => Pretty (Marked a) # 

Methods

pretty :: Marked a -> Doc #

prettyList :: [Marked a] -> Doc #

(Pretty a, Pretty b) => Pretty (a, b) 

Methods

pretty :: (a, b) -> Doc #

prettyList :: [(a, b)] -> Doc #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) 

Methods

pretty :: (a, b, c) -> Doc #

prettyList :: [(a, b, c)] -> Doc #

fsep :: [Doc] -> Doc Source #

sep :: [Doc] -> Doc Source #

hsep :: [Doc] -> Doc Source #

vsep :: [Doc] -> Doc Source #

vcat :: [Doc] -> Doc Source #

hcat :: [Doc] -> Doc Source #

brackets :: Doc -> Doc #

Document (brackets x) encloses document x in square brackets, "[" and "]".

angles :: Doc -> Doc #

Document (angles x) encloses document x in angles, "<" and ">".

braces :: Doc -> Doc #

Document (braces x) encloses document x in braces, "{" and "}".

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

The document (enclose l r x) encloses document x between documents l and r using (<>).

enclose l r x = l <> x <> r

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

(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 laid out on a page width of 20 as:

  (words,in,a,tuple)
  

But when the page width is 15, it is laid 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.)

comma :: Doc #

The document comma contains a comma, ",".

nest :: Int -> Doc -> Doc #

The document (nest i x) renders document x with the current indentation level increased by i (See also hang, align and indent).

nest 2 (text "hello" <$> text "world") <$> text "!"

outputs as:

  hello
    world
  !
  

empty :: Doc #

The empty document is, indeed, empty. Although empty has no content, it does have a 'height' of 1 and behaves exactly like (text "") (and is therefore not a unit of <$>).

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

The document (x <> y) concatenates document x and document y. It is an associative operation having empty as a left and right unit. (infixr 6)

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

($$) :: Doc -> Doc -> Doc Source #

Orphan instances

(Pretty a, Pretty b) => Pretty (Either a b) Source # 

Methods

pretty :: Either a b -> Doc #

prettyList :: [Either a b] -> Doc #

(Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) Source # 

Methods

pretty :: (a, b, c, d) -> Doc #

prettyList :: [(a, b, c, d)] -> Doc #