silkscreen-0.0.0.3: Prettyprinting transformers.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Silkscreen

Description

Silkscreen is a library of pretty-printing transformers built around the prettyprinter package. This module defines the core Printer abstraction and a few instances.

More documentation can be found in Prettyprinter.

Synopsis

Printing

class Monoid p => Printer p where Source #

A Printer abstracts pretty-printing to allow the composition of behaviours such as e.g. rainbow parentheses, precedence handling, and so forth.

Minimal complete definition

liftDoc0, liftDoc1, liftDoc2, column, nesting, pageWidth

Associated Types

type Ann p Source #

The type of annotations supported by the printer.

We provide this as a type family instead of defining Printer over kind Type -> Type in order to allow instances to constrain annotations.

Methods

liftDoc0 :: Doc (Ann p) -> p Source #

Lift a Doc to a Printer.

liftDoc1 :: (Doc (Ann p) -> Doc (Ann p)) -> p -> p Source #

Lift a unary function on Doc to a Printer.

liftDoc2 :: (Doc (Ann p) -> Doc (Ann p) -> Doc (Ann p)) -> p -> p -> p Source #

Lift a binary function on Doc to a Printer.

enclosing :: p -> p -> p -> p Source #

enclosing l r x wraps x in l and r.

Distinct from enclose (which is not overloaded) so that enclose remains available as a convenience for appending documents without whatever extra semantics are implied by any particular Printer (rainbow precedences, resetting precedence, etc.).

Overloadable to support e.g. rainbow parentheses.

squotes :: p -> p Source #

Wrap the argument in single quotes.

The default definition is given in terms of enclosing. Overloadable to support e.g. rainbow quotes (or disabling of same, if desired).

dquotes :: p -> p Source #

Wrap the argument in double quotes.

The default definition is given in terms of enclosing. Overloadable to support e.g. rainbow quotes (or disabling of same, if desired).

parens :: p -> p Source #

Parenthesize the argument.

The default definition is given in terms of enclosing. Overloadable to support e.g. rainbow parentheses (or disabling of same, if desired).

brackets :: p -> p Source #

Wrap the argument in brackets.

The default definition is given in terms of enclosing. Overloadable to support e.g. rainbow brackets (or disabling of same, if desired).

braces :: p -> p Source #

Wrap the argument in braces.

The default definition is given in terms of enclosing. Overloadable to support e.g. rainbow braces (or disabling of same, if desired).

angles :: p -> p Source #

Wrap the argument in angle brackets.

The default definition is given in terms of enclosing. Overloadable to support e.g. rainbow angle brackets (or disabling of same, if desired).

column :: (Int -> p) -> p Source #

nesting :: (Int -> p) -> p Source #

pageWidth :: (PageWidth -> p) -> p Source #

Instances

Instances details
Printer (Doc ann) Source # 
Instance details

Defined in Silkscreen

Associated Types

type Ann (Doc ann) Source #

Methods

liftDoc0 :: Doc (Ann (Doc ann)) -> Doc ann Source #

liftDoc1 :: (Doc (Ann (Doc ann)) -> Doc (Ann (Doc ann))) -> Doc ann -> Doc ann Source #

liftDoc2 :: (Doc (Ann (Doc ann)) -> Doc (Ann (Doc ann)) -> Doc (Ann (Doc ann))) -> Doc ann -> Doc ann -> Doc ann Source #

enclosing :: Doc ann -> Doc ann -> Doc ann -> Doc ann Source #

squotes :: Doc ann -> Doc ann Source #

dquotes :: Doc ann -> Doc ann Source #

parens :: Doc ann -> Doc ann Source #

brackets :: Doc ann -> Doc ann Source #

braces :: Doc ann -> Doc ann Source #

angles :: Doc ann -> Doc ann Source #

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

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

pageWidth :: (PageWidth -> Doc ann) -> Doc ann Source #

Printer a => Printer (Rainbow a) Source # 
Instance details

Defined in Silkscreen.Printer.Rainbow

