language-Modula2-0.1.3: Parser, pretty-printer, and more for the Modula-2 programming language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Modula2.ISO.ConstantFolder

Description

The main export of this module is the function foldConstants that folds the constants in an ISO Modula-2 AST using an attribute grammar. Other exports are helper functions and attribute types that can be reused for other languages or attribute grammars.

Synopsis

Documentation

foldConstants :: forall l. (Modula2 l, Nameable l, Ord (QualIdent l), Show (QualIdent l), Atts (Inherited (Auto ConstantFold)) (Block l l Sem Sem) ~ InhCF l, Atts (Inherited (Auto ConstantFold)) (Definition l l Sem Sem) ~ InhCF l, Atts (Inherited (Auto ConstantFold)) (Expression l l Sem Sem) ~ InhCF l, Atts (Synthesized (Auto ConstantFold)) (Block l l Sem Sem) ~ SynCFMod' l (Block l l), Atts (Synthesized (Auto ConstantFold)) (Block l l Placed Placed) ~ SynCFMod' l (Block l l), Atts (Synthesized (Auto ConstantFold)) (Definition l l Sem Sem) ~ SynCFMod' l (Definition l l), Atts (Synthesized (Auto ConstantFold)) (Definition l l Placed Placed) ~ SynCFMod' l (Definition l l), Atts (Synthesized (Auto ConstantFold)) (Expression l l Sem Sem) ~ SynCFExp l l, Atts (Synthesized (Auto ConstantFold)) (Expression l l Placed Placed) ~ SynCFExp l l, Functor (Auto ConstantFold) (Block l l), Functor (Auto ConstantFold) (Definition l l), Functor (Auto ConstantFold) (Expression l l)) => Environment l -> Module l l Placed Placed -> Module l l Placed Placed Source #

Fold the constants in the given collection of Modula-2 modules (a Map of modules keyed by module name). It uses the constant declarations from the modules as well as the given Environment of predefined constants and functions.

Note that the ISO Modula-2 Language satisfies all constraints in the function's type signature.

data ConstantFold #

Instances

Instances details
(Ord (QualIdent l), v ~ Value l l Placed Placed) => SynthesizedField "designatorValue" (Maybe (Placed v)) (Auto ConstantFold) (Designator l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Proxy "designatorValue" -> Auto ConstantFold -> Placed (Designator l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Designator l l sem sem) -> Designator l l sem (Synthesized (Auto ConstantFold)) -> Maybe (Placed v) #

(Nameable l, k ~ QualIdent l, v ~ Value l l Placed Placed, Ord k, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l)) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Block l l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Nameable l, k ~ QualIdent l, v ~ Value l l Placed Placed, Ord k, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l)) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Block l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Nameable l, k ~ QualIdent l, v ~ Value l l Placed Placed, Ord k, Atts (Synthesized (Auto ConstantFold)) (ConstExpression l l Sem Sem) ~ SynCFExp l l) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Declaration l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Declaration l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Declaration l l sem sem) -> Declaration l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Modula2 l, Nameable l, k ~ QualIdent l, Ord k, v ~ Value l l Placed Placed, Export l ~ Export l, Value l ~ Value l, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Synthesized (Auto ConstantFold)) (Type l l Sem Sem) ~ SynCF' (Type l l), Atts (Synthesized (Auto ConstantFold)) (ProcedureHeading l l Sem Sem) ~ SynCF' (ProcedureHeading l l), Atts (Synthesized (Auto ConstantFold)) (FormalParameters l l Sem Sem) ~ SynCF' (FormalParameters l l), Atts (Synthesized (Auto ConstantFold)) (Block l l Sem Sem) ~ SynCFMod' l (Block l l), Atts (Synthesized (Auto ConstantFold)) (ConstExpression l l Sem Sem) ~ SynCFExp l l) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Declaration full l l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Declaration full l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Declaration full l l sem sem) -> Declaration full l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

Transformation (Auto ConstantFold) 
Instance details

Defined in Language.Oberon.ConstantFolder

Associated Types

type Domain (Auto ConstantFold) :: Type -> Type #

type Codomain (Auto ConstantFold) :: Type -> Type #

Revelation (Auto ConstantFold) 
Instance details

Defined in Language.Oberon.ConstantFolder

