Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Printer p => PrecedencePrinter p where
- setPrec :: PrecedencePrinter p => Level p -> p -> p
- prec :: (PrecedencePrinter p, Ord (Level p)) => Level p -> p -> p
- assoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> (p -> p -> p) -> p -> p -> p
- nonAssoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> Level p -> (p -> p -> p) -> p -> p -> p
- leftAssoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> Level p -> (p -> p -> p) -> p -> p -> p
- rightAssoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> Level p -> (p -> p -> p) -> p -> p -> p
- infix_ :: (PrecedencePrinter p, Ord (Level p)) => Level p -> (p -> p) -> (p -> p) -> (p -> p -> p) -> p -> p -> p
- module Silkscreen
Printing with precedence
class Printer p => PrecedencePrinter p where Source #
Pretty-printing with parenthesis insertion resolving precedence.
Given:
data ArithLevel = Bottom | Add | Mult | Exp | Top deriving (Eq, Ord) (+.) :: (PrecedencePrinter p, Level p ~ ArithLevel) => p -> p -> p (+.) =assoc
Add (surround
(pretty
" + ")) infixl 6 +. (*.) :: (PrecedencePrinter p, Level p ~ ArithLevel) => p -> p -> p (*.) =assoc
Mult (surround
(pretty
" * ")) infixl 7 *. (^.) :: (PrecedencePrinter p, Level p ~ ArithLevel) => p -> p -> p (^.) =rightAssoc
Exp Top (surround
(pretty
" ^ ")) infixr 8 ^.
>>>
putDoc . runPrec Bottom $ ('pretty' "a" +. 'pretty' "b") *. 'pretty' "c" ^. ('pretty' "d" *. 'pretty' "e")
(a + b) * c ^ (d * e)
The type used to represent precedence levels. This is defined as an associated type so that consumers can use e.g. symbolic representations of their DSL’s precedence levels instead of e.g. unsemantic Int
s.
This type will usually be Ord
ered, but this isn’t strictly required so that other means of determining precedence can be provided.
askingPrec :: (Level p -> p) -> p Source #
Print informed by the current Level
.
localPrec :: (Level p -> Level p) -> p -> p Source #
Locally change the Level
in a printer.
Instances
PrecedencePrinter p => PrecedencePrinter (Rainbow p) Source # | |
PrecedencePrinter b => PrecedencePrinter (a -> b) Source # | |
(Bounded level, Printer a) => PrecedencePrinter (Prec level a) Source # | |
setPrec :: PrecedencePrinter p => Level p -> p -> p Source #
Set a constant precedence.
This function does not insert parentheses, and thus should be used when inserting parentheses or otherwise resetting the precedence level.
prec :: (PrecedencePrinter p, Ord (Level p)) => Level p -> p -> p Source #
Set a constant precedence, parenthesizing in higher-precedence contexts.
assoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> (p -> p -> p) -> p -> p -> p Source #
Make an associative infix combinator at the given level.
nonAssoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> Level p -> (p -> p -> p) -> p -> p -> p Source #
Make a non-associative infix combinator at the given levels for the operator itself and its operands.
leftAssoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> Level p -> (p -> p -> p) -> p -> p -> p Source #
Make a left-associative infix combinator at the given levels for the operator itself and its right operand.
rightAssoc :: (PrecedencePrinter p, Ord (Level p)) => Level p -> Level p -> (p -> p -> p) -> p -> p -> p Source #
Make a right-associative infix combinator at the given levels for the operator itself and its left operand.
infix_ :: (PrecedencePrinter p, Ord (Level p)) => Level p -> (p -> p) -> (p -> p) -> (p -> p -> p) -> p -> p -> p Source #
Make an infix combinator at the given level for the operator itself, applying functions to either operand.
Re-exports
module Silkscreen