Associated Types

type Ann (Rainbow a) Source #

Printer b => Printer (a -> b) Source # 
Instance details

Defined in Silkscreen

Associated Types

type Ann (a -> b) Source #

Methods

liftDoc0 :: Doc (Ann (a -> b)) -> a -> b Source #

liftDoc1 :: (Doc (Ann (a -> b)) -> Doc (Ann (a -> b))) -> (a -> b) -> a -> b Source #

liftDoc2 :: (Doc (Ann (a -> b)) -> Doc (Ann (a -> b)) -> Doc (Ann (a -> b))) -> (a -> b) -> (a -> b) -> a -> b Source #

enclosing :: (a -> b) -> (a -> b) -> (a -> b) -> a -> b Source #

squotes :: (a -> b) -> a -> b Source #

dquotes :: (a -> b) -> a -> b Source #

parens :: (a -> b) -> a -> b Source #

brackets :: (a -> b) -> a -> b Source #

braces :: (a -> b) -> a -> b Source #

angles :: (a -> b) -> a -> b Source #

column :: (Int -> a -> b) -> a -> b Source #

nesting :: (Int -> a -> b) -> a -> b Source #

pageWidth :: (PageWidth -> a -> b) -> a -> b Source #

(Printer a, Printer b, Ann a ~ Ann b) => Printer (a, b) Source # 
Instance details

Defined in Silkscreen

Associated Types

type Ann (a, b) Source #

Methods

liftDoc0 :: Doc (Ann (a, b)) -> (a, b) Source #

liftDoc1 :: (Doc (Ann (a, b)) -> Doc (Ann (a, b))) -> (a, b) -> (a, b) Source #

liftDoc2 :: (Doc (Ann (a, b)) -> Doc (Ann (a, b)) -> Doc (Ann (a, b))) -> (a, b) -> (a, b) -> (a, b) Source #

enclosing :: (a, b) -> (a, b) -> (a, b) -> (a, b) Source #

squotes :: (a, b) -> (a, b) Source #

dquotes :: (a, b) -> (a, b) Source #

parens :: (a, b) -> (a, b) Source #

brackets :: (a, b) -> (a, b) Source #

braces :: (a, b) -> (a, b) Source #

angles :: (a, b) -> (a, b) Source #

column :: (Int -> (a, b)) -> (a, b) Source #

nesting :: (Int -> (a, b)) -> (a, b) Source #

pageWidth :: (PageWidth -> (a, b)) -> (a, b) Source #

(Bounded level, Printer a) => Printer (Prec level a) Source # 
Instance details

Defined in Silkscreen.Printer.Prec

Associated Types

type Ann (Prec level a) Source #

Methods

liftDoc0 :: Doc (Ann (Prec level a)) -> Prec level a Source #

liftDoc1 :: (Doc (Ann (Prec level a)) -> Doc (Ann (Prec level a))) -> Prec level a -> Prec level a Source #

liftDoc2 :: (Doc (Ann (Prec level a)) -> Doc (Ann (Prec level a)) -> Doc (Ann (Prec level a))) -> Prec level a -> Prec level a -> Prec level a Source #

enclosing :: Prec level a -> Prec level a -> Prec level a -> Prec level a Source #

squotes :: Prec level a -> Prec level a Source #

dquotes :: Prec level a -> Prec level a Source #

parens :: Prec level a -> Prec level a Source #

brackets :: Prec level a -> Prec level a Source #

braces :: Prec level a -> Prec level a Source #

angles :: Prec level a -> Prec level a Source #

column :: (Int -> Prec level a) -> Prec level a Source #

nesting :: (Int -> Prec level a) -> Prec level a Source #

pageWidth :: (PageWidth -> Prec level a) -> Prec level a Source #

Combinators

pretty :: (Printer p, Pretty t) => t -> p Source #

Pretty-print a value using the Pretty instance for its type.

prettyList :: (Printer p, Pretty t) => [t] -> p Source #

annotate :: Printer p => Ann p -> p -> p Source #

