Safe Haskell | None |
---|---|
Language | Haskell98 |
DDC.Source.Tetra.Transform.Defix
Description
Convert infix expressions to prefix form.
The parser packs up sequences of expressions and operators into an XDefix node, but does not convert them to standard prefix applications. That is the job of this module.
The parsed code will contain XDefix, XInfixOp and XInfixVar nodes, which are pretty-printed like this:
[DEFIX| Cons start [DEFIX| enumFromTo [DEFIX| start (INFIXOP "+") 1 ] end ]
After applying the transform in this module, all function applications will be in prefix form:
Cons start (enumFromTo ((+) start 1) end)
- data FixTable l = FixTable [FixDef l]
- data FixDef l
- = FixDefPrefix {
- fixDefSymbol :: String
- fixDefExp :: GXAnnot l -> GExp l
- | FixDefInfix {
- fixDefSymbol :: String
- fixDefExp :: GXAnnot l -> GExp l
- fixDefAssoc :: InfixAssoc
- fixDefPrec :: Int
- = FixDefPrefix {
- data InfixAssoc
- defaultFixTable :: GXBoundVar l ~ Bound => FixTable l
- data Error l
- = ErrorNoInfixDef {
- errorAnnot :: GXAnnot l
- errorSymbol :: String
- | ErrorDefixNonAssoc {
- errorOp1 :: String
- errorAnnot1 :: GXAnnot l
- errorOp2 :: String
- errorAnnot2 :: GXAnnot l
- | ErrorDefixMixedAssoc {
- errorAnnot :: GXAnnot l
- errorOps :: [String]
- | ErrorMalformed {
- errorAnnot :: GXAnnot l
- errorExp :: GExp l
- = ErrorNoInfixDef {
- class Defix c l where
Documentation
Infix operator definition.
Constructors
FixDefPrefix | |
Fields
| |
FixDefInfix | |
Fields
|
data InfixAssoc Source #
Infix associativity.
Constructors
InfixLeft | Left associative. |
InfixRight | Right associative. |
InfixNone | Non associative. |
Instances
defaultFixTable :: GXBoundVar l ~ Bound => FixTable l Source #
Default fixity table for infix operators.
Things that can go wrong when defixing code.
Constructors
ErrorNoInfixDef | Infix operator symbol has no infix definition. |
Fields
| |
ErrorDefixNonAssoc | Two non-associative operators with the same precedence. |
Fields
| |
ErrorDefixMixedAssoc | Two operators of different associativies with same precedence. |
Fields
| |
ErrorMalformed | Infix expression is malformed. Eg "+ 3" or "2 + + 2" |
Fields
|
Instances
ShowLanguage l => Show (Error l) Source # | |
PrettyLanguage l => Pretty (Error l) Source # | |