haskell-src-exts-1.17.0: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer

Copyright(c) Niklas Broberg 2009
LicenseBSD-style (see the file LICENSE.txt)
MaintainerNiklas Broberg, d00nibro@chalmers.se
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Language.Haskell.Exts.Annotated.Fixity

Contents

Description

Fixity information to give the parser so that infix operators can be parsed properly.

Synopsis

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 QName 

Instances

Eq Fixity Source 

Methods

(==) :: Fixity -> Fixity -> Bool

(/=) :: Fixity -> Fixity -> Bool

Data Fixity Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity

toConstr :: Fixity -> Constr

dataTypeOf :: Fixity -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Fixity)

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity)

gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r

gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity

Ord Fixity Source 
Show Fixity Source 

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.

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 where Source

All AST elements that may include expressions which in turn may need fixity tweaking will be instances of this class.

Methods

applyFixities Source

Arguments

:: Monad m 
=> [Fixity]

The fixities to account for.

-> ast SrcSpanInfo

The element to tweak.

-> m (ast SrcSpanInfo)

The same element, but with operator expressions updated, or a failure.

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.

Instances

AppFixity Alt Source 
AppFixity FieldUpdate Source 
AppFixity QualStmt Source 
AppFixity Stmt Source 
AppFixity PatField Source 
AppFixity RPat Source 
AppFixity PXAttr Source 
AppFixity Pat Source 
AppFixity Splice Source 
AppFixity Bracket Source 
AppFixity XAttr Source 
AppFixity Exp Source 
AppFixity GuardedRhs Source 
AppFixity Rhs Source 
AppFixity InstDecl Source 
AppFixity ClassDecl Source 
AppFixity Match Source 
AppFixity IPBind Source 
AppFixity Binds Source 
AppFixity Annotation Source 
AppFixity Decl Source 
AppFixity Module Source