AspectAG-0.1.3: Attribute Grammars in the form of an EDSLSource codeContentsIndex
Data.AspectAG
Contents
Rules
Aspects
Semantic Functions
Common Patterns
Defining Aspects
Description

Library for First-Class Attribute Grammars.

The library is documented in the paper: Attribute Grammars Fly First-Class. How to do aspect oriented programming in Haskell

For more documentation see the AspectAG webpage: http://www.cs.uu.nl/wiki/bin/view/Center/AspectAG.

Synopsis
type Att att val = LVPair att val
data Fam c p = Fam c p
type Chi ch atts = LVPair ch atts
type Rule sc ip ic sp ic' sp' = Fam sc ip -> Fam ic sp -> Fam ic' sp'
inhdef :: Defs att nts vals ic ic' => att -> nts -> vals -> Fam ic sp -> Fam ic' sp
syndef :: HExtend (Att att val) sp sp' => att -> val -> Fam ic sp -> Fam ic sp'
ext :: Rule sc ip ic' sp' ic'' sp'' -> Rule sc ip ic sp ic' sp' -> Rule sc ip ic sp ic'' sp''
type Prd prd rule = LVPair prd rule
(.+.) :: Com r r' r'' => r -> r' -> r''
sem_Lit :: a -> Record HNil -> a
knit :: (Kn fc ic sc, Empties fc ec) => Rule sc ip ec (Record HNil) ic sp -> fc -> ip -> sp
copy :: (Copy att nts vp ic ic', HasField att ip vp) => att -> nts -> Rule sc ip ic sp ic' sp
use :: (Use att nts a sc, HExtend (Att att a) sp sp') => att -> nts -> (a -> a -> a) -> a -> Rule sc ip ic sp ic sp'
chain :: (Chain att nts val sc ic sp ic' sp', HasField att ip val) => att -> nts -> Rule sc ip ic sp ic' sp'
inhAspect :: (AttAspect (FnInh att nts) defs defasp, DefAspect (FnCpy att nts) cpys cpyasp, Com cpyasp defasp inhasp) => att -> nts -> cpys -> defs -> inhasp
synAspect :: (AttAspect (FnSyn att) defs defasp, DefAspect (FnUse att nts op unit) uses useasp, Com useasp defasp synasp) => att -> nts -> op -> unit -> uses -> defs -> synasp
chnAspect :: (DefAspect (FnChn att nts) chns chnasp, AttAspect (FnInh att nts) inhdefs inhasp, Com chnasp inhasp asp, AttAspect (FnSyn att) syndefs synasp, Com asp synasp asp') => att -> nts -> chns -> inhdefs -> syndefs -> asp'
attAspect :: AttAspect rdef defs rules => rdef -> defs -> rules
defAspect :: DefAspect deff prds rules => deff -> prds -> rules
class At l m v | l -> v where
at :: l -> m v
lhs :: Proxy Lhs
def :: Reader (Fam chi par) a -> Fam chi par -> a
module Data.HList
Rules
type Att att val = LVPair att valSource
Field of an attribution.
data Fam c p Source
A Family Fam contains a single attribution p for the parent and a collection of attributions c for the children.
Constructors
Fam c p
type Chi ch atts = LVPair ch attsSource
Field of the record of attributions for the children.
type Rule sc ip ic sp ic' sp' = Fam sc ip -> Fam ic sp -> Fam ic' sp'Source
The type Rule states that a rule takes as input the synthesized attributes of the children sc and the inherited attributes of the parent ip and returns a function from the output constructed thus far (inherited attributes of the children |ic| and synthesized attributes of the parent sp) to the extended output.
inhdef :: Defs att nts vals ic ic' => att -> nts -> vals -> Fam ic sp -> Fam ic' spSource
The function inhdef introduces a new inherited attribute for a collection of non-terminals. It takes the following parameters: att: the attribute which is being defined, nts: the non-terminals with which this attribute is being associated, and vals: a record labelled with child names and containing values, describing how to compute the attribute being defined at each of the applicable child positions. It builds a function which updates the output constructed thus far.||
syndef :: HExtend (Att att val) sp sp' => att -> val -> Fam ic sp -> Fam ic sp'Source
The function syndef adds the definition of a synthesized attribute. It takes a label att representing the name of the new attribute, a value val to be assigned to this attribute, and it builds a function which updates the output constructed thus far.
ext :: Rule sc ip ic' sp' ic'' sp'' -> Rule sc ip ic sp ic' sp' -> Rule sc ip ic sp ic'' sp''Source
Composition of two rules.
Aspects
type Prd prd rule = LVPair prd ruleSource
Field of an aspect. It associates a production prd with a rule rule.
(.+.) :: Com r r' r'' => r -> r' -> r''Source
Semantic Functions
sem_Lit :: a -> Record HNil -> aSource
Semantic function of a terminal
knit :: (Kn fc ic sc, Empties fc ec) => Rule sc ip ec (Record HNil) ic sp -> fc -> ip -> spSource
The function knit takes the combined rules for a node and the semantic functions of the children, and builds a function from the inherited attributes of the parent to its synthesized attributes.
Common Patterns
copy :: (Copy att nts vp ic ic', HasField att ip vp) => att -> nts -> Rule sc ip ic sp ic' spSource
A copy rule copies an inherited attribute from the parent to all its children. The function copy takes the name of an attribute att and an heterogeneous list of non-terminals nts for which the attribute has to be defined, and generates a copy rule for this.
use :: (Use att nts a sc, HExtend (Att att a) sp sp') => att -> nts -> (a -> a -> a) -> a -> Rule sc ip ic sp ic sp'Source
A use rule declares a synthesized attribute that collects information from some of the children. The function use takes the following arguments: the attribute to be defined, the list of non-terminals for which the attribute is defined, a monoidal operator which combines the attribute values, and a unit value to be used in those cases where none of the children has such an attribute.
chain :: (Chain att nts val sc ic sp ic' sp', HasField att ip val) => att -> nts -> Rule sc ip ic sp ic' sp'Source
In the chain rule a value is threaded in a depth-first way through the tree, being updated every now and then. For this we have chained attributes (both inherited and synthesized). If a definition for a synthesized attribute of the parent with this name is missing we look for the right-most child with a synthesized attribute of this name. If we are missing a definition for one of the children, we look for the right-most of its left siblings which can provide such a value, and if we cannot find it there, we look at the inherited attributes of the father.
Defining Aspects
inhAspect :: (AttAspect (FnInh att nts) defs defasp, DefAspect (FnCpy att nts) cpys cpyasp, Com cpyasp defasp inhasp) => att -> nts -> cpys -> defs -> inhaspSource
The function inhAspect defines an inherited attribute aspect. It takes as arguments: the name of the attribute att, the list nts of non-terminals where the attribute is defined, the list cpys of productions where the copy rule has to be applied, and a record defs containing the explicit definitions for some productions.
synAspect :: (AttAspect (FnSyn att) defs defasp, DefAspect (FnUse att nts op unit) uses useasp, Com useasp defasp synasp) => att -> nts -> op -> unit -> uses -> defs -> synaspSource
The function synAspect defines a synthesized attribute aspect.
chnAspect :: (DefAspect (FnChn att nts) chns chnasp, AttAspect (FnInh att nts) inhdefs inhasp, Com chnasp inhasp asp, AttAspect (FnSyn att) syndefs synasp, Com asp synasp asp') => att -> nts -> chns -> inhdefs -> syndefs -> asp'Source
A chained attribute definition introduces both an inherited and a synthesized attribute. In this case the pattern to be applied is the chain rule.
attAspect :: AttAspect rdef defs rules => rdef -> defs -> rulesSource
defAspect :: DefAspect deff prds rules => deff -> prds -> rulesSource
class At l m v | l -> v whereSource
Methods
at :: l -> m vSource
show/hide Instances
(HasField (Proxy ((,) lch nt)) chi v, MonadReader (Fam chi par) m) => At (Proxy ((,) lch nt)) m v
MonadReader (Fam chi par) m => At (Proxy Lhs) m par
lhs :: Proxy LhsSource
def :: Reader (Fam chi par) a -> Fam chi par -> aSource
module Data.HList
Produced by Haddock version 2.4.2