07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

23
07/09/05 CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure

Transcript of 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

Page 1: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

1

CONFLUENCE

Compiler Structure

Page 2: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

2

Overview

.CF

.VHDL .C

.FNF

Page 3: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

3

Example

ccounterscounter is component ccounter +Width -output with constone next is constone <- {const Width 1 $} next <- (output '+' constone) output <- {reg Width next $} end

scounter <- {ccounter _ _}scounter.Width <- 10scounter.output <- {output "la

sortie" $}

struct simulator_s { struct { struct { unsigned long * sortie; // output sortie : 10 bits, 1 words unsigned long * clock; // input clock : 1 bits, 1 words } top; } signals; unsigned long memory[11];};typedef struct simulator_s *simulator_t;// Simulator Initializationvoid init_simulator(simulator_t);// Simulator Cycle Calculationvoid calc_simulator(simulator_t);

Page 4: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

4

Example

ccounterscounter is component ccounter +Width -output with constone next is constone <- {const Width 1 $} next <- (output '+' constone) output <- {reg Width next $} end

scounter <- {ccounter _ _}scounter.Width <- 10scounter.output <- {output "la

sortie" $}

Global variables declaration

Component declaration : ports are declared without types

Component description

Component instantion = evaluation of the component +

hardware generation

Page 5: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

5

Files organisation of confluence source code

• Confluence 0.10.5/src/– Cfeval : contains the core of the compiler

• Parser.mly is the parser description written in Ocamlyacc• Lexer.mll is the lexer description written in ocamllex (see ocaml

documentation)• Cf.ml is the main function (the one that you call when you want to compile

your confluence code)• CfAst.ml contains the structures for the building of the abstract syntax tree• CfParserUtil.ml contains tools to translate confluence program into AST• CfCompiler contains the recursive compilation functions• CfTypes contains the tool functions and the data types for the compiler• Cf_fnf contains the functions aimed at writing the .fnf file, with their specific

data structures– Fnflib : contains the program converting fnf into VHDL etc– Misc : contains several tools used in the compiler source code

• A few libraries from Ocaml are used (see the manual)– Hashtbl, List, Array …

Page 6: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

6

The Cf function

In the cf.ml file we get :

1. Function parse_cmd_args : checks the options, find the file name, deals with output file stuffs : Gives back (file name, compile_only, file output)

2. Function main () : takes the result of parse_cmd_args. Acts in 3 stages : 1. Parsing the text of the program to build the syntax tree

2. Compile : translate the tree into instruction to be executed by the computer itself

3. Execute the tasks and write the output file

cf [options] [file] [arguments]

let parse_cmd_args ...

Let main() = ...

ast = CfParserUtil.parse_program program CfLexer.token CfParser.file ...

task = CfCompiler.compileApplication ast ...

CfTypes.readyTask task; ...

CfTypes.executeTasks (); ...

$ cf test_counter.cf

Page 7: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

7

statements : { [] } | statements statement { $1 @ [$2] } ;

statement : name_space { CfAst.ApplyStmt $1 } | ifelse { $1 } | component_named { $1 } | application { CfAst.ApplyStmt $1 } | connect { CfAst.ConnectStmt $1 } ;

name_space : LOCAL locals IS statements END { CfParserUtil.app... } ;

Parser and Abstract Syntax Trees

• Abstract Syntax Tree is the data structure in which the text of your program is translated, so that it makes sense for the compiler.

• The structure of the AST comes from the parser itself, which recognizes the tokens (keywords) of the language. The data structure of trees is defined in CfAsts.

This is an example of what the parser looks like.

• We have tokens (keywords of the language) in upper case, and references to lower structures in lower case. • Tokens are linked with keywords in the lexer.• Between braces are the instructions for the building of the AST

Page 8: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

8

Parsing what the file contains

Parse_Program (parser, lexer, file) does :

1. Create a fifo of files to parse, and adds the program to it (this list will contain all the different library locations in addition to your main program)

2. Parser and lexer are generated from the description using ocamlyacc and ocamllex in the installation procedure. (at the beginning of the installation, you can see ocamlyacc …)

3. The recursive Parse_all_files function takes a Parse_channel function as argument

– It keeps in mind informations about position, parent file, etc…– Takes the file in a list To_Parse, check if the file is linked in the Hashtbl ASTs, and

if not, parse the file using Parse_channel on it, and binds the result with files in ASTs

– It links the file with its parent list in the hashtabl subs– It stores the parsed files in Files list

4. Builds and gives back the main AST

ast = CfParserUtil.parse_program program CfLexer.token CfParser.file

Page 9: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

9

Building the main AST

• Call the recursive function Insert_sub_asts : it is a cross-recursive function in 2 parts :

– Insert_sub_asts itself : takes a ast_apply (of type expr, subtype apply) and a file as arguments. Calls the function add_sub_env on (ast_apply, buildsubast file,”_file_”^ file)

• Addsubenv (apply_parent, apply_sub, sub_name) takes the component part of the apply, and add a new Connect statement with name sub_name in the statements of the component, which connects to the apply_sub expression

– Build_sub_asts : builds the ASTs for subfiles and libraries

• This function actually builds the AST : it inserts in ast_apply the ast corresponding to the hd of files list and recursively…

• The tools for the building of the AST are provided in CfAst and CfParserUtil

type expr = Apply of Loc.loc * string * expr * expr list | Connect of Loc.loc * expr * expr

| Name of Loc.loc * string | Comp of Loc.loc * string * string list * stmt list | DotName of Loc.loc * expr * string ... | Vector of Loc.loc * string | Record of Loc.loc * (string * expr) list

Page 10: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

10

Examples of ASTs

• Component f +a –b is …ConnectStmt

Connect

Name (f) Comp (f, [a;b], stmts)

• b <- {output 6 $} Connect

DotPositionName (b)

Apply (“”, Name output, [Integer 6, Free])

2

Page 11: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

11

Examples of ASTs

• c = a + b Connect

Name (c)

Apply (“”, Name (+), [a;b;Free])

DotPosition

3

This refers to the component (+) named

before. This component has been

defined in Base.cf

Infix operators in confluence :

They are defined as confluence components in Base.cf, from the primitives. In the parser you get a list of all the infix operators. When encountered in the parsing process, they are translated into exactly the same AST as if they had been invoked in the standard way. This translation is completed by the application_of_infix in CfParserUtil. (have a look in base.cf)

Page 12: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

12

Operators definition : the Base.cf library

• Base.cf is set as default environnement in the installation. It is the default library of commands. When calling a basic operator in a confluence program, it refers to one of the Base.cf component.

• It is possible to use other libraries : begin a confluence program using the keyword ENVIRONNEMENT “name.cf” which will add name.cf the the fifo of files to parse. It is a way to quote programs in confluence

• Base.cf contains all the functions corresponding to infix or prefix operators, defined using the primitives.

• The primitives themselves are defined in CfPrims, and they are implemented in OCaML.

Primitives

Base.cf

component, variable names

User level

Source code level

Page 13: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

13

Infix Operators Management

• In confluence : static predefined list of infix operators. (line 317, CfParser)

• The infix operators syntax is expr INFIXOP expr

• From an expression like a + b the Parser will use CfParserUtil.application_of_infix to generate artificially the same thing as {(+) a b $}

– So we have all the tools to define our own infix operators• It is not possible to write anything like expr INDENTIFIER expr , because it will create ambiguities in

the parsing (look at the expression definition)

In OCaML the way to define infix operators is to write : let (#$) a b = a + b;; then #$ can be used as an infix operator in expressions like a #$ b.

The name of an infix operator cannot be a standard name with lowercase characters, in that it could generate ambiguities and conflicts -> one has to use symbol identifiers.

Page 14: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

14

OCaML Parser for infix operators

val_ident: LIDENT

{ $1 } | LPAREN operator RPAREN

{ $2 };operator: PREFIXOP { $1 } | INFIXOP0 { $1 } | INFIXOP1 { $1 } | INFIXOP2 { $1 } | INFIXOP3 { $1 } | INFIXOP4 { $1 } | PLUS { "+" } | MINUS { "-" } | MINUSDOT { "-." } | STAR { "*" } | EQUAL { "=" } | LESS { "<" } | GREATER { ">" } | OR { "or" } | BARBAR { "||" } | AMPERSAND { "&" } | AMPERAMPER { "&&" } | COLONEQUAL { ":=" };

• At that point we see that here there are two totally different ways to describe functions, which are disjoined, because no operator occurrence could refer to a standard identifier.

• In principal one could do the same in confluence, because in confluence the identifier definition includes all the lowercase character strings, but excludes all the symbol strings, except those corresponding to base.cf components

Page 15: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

15

Compilation

1. Defines the Root environnement

2. Defines the run () function : expr (renv, CfTypesNewFree) which just initialize the recursion, and gives back the recording (renv, run ())

3. Defines expr as compExpr (EnvRoot,AstApply)compExpr is the recursive function that traverse the AST. Each node and each leaf is converted into tasks to be executed. Tasks to be executed consists

in 3 sequences :

• call for the tasks of the son trees (recursive traversal)• create a new task from the current node, from the tasks of the son node• express this task in terms of taskedExpr, which means : ready this task to be added to the list

When you eventually will evaluate this point of the compiled tree the function will only put the prepared tak into the list, so that it is going to be executed in the next loop of execution.

So in that way, you only get one task in the task list, in that the following tasks to be executed are generated by the previous ones. It is also a way to manage the order of execution of instructions.

task = CfCompiler.compileApplication ast

let compileApplication astApply = try let expr = compExpr EnvRoot astApply in ...

Page 16: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

16

let rec compExpr cenv ast = let expr = match ast with | CfAst.Apply (loc, ann, comp, args) -> compApply cenv loc ann comp args | CfAst.Connect (loc, expr0, expr1) -> compConnect cenv loc expr0 expr1 | CfAst.Cond (loc, p, t, f) -> compCond cenv loc p t f | CfAst.Name (loc, name) -> compName cenv loc name | CfAst.DotPosition (loc, sys, position) -> compDotPosition cenv loc sys position | CfAst.Comp (loc, ann, ports, stmts) -> compComponent cenv loc ann ports stmts … | CfAst.Integer (loc, i) -> compInteger cenv loc i | CfAst.Vector (loc, s) -> compVector cenv loc s | CfAst.Record (loc, fields) -> compRecord cenv loc fields in let taskedExpr renv variable = CfTypes.readyTask (renv, fun () -> expr renv variable) in taskedExpr

and compStmts = … and compComp = … and compName = ……

The compilation function1st step

2nd step

3rd step

Page 17: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

17

• The CfType module contains the auxiliary functions for the compiler, like functions manipulating types, creating structure from raw datas… The main part of these functions are error management and various checking functions or specific type management functions.

• It contains also the types of the datas the tasks will deal with : those types are quite similar to what we had in the AST, but they have a different nature : they are really part of result itself, so they are aimed at describing the results of the compilation of the AST.

• They also are trees :

• In CfTypes you also have the environment management : the type env is defined, and the structure of environment is described.

The CfType module

value = Free of slot list ref * variable list ref | Integer of Intbig.intbig | Float of float | Boolean of bool | Vector of Cf_fnf.producer | Vector0 | Record of int * string array * variable array | System of renv | Comp of renv * Loc.loc * int * string * string array * (renv -> unit) | Property of property

Page 18: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

18

Environment management

• The environments are organised in layers with parent and son. The root environment is its own parent (recursive reference).

• The renvPort variable is usually a Record consisting in two arrays : 1 of variable names, 1 of values.

• The environment is the place where systems are translated in netlists. The environment is also the place where informations about the fnf netlist are stored.

type renv = { renvId : Cf_fnf.system;

renvParent : renv; (* parent env *)

renvCompLoc : Loc.loc; (* loc of the component description*)

renvAppLocs : Loc.loc list; (* loc the component evaluations*)

renvPorts : variable;} (* ports with names and values *)

Page 19: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

19

The unification function

• A unification of 2 terms is an operation where the function tries to substitute a variable by an expression. This process is used in the compilation to effectively replace an instruction by its value

• The unification function is the major point of the CfType module. (see The functional approach to programming by Guy Cousineau and Michel Mauny)

let rec unify var0 var1 upSet = ... match (val0, val1) with (Free (slots0, frees0), Free (slots1, frees1)) -> let slotsNew = List.rev_append !slots0 !slots1 in

...

| (Free (slots, frees), value) | (value, Free (slots, frees)) -> List.iter (fun var -> var := value; freeVariableDetermined ()) !frees; List.iter (fun slot -> sync slot) !slots

| (Record (arity0, names0, variables0), Record (arity1, names1, variables1)) -> ...

Page 20: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

20

Execution of the tasks

• Computes Readytasks task, which adds the tasks (renv, run()) defined to the tasklist

• Runs recursively all the tasks of the list

• Checks errors

Instruction n+1Instruction nInstruction n-1

Task

Evaluation of functions, modification of the instruction list …

Instructio

n n+1

Instruction n+1

Task

Evaluation of functions, modification of the instruction list …

Instruction n

Page 21: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

21

Output file

• Computes Cf_fnf.output_fnf channel : this program translate the components, slots, cells defined into a text file of .fnf format

(scope "top" "top" ( (dangle 0) (const 1 "0") (const 2 "1") (buf 3 10 6) (const 4 "0000000001") (add 5 10 3 4) (ff 6 10 11 7) (mux 7 10 1 8 9) (mux 8 10 2 6 5) (const 9 "0000000000") (output 10 "la sortie" 10 3) (input 11 "clock" 1)))

Page 22: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

22

Type system of confluence

• There is no type system in confluence, except the one coming from Ocaml itself : this means that there is no typing algorithm in confluence.

• The data structures in the confluence compiler are Ocaml types. They do not correspond to confluence data types, even if they are very similar.

• A way to define a typing algorithm in confluence is to start from the AST and take the tree traversal function defined for the compilation. Equiped with that, we have to implement :

1. Confluence types : type cf_type = etc…

2. The type constraints for primitives

3. The algorithm generating type constraints

4. The algorithm solving the type constraints

Page 23: 07/09/05CERN PH-ED Summer Student Work 1 CONFLUENCE Compiler Structure.

07/09/05 CERN PH-EDSummer Student Work

23

Conclusion

• The type system remains to be done. (I’m working on it)• From it we could work on overloading for operators and components

• References :– www.confluent.org (confluence home page, with manual and links)

– http://caml.inria.fr/pub/docs/manual-ocaml/index.html (ocaml manual, contains lexer and parser description, libraries documentation ... )

– The Functional Approach to Programming by Guy Cousineau, Michel Mauny

– Modern Compiler Implementation in ML by Andrew Appel