| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Text.Fixity
Description
Machinery for deciding whether an expression needs to be wrapped in parentheses or not.
Synopsis
- type Precedence = Double
- data Associativity
- data FixityOver prec = Fixity {
- _fixityAssociativity :: !Associativity
- _fixityPrecedence :: !prec
- type Fixity = FixityOver Precedence
- data Direction
- data RenderContextOver prec = RenderContext {
- _renderContextDirection :: !Direction
- _renderContextFixity :: !(FixityOver prec)
- type RenderContext = RenderContextOver Precedence
- encloseIn :: Ord prec => (a -> a) -> RenderContextOver prec -> FixityOver prec -> a -> a
- botFixity :: Fixity
- juxtFixity :: Fixity
- unitFixity :: Fixity
- topFixity :: Fixity
- botRenderContext :: RenderContext
- topRenderContext :: RenderContext
Documentation
type Precedence = Double Source #
Fractional precedence, so that it's always possible to squeeze an operator precedence between
two existing precedences. Ranges over [-20, 120]. A normal operator should have a precedence
within [0, 100). It might be useful to have a negative precedence if you're trying to model
some already existing system, for example in Haskell ($) has precedence 0, but clearly
if b then y else f $ x should be rendered without any parens, hence the precedence of
if_then_else_ is less than 0, i.e. negative.
The precedence of juxtaposition is 100. Normally you want juxtaposition to have the highest
precedence, but some languages have operators that bind tighter than juxtaposition, e.g.
Haskell's postfix _{_}: f z { x = y } means f (z {x = y}).
data Associativity Source #
Associativity of an operator.
Constructors
| LeftAssociative | |
| RightAssociative | |
| NonAssociative |
Instances
| Show Associativity Source # | |
Defined in Text.Fixity.Internal Methods showsPrec :: Int -> Associativity -> ShowS # show :: Associativity -> String # showList :: [Associativity] -> ShowS # | |
| Eq Associativity Source # | |
Defined in Text.Fixity.Internal Methods (==) :: Associativity -> Associativity -> Bool # (/=) :: Associativity -> Associativity -> Bool # | |
data FixityOver prec Source #
Fixity of an operator.
We allow unary operators to have associativity, because it's useful to distinguish
between an expression like -(-x) (unary minus, left-associative) and ~~b
(boolean NOT, right-associative).
Associativity of unary operators also matters when pretty-printing expressions like (-x) + y,
which is pretty-printed as -x + y, assuming unary minus has the same fixity as + (and both
the operators are left-associative). I.e. unary minus is handled just like the binary one:
(0 - x) + y is pretty-printed as 0 - x + y.
Postfix operators are handled similarly. E.g. if ! is left-associative, then (x!)! is
pretty-printed as x!! and if it's right-associative -- (x!)!.
The data type is parameterized, so that the user can choose precedence to be integer/fractional,
bounded/unbounded, etc (we could also allows operators to be partially or totally ordered, but
at the moment prec is required to implement Ord, i.e. it has to be totally ordered).
By default we go with bounded fractional precedence, see the main Text.Fixity module.
Constructors
| Fixity | |
Fields
| |
Instances
| Show prec => Show (FixityOver prec) Source # | |
Defined in Text.Fixity.Internal Methods showsPrec :: Int -> FixityOver prec -> ShowS # show :: FixityOver prec -> String # showList :: [FixityOver prec] -> ShowS # | |
| Eq prec => Eq (FixityOver prec) Source # | |
Defined in Text.Fixity.Internal Methods (==) :: FixityOver prec -> FixityOver prec -> Bool # (/=) :: FixityOver prec -> FixityOver prec -> Bool # | |
type Fixity = FixityOver Precedence Source #
FixityOver instantiated at Precedence.
Direction in which pretty-printing goes. For example in x + y x is pretty-printed to the
left of + and y is pretty-printed to the right of +.
Constructors
| ToTheLeft | |
| ToTheRight |
data RenderContextOver prec Source #
A context that an expression is being rendered in.
Constructors
| RenderContext | |
Fields
| |
Instances
| HasRenderContext RenderContext Source # | |
Defined in Text.PrettyBy.Fixity Methods | |
| Show prec => Show (RenderContextOver prec) Source # | |
Defined in Text.Fixity.Internal Methods showsPrec :: Int -> RenderContextOver prec -> ShowS # show :: RenderContextOver prec -> String # showList :: [RenderContextOver prec] -> ShowS # | |
| Eq prec => Eq (RenderContextOver prec) Source # | |
Defined in Text.Fixity.Internal Methods (==) :: RenderContextOver prec -> RenderContextOver prec -> Bool # (/=) :: RenderContextOver prec -> RenderContextOver prec -> Bool # | |
type RenderContext = RenderContextOver Precedence Source #
FixityOver instantiated at Precedence.
Arguments
| :: Ord prec | |
| => (a -> a) | Enclose a value of type |
| -> RenderContextOver prec | An outer context. |
| -> FixityOver prec | An inner fixity. |
| -> a | |
| -> a |
Enclose an a (using the provided function) if required or leave it as is.
The need for enclosing is determined from an outer RenderContext and the inner fixity.
A fixity with the lowest precedence. When used as a part of an outer context, never causes addition of parens.
juxtFixity :: Fixity Source #
The fixity of juxtaposition.
unitFixity :: Fixity Source #
The fixity of a unitary expression which is safe to render without parens in any context.
A fixity with the highest precedence. When used as a part of an outer context, always causes addition of parens.
botRenderContext :: RenderContext Source #
An initial RenderContext.
An expression printed in this context never gets enclosed in parens.
topRenderContext :: RenderContext Source #
An initial RenderContext.
An expression printed in this context always gets enclosed in parens.