| Copyright | (c) Niklas Broberg 2009 | 
|---|---|
| License | BSD-style (see the file LICENSE.txt) | 
| Maintainer | Niklas Broberg, d00nibro@chalmers.se | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Language.Haskell.Exts.Fixity
Description
Fixity information to give the parser so that infix operators can be parsed properly.
Synopsis
- data Fixity = Fixity (Assoc ()) Int (QName ())
- infix_ :: Int -> [String] -> [Fixity]
- infixl_ :: Int -> [String] -> [Fixity]
- infixr_ :: Int -> [String] -> [Fixity]
- preludeFixities :: [Fixity]
- baseFixities :: [Fixity]
- class AppFixity ast where- applyFixities :: Monad m => [Fixity] -> ast SrcSpanInfo -> m (ast SrcSpanInfo)
 
Fixity representation
Operator fixities are represented by their associativity (left, right or none) and their precedence (0-9).
Instances
| Eq Fixity Source # | |
| Data Fixity Source # | |
| Defined in Language.Haskell.Exts.Fixity 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
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.