haskell-src-exts-1.3.5: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printerSource codeContentsIndex
Language.Haskell.Exts.Fixity
Portabilityportable
Stabilitystable
MaintainerNiklas Broberg, d00nibro@chalmers.se
Contents
Fixity representation
Collections of fixities
Applying fixities to an AST
Description
Fixity information to give the parser so that infix operators can be parsed properly.
Synopsis
data Fixity = Fixity Assoc Int Op
infix_ :: Int -> [String] -> [Fixity]
infixl_ :: Int -> [String] -> [Fixity]
infixr_ :: Int -> [String] -> [Fixity]
preludeFixities :: [Fixity]
baseFixities :: [Fixity]
class AppFixity ast where
applyFixities :: [Fixity] -> ast -> ast
Fixity representation
data Fixity Source
Operator fixities are represented by their associativity (left, right or none) and their precedence (0-9).
Constructors
Fixity Assoc Int Op

The following three functions all create lists of fixities from textual representations of operators. The intended usage is e.g.

 fixs = infixr_ 0  ["$","$!","`seq`"]

Note that the operators are expected as you would write them infix, i.e. with ` characters surrounding varid operators, and varsym operators written as is.

infix_ :: Int -> [String] -> [Fixity]Source
infixl_ :: Int -> [String] -> [Fixity]Source
infixr_ :: Int -> [String] -> [Fixity]Source
Collections of fixities
preludeFixities :: [Fixity]Source
All fixities defined in the Prelude.
baseFixities :: [Fixity]Source

All fixities defined in the base package.

Note that the +++ operator appears in both Control.Arrows and Text.ParserCombinators.ReadP. The listed precedence for +++ in this list is that of Control.Arrows.

Applying fixities to an AST
class AppFixity ast whereSource
All AST elements that may include expressions which in turn may need fixity tweaking will be instances of this class.
Methods
applyFixitiesSource
:: [Fixity]The fixities to account for.
-> astThe element to tweak.
-> astThe same element, but with operator expressions updated.
Tweak any expressions in the element to account for the fixities given. Assumes that all operator expressions are fully left associative chains to begin with.
show/hide Instances
Produced by Haddock version 2.6.0