Ord (QualIdent l) => Bequether (Auto ConstantFold) (Modules l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Ord (QualIdent l) => Synthesizer (Auto ConstantFold) (Modules l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

(Nameable l, Ord (QualIdent l), Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Inherited (Auto ConstantFold)) (StatementSequence l l Sem Sem) ~ InhCF l, Atts (Inherited (Auto ConstantFold)) (Declaration l l Sem Sem) ~ InhCF l) => Bequether (Auto ConstantFold) (Block l l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

bequest :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Block l l sem (Inherited (Auto ConstantFold)) #

(Nameable l, Ord (QualIdent l), Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Inherited (Auto ConstantFold)) (StatementSequence l l Sem Sem) ~ InhCF l, Atts (Inherited (Auto ConstantFold)) (Declaration l l Sem Sem) ~ InhCF l) => Bequether (Auto ConstantFold) (Block l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

bequest :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Block l l sem (Inherited (Auto ConstantFold)) #

(Nameable l, Ord (QualIdent l), Expression λ ~ Expression Language, QualIdent λ ~ QualIdent Language, InhCF l ~ InhCF λ, Pretty (Value l l Identity Identity), Atts (Synthesized (Auto ConstantFold)) (Expression l l Sem Sem) ~ SynCFExp l l, Atts (Synthesized (Auto ConstantFold)) (Element l l Sem Sem) ~ SynCF' (Element l l), Atts (Synthesized (Auto ConstantFold)) (Item l l Sem Sem) ~ SynCF' (Item l l), Atts (Synthesized (Auto ConstantFold)) (Designator l l Sem Sem) ~ SynCFDesignator l) => Synthesizer (Auto ConstantFold) (Expression λ l) Sem Placed Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Expression λ l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Expression λ l sem sem) -> Expression λ l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Expression λ l sem sem) #

(Oberon λ, Nameable l, Ord (QualIdent l), Value l ~ Value l, Pretty (Value l l Identity Identity), Atts (Synthesized (Auto ConstantFold)) (Expression l l Sem Sem) ~ SynCFExp l l, Atts (Synthesized (Auto ConstantFold)) (Element l l Sem Sem) ~ SynCF' (Element l l), Atts (Synthesized (Auto ConstantFold)) (Designator l l Sem Sem) ~ SynCFDesignator l) => Synthesizer (Auto ConstantFold) (Expression λ l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Expression λ l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Expression λ l sem sem) -> Expression λ l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Expression λ l sem sem) #

(Oberon l, Nameable l, Ord (QualIdent l), Show (QualIdent l), Atts (Synthesized (Auto ConstantFold)) (Block l l Sem Sem) ~ SynCFMod' l (Block l l)) => Synthesizer (Auto ConstantFold) (Module l l) Sem Placed 
Instance details

Defined in Language.Oberon.ConstantFolder

Methods

synthesis :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Module l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Module l l sem sem) -> Module l l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Module l l sem sem) #

