ddc-source-tetra-0.4.3.1: Disciplined Disciple Compiler source language.

Safe HaskellNone
LanguageHaskell98

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)

Synopsis

Documentation

data FixTable l Source #

Table of infix operator definitions.

Constructors

FixTable [FixDef l] 

data FixDef l Source #

Infix operator definition.

data InfixAssoc Source #

Infix associativity.

Constructors

InfixLeft

Left associative.

InfixRight

Right associative.

InfixNone

Non associative.

defaultFixTable :: GXBoundVar l ~ Bound => FixTable l Source #

Default fixity table for infix operators.

data Error l Source #

Things that can go wrong when defixing code.

Constructors

ErrorNoInfixDef

Infix operator symbol has no infix definition.

ErrorDefixNonAssoc

Two non-associative operators with the same precedence.

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 # 

Methods

showsPrec :: Int -> Error l -> ShowS #

show :: Error l -> String #

showList :: [Error l] -> ShowS #

PrettyLanguage l => Pretty (Error l) Source # 

Associated Types

data PrettyMode (Error l) :: * #

Methods

pprDefaultMode :: PrettyMode (Error l) #

ppr :: Error l -> Doc #

pprPrec :: Int -> Error l -> Doc #

pprModePrec :: PrettyMode (Error l) -> Int -> Error l -> Doc #

class Defix c l where Source #

Minimal complete definition

defix

Methods

defix :: FixTable l -> c l -> Either (Error l) (c l) Source #

Resolve infix expressions in a thing.

Instances

Defix GAltMatch l Source # 

Methods

defix :: FixTable l -> GAltMatch l -> Either (Error l) (GAltMatch l) Source #

Defix GAltCase l Source # 

Methods

defix :: FixTable l -> GAltCase l -> Either (Error l) (GAltCase l) Source #

Defix GGuard l Source # 

Methods

defix :: FixTable l -> GGuard l -> Either (Error l) (GGuard l) Source #

Defix GGuardedExp l Source # 
Defix GClause l Source # 

Methods

defix :: FixTable l -> GClause l -> Either (Error l) (GClause l) Source #

Defix GLets l Source # 

Methods

defix :: FixTable l -> GLets l -> Either (Error l) (GLets l) Source #

Defix GExp l Source # 

Methods

defix :: FixTable l -> GExp l -> Either (Error l) (GExp l) Source #

Defix Top l Source # 

Methods

defix :: FixTable l -> Top l -> Either (Error l) (Top l) Source #

Defix Module l Source # 

Methods

defix :: FixTable l -> Module l -> Either (Error l) (Module l) Source #