Annotate a Printer with an Ann p.

group :: Printer p => p -> p Source #

Try to unwrap the argument, if it will fit.

flatAlt :: Printer p => p -> p -> p Source #

Print the first argument by default, or the second when an enclosing group flattens it.

align :: Printer p => p -> p Source #

Indent lines in the argument to the current column.

hang :: Printer p => Int -> p -> p Source #

Indent following lines in the argument to the current column + some delta.

indent :: Printer p => Int -> p -> p Source #

Indent lines in the argument to the current column + some delta.

nest :: Printer p => Int -> p -> p Source #

nest i p changes the indentation level for new lines in p by i.

concatWith :: (Monoid p, Foldable t) => (p -> p -> p) -> t p -> p Source #

hsep :: Printer p => [p] -> p Source #

vsep :: Printer p => [p] -> p Source #

fillSep :: Printer p => [p] -> p Source #

sep :: Printer p => [p] -> p Source #

hcat :: Printer p => [p] -> p Source #

vcat :: Printer p => [p] -> p Source #

fillCat :: Printer p => [p] -> p Source #

cat :: Printer p => [p] -> p Source #

punctuate :: Printer p => p -> [p] -> [p] Source #

width :: Printer p => p -> (Int -> p) -> p Source #

fill :: Printer p => Int -> p -> p Source #

fillBreak :: Printer p => Int -> p -> p Source #

plural #

Arguments

:: (Num amount, Eq amount) 
=> doc

1 case

-> doc

other cases

-> amount 
-> doc 

(plural n one many) is one if n is 1, and many otherwise. A typical use case is adding a plural "s".

>>> let things = [True]
>>> let amount = length things
>>> pretty things <+> "has" <+> pretty amount <+> plural "entry" "entries" amount
[True] has 1 entry

enclose :: Printer p => p -> p -> p -> p Source #

enclose l r x wraps x in l and r.

encloseSep :: Printer p => p -> p -> p -> [p] -> p Source #

list :: Printer p => [p] -> p Source #

tupled :: Printer p => [p] -> p Source #

surround :: Printer p => p -> p -> p -> p Source #

surround x l r wraps x in l and r.

This is a reordering of enclose, but allows for convenient use in e.g. folds:

>>> 'foldr1' ('surround' ('pretty' ", ")) ['pretty' "apple", 'pretty' "banana"]
apple, banana

(<+>) :: Printer p => p -> p -> p infixr 6 Source #

Separate the arguments with a space.

(</>) :: Printer p => p -> p -> p infixr 6 Source #

Separate the arguments with a line.

Conditional combinators

parensIf :: Printer p => Bool -> p -> p Source #

Conditional parenthesization of a printer. Analogous to showParen, but for printers.

Symbols

space :: Printer p => p Source #

line :: Printer p => p Source #

line' :: Printer p => p Source #

semi :: Printer p => p Source #

comma :: Printer p => p Source #

colon :: Printer p => p Source #

dot :: Printer p => p Source #

slash :: Printer p => p Source #

pipe :: Printer p => p Source #

Re-exports

class Pretty a #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Instances

Instances details
Pretty Bool
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty ()
>>> pretty ()
()

The argument is not used,

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Void

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Text

(lazy Text instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty a => Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

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

Pretty a => Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

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

Pretty a => Pretty (Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

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

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

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

(Pretty a1, Pretty a2) => Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

data PageWidth #

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.

  • The Int is the number of characters, including whitespace, that fit in a line. A typical value is 80.
  • The Double is the ribbon with, i.e. the fraction of the total page width that can be printed on. This allows limiting the length of printable text per line. Values must be between 0 and 1, and 0.4 to 1 is typical.
Unbounded

Layouters should not introduce line breaks on their own.

Instances

Instances details
Eq PageWidth 
Instance details

Defined in Prettyprinter.Internal

Ord PageWidth 
Instance details

Defined in Prettyprinter.Internal

Show PageWidth 
Instance details

Defined in Prettyprinter.Internal