mainland-pretty-0.7.1: Pretty printing designed for printing source code.
Copyright(c) 2006-2011 Harvard University
(c) 2011-2012 Geoffrey Mainland
(c) 2015-2017 Drexel University
LicenseBSD-style
Maintainermainland@drexel.edu
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.PrettyPrint.Mainland.Class

Description

This module is based on A Prettier Printer by Phil Wadler in The Fun of Programming, Jeremy Gibbons and Oege de Moor (eds) http://homepages.inf.ed.ac.uk/wadler/papers/prettier/prettier.pdf

At the time it was originally written I didn't know about Daan Leijen's pretty printing module based on the same paper. I have since incorporated many of his improvements. This module is geared towards pretty printing source code; its main advantages over other libraries are the ability to automatically track the source locations associated with pretty printed values and output appropriate #line pragmas and the use of Text for output.

Synopsis

The Pretty type class for pretty printing

class Pretty a where Source #

Minimal complete definition

pprPrec | ppr

Methods

ppr :: a -> Doc Source #

pprPrec :: Int -> a -> Doc Source #

pprList :: [a] -> Doc Source #

Instances

Instances details
Pretty Bool Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Bool -> Doc Source #

pprPrec :: Int -> Bool -> Doc Source #

pprList :: [Bool] -> Doc Source #

Pretty Char Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Char -> Doc Source #

pprPrec :: Int -> Char -> Doc Source #

pprList :: [Char] -> Doc Source #

Pretty Double Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Float Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Int Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int -> Doc Source #

pprPrec :: Int -> Int -> Doc Source #

pprList :: [Int] -> Doc Source #

Pretty Int8 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Int8 -> Doc Source #

pprPrec :: Int -> Int8 -> Doc Source #

pprList :: [Int8] -> Doc Source #

Pretty Int16 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Int32 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Int64 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Integer Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Word8 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Word16 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Word32 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty Word64 Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Pretty () Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: () -> Doc Source #

pprPrec :: Int -> () -> Doc Source #

pprList :: [()] -> Doc Source #

Pretty Pos Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Pos -> Doc Source #

pprPrec :: Int -> Pos -> Doc Source #

pprList :: [Pos] -> Doc Source #

Pretty Loc Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Loc -> Doc Source #

pprPrec :: Int -> Loc -> Doc Source #

pprList :: [Loc] -> Doc Source #

Pretty Text Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Text -> Doc Source #

pprPrec :: Int -> Text -> Doc Source #

pprList :: [Text] -> Doc Source #

Pretty Text Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Text -> Doc Source #

pprPrec :: Int -> Text -> Doc Source #

pprList :: [Text] -> Doc Source #

Pretty Doc Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Doc -> Doc Source #

pprPrec :: Int -> Doc -> Doc Source #

pprList :: [Doc] -> Doc Source #

Pretty a => Pretty [a] Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: [a] -> Doc Source #

pprPrec :: Int -> [a] -> Doc Source #

pprList :: [[a]] -> Doc Source #

Pretty a => Pretty (Maybe a) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Maybe a -> Doc Source #

pprPrec :: Int -> Maybe a -> Doc Source #

pprList :: [Maybe a] -> Doc Source #

(Integral a, Pretty a) => Pretty (Ratio a) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Ratio a -> Doc Source #

pprPrec :: Int -> Ratio a -> Doc Source #

pprList :: [Ratio a] -> Doc Source #

(RealFloat a, Pretty a) => Pretty (Complex a) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Complex a -> Doc Source #

pprPrec :: Int -> Complex a -> Doc Source #

pprList :: [Complex a] -> Doc Source #

Pretty a => Pretty (Set a) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Set a -> Doc Source #

pprPrec :: Int -> Set a -> Doc Source #

pprList :: [Set a] -> Doc Source #

Pretty x => Pretty (L x) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: L x -> Doc Source #

pprPrec :: Int -> L x -> Doc Source #

pprList :: [L x] -> Doc Source #

(Pretty a, Pretty b) => Pretty (a, b) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b) -> Doc Source #

pprPrec :: Int -> (a, b) -> Doc Source #

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

(Pretty k, Pretty v) => Pretty (Map k v) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: Map k v -> Doc Source #

pprPrec :: Int -> Map k v -> Doc Source #

pprList :: [Map k v] -> Doc Source #

(Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c) -> Doc Source #

pprPrec :: Int -> (a, b, c) -> Doc Source #

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

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

Defined in Text.PrettyPrint.Mainland.Class

Methods

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

pprPrec :: Int -> (a, b, c, d) -> Doc Source #

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

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

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e) -> Doc Source #

pprList :: [(a, b, c, d, e)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f) -> Doc Source #

pprList :: [(a, b, c, d, e, f)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => Pretty (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i) => Pretty (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h, i) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h, i)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j) => Pretty (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h, i, j) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h, i, j)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k) => Pretty (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h, i, j, k) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l, Pretty m) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l, Pretty m, Pretty n) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Doc Source #

(Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h, Pretty i, Pretty j, Pretty k, Pretty l, Pretty m, Pretty n, Pretty o) => Pretty (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Text.PrettyPrint.Mainland.Class

Methods

ppr :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Doc Source #

pprPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Doc Source #

pprList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Doc Source #

pprint :: (Pretty a, MonadIO m) => a -> m () Source #

The pprint function outputs a value of any type that is an instance of Pretty to the standard output device by calling ppr and adding a newline.