type Codomain (Auto ConstantFold) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Domain (Auto ConstantFold) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Modules l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Modules l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Designator λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Designator λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Expression λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Expression λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (FieldList λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (FieldList λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Module λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Module λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (ProcedureHeading λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Statement λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Statement λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Type λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Type λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Variant λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Variant λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (AddressedIdent λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Block λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Block λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Expression λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Expression λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Item λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Item λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Statement λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Statement λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Type λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Type λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Variant λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Variant λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Block λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Block λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Case λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Case λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (CaseLabels λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (CaseLabels λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (ConditionalBranch λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Declaration λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Declaration λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Designator λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Designator λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Element λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Element λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Expression λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Expression λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (FPSection λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (FPSection λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (FieldList λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (FieldList λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (FormalParameters λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Module λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Module λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (ProcedureHeading λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Statement λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Statement λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (StatementSequence λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Type λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Type λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Value l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Value l l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (WithAlternative λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Designator λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Expression λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Expression λ l _1 _2) = SynCFExp λ l
type Atts (Synthesized ConstantFold) (FieldList λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (FieldList λ l _1 _2) = SynCF' (FieldList λ l)
type Atts (Synthesized ConstantFold) (Module λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Module λ l _1 _2) = SynCFMod' l (Module λ l)
type Atts (Synthesized ConstantFold) (ProcedureHeading λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Statement λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Statement λ l _1 _2) = SynCF' (Statement λ l)
type Atts (Synthesized ConstantFold) (Type λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Type λ l _1 _2) = SynCF' (Type λ l)
type Atts (Synthesized ConstantFold) (Variant λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Variant λ l _1 _2) = SynCF' (Variant λ l)
type Atts (Synthesized ConstantFold) (AddressedIdent λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Block λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Block λ l _1 _2) = SynCFMod' l (Block l l)
type Atts (Synthesized ConstantFold) (Expression λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Expression λ l _1 _2) = SynCFExp λ l
type Atts (Synthesized ConstantFold) (Item λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Item λ l _1 _2) = SynCF' (Item l l)
type Atts (Synthesized ConstantFold) (Statement λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Type λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Type λ l _1 _2) = SynCF' (Type l l)
type Atts (Synthesized ConstantFold) (Variant λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Variant λ l _1 _2) = SynCF' (Variant l l)
type Atts (Synthesized ConstantFold) (Block l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Block l l _1 _2) = SynCFMod' l (Block l l)
type Atts (Synthesized ConstantFold) (Case l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Case l l _1 _2) = SynCF' (Case l l)
type Atts (Synthesized ConstantFold) (CaseLabels l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (ConditionalBranch l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Declaration l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Designator l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Element l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Element l l _1 _2) = SynCF' (Element l l)
type Atts (Synthesized ConstantFold) (Expression λ l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Expression λ l _1 _2) = SynCFExp λ l
type Atts (Synthesized ConstantFold) (FPSection l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (FieldList l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (FormalParameters l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Module l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Module l l _1 _2) = SynCFMod' l (Module l l)
type Atts (Synthesized ConstantFold) (ProcedureHeading l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Statement l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (StatementSequence l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Type l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Type l l _1 _2) = SynCF' (Type l l)
type Atts (Synthesized ConstantFold) (Value l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Synthesized ConstantFold) (Value l l _1 _2) = SynCF' (Value l l)
type Atts (Synthesized ConstantFold) (WithAlternative l l _1 _2) 
Instance details

Defined in Language.Oberon.ConstantFolder

type Atts (Inherited ConstantFold) (Declaration full λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Inherited ConstantFold) (Declaration full λ l _1 _2) = InhCF l
type Atts (Inherited ConstantFold) (Declaration full λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Inherited ConstantFold) (Declaration full λ l _1 _2) = InhCF l
type Atts (Synthesized ConstantFold) (Declaration full λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ConstantFolder

type Atts (Synthesized ConstantFold) (Declaration full λ l _1 _2) = SynCFMod' l (Declaration full λ l)
type Atts (Synthesized ConstantFold) (Declaration full λ l _1 _2) Source # 
Instance details

Defined in Language.Modula2.ISO.ConstantFolder

type Atts (Synthesized ConstantFold) (Declaration full λ l _1 _2) = SynCFMod' l (Declaration full l l)

Orphan instances

(Nameable l, k ~ QualIdent l, v ~ Value l l Placed Placed, Ord k, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l)) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Block l l) Sem Placed Source # 
Instance details

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Modula2 l, Nameable l, k ~ QualIdent l, Ord k, v ~ Value l l Placed Placed, Export l ~ Export l, Value l ~ Value l, Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Synthesized (Auto ConstantFold)) (Type l l Sem Sem) ~ SynCF' (Type l l), Atts (Synthesized (Auto ConstantFold)) (ProcedureHeading l l Sem Sem) ~ SynCF' (ProcedureHeading l l), Atts (Synthesized (Auto ConstantFold)) (FormalParameters l l Sem Sem) ~ SynCF' (FormalParameters l l), Atts (Synthesized (Auto ConstantFold)) (Block l l Sem Sem) ~ SynCFMod' l (Block l l), Atts (Synthesized (Auto ConstantFold)) (ConstExpression l l Sem Sem) ~ SynCFExp l l) => SynthesizedField "moduleEnv" (Map k (Maybe v)) (Auto ConstantFold) (Declaration full l l) Sem Placed Source # 
Instance details

Methods

synthesizedField :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Proxy "moduleEnv" -> Auto ConstantFold -> Placed (Declaration full l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Declaration full l l sem sem) -> Declaration full l l sem (Synthesized (Auto ConstantFold)) -> Map k (Maybe v) #

(Nameable l, Ord (QualIdent l), Atts (Synthesized (Auto ConstantFold)) (Declaration l l Sem Sem) ~ SynCFMod' l (Declaration l l), Atts (Inherited (Auto ConstantFold)) (StatementSequence l l Sem Sem) ~ InhCF l, Atts (Inherited (Auto ConstantFold)) (Declaration l l Sem Sem) ~ InhCF l) => Bequether (Auto ConstantFold) (Block l l) Sem Placed Source # 
Instance details

Methods

bequest :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Block l l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Block l l sem sem) -> Block l l sem (Synthesized (Auto ConstantFold)) -> Block l l sem (Inherited (Auto ConstantFold)) #

(Nameable l, Ord (QualIdent l), Expression λ ~ Expression Language, QualIdent λ ~ QualIdent Language, InhCF l ~ InhCF λ, Pretty (Value l l Identity Identity), Atts (Synthesized (Auto ConstantFold)) (Expression l l Sem Sem) ~ SynCFExp l l, Atts (Synthesized (Auto ConstantFold)) (Element l l Sem Sem) ~ SynCF' (Element l l), Atts (Synthesized (Auto ConstantFold)) (Item l l Sem Sem) ~ SynCF' (Item l l), Atts (Synthesized (Auto ConstantFold)) (Designator l l Sem Sem) ~ SynCFDesignator l) => Synthesizer (Auto ConstantFold) (Expression λ l) Sem Placed Source # 
Instance details

Methods

synthesis :: forall (sem :: Type -> TYPE LiftedRep). sem ~ Semantics (Auto ConstantFold) => Auto ConstantFold -> Placed (Expression λ l Sem Sem) -> Atts (Inherited (Auto ConstantFold)) (Expression λ l sem sem) -> Expression λ l sem (Synthesized (Auto ConstantFold)) -> Atts (Synthesized (Auto ConstantFold)) (Expression λ l sem sem) #