bug-bison
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

la grammar problem with Bison


From: josephus
Subject: la grammar problem with Bison
Date: Thu, 02 Jun 2005 08:08:07 -0500
User-agent: Mozilla/5.0 (Windows; U; Win98; en-US; rv:1.7.8) Gecko/20050511

I am trying to build an Algol compiler. the make file is my 'in process.' the grammar is SLR I developed with an SLR tool I have. the reason is to generate a small state set

i usually run manually

flex -l Algol.l
bison -v -d Algol.y
then compile and link.
the result should parse bigtest.alg

What has been happening is the program cannot connect tokens to grammar states. All tokens are errors. No debug access to my difficulty In fact the shift/reduce actions seem to be insane. It parsed a little but when I modified the grammar to reduce the overhead, it quit working at all. I cant get it to even see a BEGIN symbol

my purpose was to debug the grammar.  It needs work.
I would accept the idea that my grammar is wrong, but there is no indication that I do not have a parser. and I cannot guess how to make it work.

A related problem is  \R  Bison thinks it is an error.  It should not be.
          josephus
/* the lexical scanner for NUALGOL  */
%{

#include <stdio.h>
#include "algol.h"

static char copyright[] =
" @(#) Copyright (c) 1985 Joe Widows, Arlington Texas.\n";
static char CR_continuation[] = "@(#) All rights reserved.\n";
static char manufacture[] = " January, 28, 1995 \n";




int global_type = ID;     /* start out with this state */
int global_store = 0;     /* normally not anything */

%}
QUOTE           [\"]
WS              [ \t\f\n\r]+
OPTWS           [ \t\f\n\r]*
BLANK           [ \t]{1}
DOT             [\.]
OCTAL           [0-7]*
HEX             [0-9A-F]
%%
"and"           { return(AND); }
"array"         { global_store = ARRAY; return(ARRAY); }
"begin"         { return(BEGIN_SYM); }
"boolean"       { global_type = BOOLEAN; return(BOOLEAN); }
"case"          { return(CASE); }
"do"            { return(DO); }
"else"          { return(ELSE); }
"end"           { return(END_SYM); }
"endcase"       { return(ENDCASE); }
"endstr"        { return(ENDSTRUCTURE); }
"endstruct"     { return(ENDSTRUCTURE); }
"endstructure"  { return(ENDSTRUCTURE); }
"external"      { return(EXTERNAL); }
"false"         { return(FALSE); }
"for"           { return(FOR); }
"function"      { global_type = FUNCTION; return(FUNCTION);}
"go"            { return(GO); }
"goto"          { return(GOTO); }
"if"            { return(IF); }
"integer"       { global_type = INTEGER; return(INTEGER);}
"long"          { global_type = LONG; return(LONG);}
"literal"       { global_type = LITERAL; return(LITERAL);}
"not"           { return(NOT); }
"or"            { return(OR); }
"own"           { global_store = OWN; return(OWN);}
"proc"          { return(PROCEDURE); }
"procedure"     { return(PROCEDURE); }
"pointer"       { global_type = POINTER; return(POINTER);}
"real"          { global_type = REAL; return(REAL);}
"return"        { return(RETURN); }
"step"          { return(STEP); }
"string"        { global_type = STRING; return(STRING);}
"struct"        { return(STRUCTURE); }
"structure"     { return(STRUCTURE); }
"to"            { return(TO); }
"then"          { return(THEN); }
"true"          { return(TRUE); }
"type"          { return(TYPE); }
"union"         { global_type = UNION; return(UNION);}
"until"         { return(UNTIL); }
"while"         { return(WHILE); }
[0-9]*          { return(NUMERIC_CONSTANT); }
[A-Za-z_$0-9]*       { return(symbol(yytext)); }
":="            { return(ARROW); }
"+"             { return(ADD_OP); }
"||"            { return(CONCAT); }
":"             { return(COLON); }
","             { return(COMMA); }
"*"             { return(MUL_OP); }
">"             { return(REL_OP); }
";"             { global_type = ID; global_store = 0; return(SEMICOLON);}
"**"            { return(STARSTAR); }
"="             { return(LOG_OP); }
"//"            { return(MOD); }
"(*"            { return(LEFT_MARK); }
"*)"            { return(RIGHT_MARK); }
"("             { return(LEFT_PAREN); }
")"             { return(RIGHT_PAREN); }
"@"             { return(ATSIGN); }
{QUOTE}{QUOTE}  { return(QUOTEQUOTE); }
{QUOTE}.{QUOTE} { return(STRING_CONSTANT); }
%%

static struct sym_table{ 
        char *var_name; /* symbol name */   
        long address;           /* definition address */ 
        int type;               /* int,real,string, etc */ 
        int value;              /* any known value or 0 */ 
        int indexes;            /* any array indexes or 0*/
        } sym_table;

int last_sym = 0;
char filename[256];  /* this is the size of a path  4096*/;

void *
yyerror( const char *msg)
{
        printf(msg);
};

int
yywrap()
{
 yyin = fopen(filename,"r+");
return 1;
};


char *yytext;

#include <stdio.h>
#include <stdlib.h>

struct Tree_block
{
char * identifier;
long type;
long operand;
long index1;
long index2;
long value;
struct Tree_block *left_child, *right_child;
};



void * push( struct Tree_block *address, struct Tree_block *next );



int i;
double number; 
char optr;
struct Tree_block *tp, *next, *head, *current, *end; 


init(char *name)
{

/* we add a name and create the list */
end=(struct Tree_block  *)calloc(1,sizeof(struct Tree_block));
current=(struct Tree_block  *)calloc(1,sizeof(struct Tree_block));
((struct Tree_block  *)current)->identifier=(char *)calloc(1,sizeof(name));
(struct Tree_block *)current->identifier = name;
head = current;  /* remember the top of list */
end = (struct Tree_block *)(char *)(-1);
(struct Tree_block *)current->right_child=end;
next = current;
++last_sym ;
}; /* end of init */
int test;

symbol(char *name)
{
if (last_sym == 0) { init(name); return(ID); }
else {
      current = head;

while (current != end)
{
if (strcmp(name,((struct Tree_block *)current)->identifier) == 0) 
{ /* we have a match return ID */
  return(ID);
};
(struct Tree_block *)current->identifier=name; 
{
next=(struct Tree_block *)calloc(1,sizeof(struct Tree_block));
next->identifier=(char *)calloc(1,sizeof(name));
(struct Tree_block*)next->identifier=name;
++last_sym;
next->right_child=end;
push(current, next);
return(ID);
};
if(current == end) 
{
next=(struct Tree_block *)calloc(1,sizeof(struct Tree_block));
next->identifier=(char *)calloc(1,sizeof(name));
(struct Tree_block*)next->identifier=name;
++last_sym;
next->right_child=end;
return(ID);
}
 current = current->right_child;
}; /* end of top block */
}; /* end of while */
}; /* end of main  */
 
void *
push(struct Tree_block *address, struct Tree_block *next) 
{
struct Tree_block *new_node;
new_node=(struct Tree_block *)calloc(1,sizeof(struct Tree_block));
new_node->right_child=address->right_child;

next->left_child=address;
address->right_child=next;
next->right_child=new_node->right_child;
address->left_child=next;
  free(new_node);  /* free the temp */
}

int count = 0;

int        main( int argc, char **argv )
{
        char gp;

        if ( argc < 2 )
        {
        fprintf(stdout, " ltest  filename \n");
        exit(0);  /* MWC exit is zero == OK */
        }
           strcpy( filename, argv[1]);
        gp =   yywrap();
       printf(" filename = %s \n");

        while (gp =  yyparse() ){
          count++;
            if(gp == '1')exit(0);
         printf("%d  %d \"%s\"\n",count, gp, yytext);
           }
        printf(" done\n");
}

/* joe widows  */
%{
 /* the working syntactical definition of JALGOL .ALG  booted in MWC */
int var_type;  /* carries the ID type between productions */
%}
%term LEFT_PAREN BEGIN_SYM PROCEDURE INDEX LENGTH ENDSTRUCTURE
%term AND ARRAY BOOLEAN CASE DO ELSE END_SYM ENDCASE
%term EXTERNAL FALSE FOR FUNCTION GO GOTO IF INTEGER
%term LITERAL NOT OR OWN POINTER REAL RETURN STEP STRING
%term STRUCTURE SUBSTRING 
%term TO THEN TRUE TYPE UNION UNTIL WHILE 

%term ARROW COLON COMMA CONCAT 
%term SEMICOLON LEFT_MARK RIGHT_MARK
%term RIGHT_PAREN ATSIGN QUOTEQUOTE
%term STARSTAR ADD_OP MUL_OP REL_OP LOG_OP

%term ID NAMED_VAR NAMED_BOOL NAMED_PTR  NAMED_LABEL NAMED_STRING
%term FUNCTION_ID BOOLEAN_ID PROC_ID STRING_ID
%term NAMED_STRUCT USER_TYPE STRING_CONSTANT NUMERIC_CONSTANT
%term COMMENT
%left NOT AND OR LOG_OP REL_OP ADD_OP MUL_OP
%right STARSTAR CONCAT
%%
algol : PROG

PROG: block semi_list
     { printf(" almost done : block \n") ;  }
        | block semi_list proc_list semi_list
     { printf(" almost done block ; proc_list \n"); }
        | proc_list semi_list
     { printf(" just procedure list \n"); }
        ;
block : block_head end_part
        { printf(" close up : BLOCK\n"); }
        ;
block_head :
        BEGIN_SYM
                { printf(" BEGIN token found: prolog()\n"); }
        ;
proc_list :
        proc_list semi_list proc_block
        { printf(" we are outside of the main or inital block \n"); }
        | proc_block
        { printf(" we have one outside block \n"); }
        ;
semi_list :
         SEMICOLON
          { printf("  SEMICOLON  \n"); }
        | semi_list SEMICOLON
          { printf(" semi_list \n"); }
        ;
end_part :
        declare_parts semi_list stmts semi_list block_end
        | block_end
        { printf(" end of a block :  no epilog() here\n"); }
        | stmts semi_list block_end
        { printf(" end of a block : epilog()/return \n"); }
                ;
block_end :
          END_SYM
           { printf(" close block scope / adjust frame / epilog()\n"); }
        ;
declare_parts :
         declare_parts semi_list declare_member
        { printf(" some internal declarations \n"); }
        | declare_member
        { printf(" just one member declared \n"); }
        ;
declare_member :
        proc_block
           { printf(" precedence phasing for declarations : proc \n"); }
        | declare_stmt
           { printf(" precedence phasing for declarations : decl \n"); }
        ;
proc_block :
          proc_head proc_part
        { printf(" proc_block \n"); }
        ;
proc_head :
          PROCEDURE ID
        { printf(" proc_head : make ID procedure \n"); }
        | data_type PROCEDURE ID
        { printf(" proc_head : make ID datatype procedure \n"); }
        ;
proc_part : proc_arg_part semi_list block
        { printf(" end of a proc_block : epilog()/return \n"); }
        ;
proc_arg_part :
         LEFT_PAREN declare_list RIGHT_PAREN 
              { printf(" proc block :: proc_head ( arg_list ) \n"); }
          ;
declare_list :
        declare_list semi_list declare_stmt
        { printf(" declare_list : list ; stmt \n"); }
        | declare_stmt
        { printf(" declare_list : stmt \n"); }
        ;
declare_stmt :
        type_declare
        { printf(" dcl stmt : type \n"); }
        | user_declare
        { printf(" dcl stmt : user \n"); }
        ;
type_declare :
        storage_type data_type id_list
        { printf(" type_declare : storage datatype id_list\n"); }
        data_type id_list
        { printf(" type_declare : datatype id_list\n"); }
        ;
data_type :
           BOOLEAN
                { printf(" data_type : BOOLEAN\n"); var_type = BOOLEAN; }
         | INTEGER
               { printf(" data_type : INTEGER\n");  var_type = INTEGER; }
         | POINTER
                { printf(" data_type : POINTER\n"); var_type = POINTER; }
         | REAL
               { printf(" data_type : REAL\n"); var_type = REAL; }
         | STRING
               { printf(" data_type : STRING\n"); var_type = STRING; }
         | structure_type
               { printf(" data_type : STRUCTURE\n"); var_type = STRUCTURE; }
         | USER_TYPE
               { printf(" data_type : USER_TYPE\n"); var_type = USER_TYPE; }
         ;
storage_type :  
          OWN
        { printf(" OWN means initialize to 0, NULL, EMPTY, etc\n"); }
         | EXTERNAL
        { printf(" EXTERN means somebody else owns this address\n"); }
         ;
id_list :
        id_list COMMA ID
           { printf(" id_list, add ID to symbol table var_type\n"); }
          |  ID
               { printf(" add ID to symbol table using var_type\n"); }
        ;
structure_type :
          structure_define ENDSTRUCTURE
          { printf(" turn off the STRUCTURE qualifier condition \n"); }
          ;
structure_define :
         STRUCTURE ID LEFT_MARK
      { printf(" turn on the STRUCTURE qualifier condition : ID\n"); }
                declare_list
        { printf(" STRUCTURE declare_list \n"); }
        ; 
stmts :
        stmts semi_list label_stmt
        { printf(" stmts: list ; label_stmt\n"); }
      |  COMMENT label_stmt
        { printf(" stmts: COMMENT label_stmt\n"); }
      | label_stmt
        { printf(" stmts: label_stmt\n"); }
        ;
user_declare :
          TYPE data_type ID
 { printf(" using the globally defined data_type set ID as user_type \n"); } 
        ;
label_stmt :
     label_list stmt
        { printf(" lable_stmt : lable_list stmt\n"); }
     | stmt
        { printf(" label_stmt : stmt\n"); }
     ;
label_list :
     label_list label_mark
        { printf(" label_list : list label_mark\n"); }
     | label_mark
        { printf(" label_list : label_mark\n"); }
     ;
label_mark :
     ID COLON
 { printf(" create a new label here s_lookup(yytext,NAMED_LABEL,INSERT); \n"); }
     ;
stmt :
        any_stmt
        { printf(" stmt : any_stmt\n"); }
        | if_stmt
        { printf(" stmt : if_stmt\n"); }
        | for_stmt
        { printf(" stmt : for_stmt\n"); }
        ;

any_stmt :
        goto_stmt
        { printf(" any_stmt : goto_stmt\n"); }
        | while_stmt
        { printf(" any_stmt : while_stmt\n"); }
        | until_stmt
        { printf(" any_stmt : until_stmt\n"); }
        | assign_stmt
        { printf(" any_stmt : assign_stmt\n"); }
        | string_stmt
        { printf(" any_stmt : string_stmt\n"); }
        | proc_call
        { printf(" any_stmt : proc_call\n"); }
        | case_stmt
        { printf(" any_stmt : case_stmt\n"); }
        | block
        { printf(" any_stmt : block\n"); }
        | return_stmt
        { printf(" any_stmt : return_stmt\n"); }
        ;
if_stmt :
      IF bool_part then_part else_part
        { printf(" end if IF then else statement generate label \n"); }
     | IF bool_part boolean_expr then_part
        { printf(" end of IF then statement generate label\n"); } 
     ;
bool_part :
        LEFT_PAREN boolean_expr
        { printf(" add tmp_x = not tmp_x, jmp to label+2 \n"); }
        ;
then_part :
        RIGHT_PAREN THEN stmt
     { printf(" ) THEN stmt :: jmp to end of else\n"); }
        | RIGHT_PAREN THEN 
     { printf(" ) THEN :: null block jmp to end of else\n"); }
        ;
else_part :
        ELSE stmt
     { printf(" ELSE stmt :: gen_labels \n"); }
       |  ELSE 
     { printf(" ELSE :: gen_labels \n"); }
        ;
for_stmt:
        FOR step_part step_part_2 DO stmt
    { printf(" generate for_branch_back :: jmp last_label: end_label \n"); }
        ;
step_part : NAMED_VAR  ARROW  expression STEP
        { printf(" step_part : NAMED_VAR = expression STEP\n"); }
        ;
step_part_2 :
         expression UNTIL expression
{ printf(" STEP eval(1) = eval(1) - eval(2) : gen_label, incr_code \n"); }
        ;
goto_stmt :
        GOTO NAMED_LABEL
          { printf(" GOTO ID  : jmp to address(ID) \n"); }
        | GO TO NAMED_LABEL
          { printf(" GOTO ID  : jmp to address(ID) \n"); }
        ;
while_stmt :
        WHILE bool_part RIGHT_PAREN DO stmt
  {  printf(" WHILE generate branch back to previous label,gen label+1\n"); }
        ;

until_stmt :
        UNTIL bool_part RIGHT_PAREN DO stmt
        { printf(" until_stmt:  generate label+3 \n"); }
        ;
assign_stmt :
        NAMED_VAR ARROW expression
         { printf(" assign_stmt : named_var := expression\n"); }
        | NAMED_BOOL ARROW boolean_expr
         { printf(" assign_stmt : named_bool := boolean_expr\n"); }
        | NAMED_BOOL ARROW expression
         { printf(" assign_stmt :  named_ptr :=  expression\n"); }
        ;
string_stmt :
        NAMED_STRING ARROW string_val
       { printf(" string_stmt : named_string := string_val\n"); }
        | substring_proc ARROW string_val
       { printf(" string_stmt: substring_proc := string_val\n"); }
        ;
string_val :
        expression CONCAT NAMED_STRING
          { printf(" string_val : expression || named_string\n"); }
        | string_val CONCAT expression
          { printf(" string_val : string_val || expression\n"); }
        | string_val CONCAT NAMED_STRING
          { printf(" string_val : string_val || named_string\n"); }
        | string_val CONCAT string_function
          { printf(" string_val : string_vall || string_function\n"); }
        | QUOTEQUOTE
          { printf(" string_val : '\0' (quotequote)\n"); }
        | STRING_CONSTANT
          { printf(" string_val : string_constant (quoted string)\n"); }
        | NAMED_STRING
          { printf(" string_val : NAMED_STRING\n"); }
        | string_function
          { printf(" string_val : string_function\n"); }
        | substring_proc
          { printf(" string_val : substring_proc\n"); }
        ;
substring_proc:
        SUBSTRING LEFT_PAREN NAMED_STRING COMMA expression
                   COMMA expression RIGHT_PAREN
  { printf(" substring_proc : substr( Id, expression, expression )\n"); }
        ;
string_function :
        INDEX LEFT_PAREN string_val COMMA string_val RIGHT_PAREN
     { printf(" string_function : returns integer (INDEX)\n"); }
        | LENGTH LEFT_PAREN string_val RIGHT_PAREN
     { printf(" string_function : returns integer (LENGTH)\n"); }
        ;

proc_call :
        PROC_ID LEFT_PAREN arg_list RIGHT_PAREN
        { printf(" proc_call : proc_id stack/arg eval/ jmp to\n"); }
        ;
arg_list :
        arg_list COMMA expression
        { printf(" arg_list : list, call by refernce evaluation\n"); }
        | expression
        { printf(" arg_list : call by reference evaluation\n"); }
        ;
return_stmt :
        RETURN
    { printf(" return_stmt : naked return [ check proc_type ]\n"); } 
        | RETURN any_value
{ printf(" return_stmt : return the reference [ che proc_type ]\n"); }
        ;
any_value :
        boolean_expr
       { printf(" any_value : boolean_result\n"); }
        | NAMED_STRUCT
       { printf(" any_value : named_struct\n"); }
        | expression
       { printf(" any_value : numeric_result\n"); }
        | string_val
       { printf(" any_value : string_result\n"); }
        | NAMED_PTR
       { printf(" any_value : named_pointer ( holding result)\n"); } 
        ;
case_stmt :
        str_case
        { printf(" str_case \n");}
        | arithmetic_case
        { printf(" arithmetic_case \n");}
        ;
str_case :
        CASE string_val COLON string_cases ENDCASE
        { printf(" CASE strval : string_cases END \n");}
        ;
string_cases :
        string_cases  string_case
        { printf(" string_cases string_case \n");}     
        | string_case
        { printf(" string_case \n");}
        ;
string_case :
        string_val COLON any_stmt SEMICOLON
        { printf(" string_case: strval : any_stmt ;\n");}
        ;
arithmetic_case :
        CASE variable COLON arith_cases ENDCASE
        { printf(" CASE variable : arith_cases END\n");}
        ;
arith_cases :
        arith_cases arith_case
        { printf(" arith_cases arith_case \n");}
        | arith_case
        { printf(" arith_case \n");}
        ;
arith_case :
        expression COLON any_stmt SEMICOLON
        { printf(" arith_case: expression : any_stmt ;\n");}
        ;

expression :
        expression ADD_OP expression
      { printf(" expression : t3 = t1 +/- t2 \n"); }
        | expression MUL_OP expression
      { printf(" expression : t3 = t1 * or / t2 \n"); }
        | ADD_OP expression
      { printf(" expression : t1 = -1 t1 \n"); }
        | variable
       { printf(" expression : variable \n"); }
        | variable power_list
        { printf(" exprssion : variable power_list \n"); }
        ;
variable :
        LEFT_PAREN expression RIGHT_PAREN
     { printf(" variable : ( expression )\n"); }
        | NUMERIC_CONSTANT
     { printf(" variable : t1 = eval(NUMERIC_CONSTANT)\n"); }
        | function_call
     { printf(" variable : function call check return is numeric\n"); }
        | NAMED_VAR
     { printf(" variable : named_var t1 = [named_var]\n"); }
        | ATSIGN NAMED_PTR
     { printf(" variable : @ ptr : t1 = [ address(ptr) ]\n"); }
        ;
power_list :
        power_list STARSTAR variable
      { printf(" power_list : list ** variable \n"); }
        | STARSTAR variable
      { printf(" power_list : ** variable \n"); }
        ;
function_call :
        FUNCTION_ID LEFT_PAREN arg_list RIGHT_PAREN
       { printf(" function_call : arg_list/ check return type\n"); }
        | FUNCTION_ID LEFT_PAREN RIGHT_PAREN
       { printf(" function_call : no args/ check return type\n"); }
        ;

boolean_expr :
        boolean_expr OR boolean_expr
      { printf(" boolean_expr : t3 = t1 OR t2\n"); }
        | boolean_expr AND boolean_expr
      { printf(" expression : t3 = t1 AND t2 \n"); }
        | boolean_expr LOG_OP boolean_expr
      { printf(" expression : t3 = t1 = t2 \n"); }
        | boolean_expr REL_OP boolean_expr
      { printf(" expression : t3 = t1 < t2 \n"); }
        | notted_boolean
        ;
notted_boolean :
        NOT notted_boolean
      { printf(" notted boolean: t2 = NOT t1\n"); }
        | boolean_var
        ;
boolean_var :
        TRUE
     { printf(" boolean_var : TRUE \n"); }
        | FALSE
     { printf(" boolean_var : FALSE \n"); }
        | NAMED_BOOL
     { printf(" boolean_var : named_bool\n"); }
        | BOOLEAN_ID LEFT_PAREN arg_list RIGHT_PAREN
     { printf(" boolean_var : bool_funct(arg_list)\n"); }
        | BOOLEAN_ID LEFT_PAREN RIGHT_PAREN
     { printf(" boolean_var : bool_funct()\n"); }
        | LEFT_PAREN boolean_expr RIGHT_PAREN
     { printf(" boolean_var : ( boolean_expr ) \n"); }
        ;
%%
        /* end of the prototype algol grammar */


#include <stdio.h>
#define FNAMESIZE 255
extern char *yytext;
extern int yylex();
long lmalloc();

 extern FILE *yyin;
FILE *ftable;
FILE *faction;
FILE *ftemp;


/* joe widows  */
 
%{
 /* the working syntactical definition of JALGOL .ALG  booted in MWC */
int var_type;  /* carries the ID type between productions */
%}
%term LEFT_PAREN BEGIN_SYM PROCEDURE INDEX LENGTH ENDSTRUCTURE
%term AND ARRAY BOOLEAN CASE DO ELSE END_SYM ENDCASE
%term EXTERNAL FALSE FOR FUNCTION GO GOTO IF INTEGER
%term LITERAL NOT OR OWN POINTER REAL RETURN STEP STRING
%term STRUCTURE SUBSTRING 
%term TO THEN TRUE TYPE UNION UNTIL WHILE 

%term ARROW COLON COMMA CONCAT 
%term SEMICOLON LEFT_MARK RIGHT_MARK
%term RIGHT_PAREN ATSIGN QUOTEQUOTE
%term STARSTAR ADD_OP MUL_OP REL_OP LOG_OP

%term ID NAMED_VAR NAMED_BOOL NAMED_PTR  NAMED_LABEL NAMED_STRING
%term FUNCTION_ID BOOLEAN_ID PROC_ID STRING_ID
%term NAMED_STRUCT USER_TYPE STRING_CONSTANT NUMERIC_CONSTANT
%term COMMENT
%left NOT AND OR LOG_OP REL_OP ADD_OP MUL_OP
%right STARSTAR CONCAT
%%
algol :
        block semi_list
     { printf(stdout," almost done : block \n") ;  }
        | block semi_list proc_list semi_list
     { printf(stdout," almost done block ; proc_list \n"); }
        | proc_list semi_list
     { printf(stdout," just procedure list \n"); }
        ;
block :
        block_head end_part
        { printf(stdout," close up : BLOCK\n"); }
        ;
block_head :
        BEGIN_SYM
                { printf(stdout," BEGIN token found: prolog()\n"); }
        ;
proc_list :
        proc_list semi_list proc_block
        { printf(stdout," we are outside of the main or inital block \n"); }
        | proc_block
        { printf(stdout," we have one outside block \n"); }
        ;
semi_list :
         SEMICOLON
          { printf(stdout,"  SEMICOLON  \n"); }
        | semi_list SEMICOLON
          { printf(stdout," semi_list \n"); }
        ;
end_part :
        declare_parts semi_list stmts semi_list block_end
        | block_end
        { printf(stdout," end of a block :  no epilog() here\n"); }
        | stmts semi_list block_end
        { printf(stdout," end of a block : epilog()/return \n"); }
                ;
block_end :
          END_SYM
           { printf(stdout," close block scope / adjust frame / epilog()\n"); }
        ;
declare_parts :
         declare_parts semi_list declare_member
        { printf(stdout," some internal declarations \n"); }
        | declare_member
        { printf(stdout," just one member declared \n"); }
        ;
declare_member :
        proc_block
           { printf(stdout," precedence phasing for declarations : proc \n"); }
        | declare_stmt
           { printf(stdout," precedence phasing for declarations : decl \n"); }
        ;
proc_block :
          proc_head proc_part
        { printf(stdout," proc_block \n"); }
        ;
proc_head :
          PROCEDURE ID
        { printf(stdout," proc_head : make ID procedure \n"); }
        | data_type PROCEDURE ID
        { printf(stdout," proc_head : make ID datatype procedure \n"); }
        ;
proc_part : proc_arg_part semi_list block
        { printf(stdout," end of a proc_block : epilog()/return \n"); }
        ;
proc_arg_part :
         LEFT_PAREN declare_list RIGHT_PAREN 
              { printf(stdout," proc block :: proc_head ( arg_list ) \n"); }
          ;
declare_list :
        declare_list semi_list declare_stmt
        { printf(stdout," declare_list : list ; stmt \n"); }
        | declare_stmt
        { printf(stdout," declare_list : stmt \n"); }
        ;
declare_stmt :
        type_declare
        { printf(stdout," dcl stmt : type \n"); }
        | user_declare
        { printf(stdout," dcl stmt : user \n"); }
        ;
type_declare :
        storage_type data_type id_list
        { printf(stdout," type_declare : storage datatype id_list\n"); }
        data_type id_list
        { printf(stdout," type_declare : datatype id_list\n"); }
        ;
data_type :
           BOOLEAN
                { printf(stdout," data_type : BOOLEAN\n"); var_type = BOOLEAN; }
         | INTEGER
               { printf(stdout," data_type : INTEGER\n");  var_type = INTEGER; }
         | POINTER
                { printf(stdout," data_type : POINTER\n"); var_type = POINTER; }
         | REAL
               { printf(stdout," data_type : REAL\n"); var_type = REAL; }
         | STRING
               { printf(stdout," data_type : STRING\n"); var_type = STRING; }
         | structure_type
               { printf(stdout," data_type : STRUCTURE\n"); var_type = 
STRUCTURE; }
         | USER_TYPE
               { printf(stdout," data_type : USER_TYPE\n"); var_type = 
USER_TYPE; }
         ;
storage_type :  
          OWN
        { printf(stdout," OWN means initialize to 0, NULL, EMPTY, etc\n"); }
         | EXTERNAL
        { printf(stdout," EXTERN means somebody else owns this address\n"); }
         ;
id_list :
        id_list COMMA ID
           { printf(stdout," id_list, add ID to symbol table var_type\n"); }
          |  ID
               { printf(stdout," add ID to symbol table using var_type\n"); }
        ;
structure_type :
          structure_define ENDSTRUCTURE
          { printf(stdout," turn off the STRUCTURE qualifier condition \n"); }
          ;
structure_define :
         STRUCTURE ID LEFT_MARK
      { printf(stdout," turn on the STRUCTURE qualifier condition : ID\n"); }
                declare_list
        { printf(stdout," STRUCTURE declare_list \n"); }
        ; 
stmts :
        stmts semi_list label_stmt
        { printf(stdout," stmts: list ; label_stmt\n"); }
      |  COMMENT label_stmt
        { printf(stdout," stmts: COMMENT label_stmt\n"); }
      | label_stmt
        { printf(stdout," stmts: label_stmt\n"); }
        ;
user_declare :
          TYPE data_type ID
 { printf(stdout,
  " using the globally defined data_type set ID as user_type \n"); } 
        ;
label_stmt :
     label_list stmt
        { printf(stdout," lable_stmt : lable_list stmt\n"); }
     | stmt
        { printf(stdout," label_stmt : stmt\n"); }
     ;
label_list :
     label_list label_mark
        { printf(stdout," label_list : list label_mark\n"); }
     | label_mark
        { printf(stdout," label_list : label_mark\n"); }
     ;
label_mark :
     ID COLON
 { printf(stdout," create a new label here s_lookup(yytext,NAMED_LABEL,INSERT); 
\n"); }
     ;
stmt :
        any_stmt
        { printf(stdout," stmt : any_stmt\n"); }
        | if_stmt
        { printf(stdout," stmt : if_stmt\n"); }
        | for_stmt
        { printf(stdout," stmt : for_stmt\n"); }
        ;

any_stmt :
        goto_stmt
        { printf(stdout," any_stmt : goto_stmt\n"); }
        | while_stmt
        { printf(stdout," any_stmt : while_stmt\n"); }
        | until_stmt
        { printf(stdout," any_stmt : until_stmt\n"); }
        | assign_stmt
        { printf(stdout," any_stmt : assign_stmt\n"); }
        | string_stmt
        { printf(stdout," any_stmt : string_stmt\n"); }
        | proc_call
        { printf(stdout," any_stmt : proc_call\n"); }
        | case_stmt
        { printf(stdout," any_stmt : case_stmt\n"); }
        | block
        { printf(stdout," any_stmt : block\n"); }
        | return_stmt
        { printf(stdout," any_stmt : return_stmt\n"); }
        ;
if_stmt :
      IF bool_part then_part else_part
        { printf(stdout," end if IF then else statement generate label \n"); }
     | IF bool_part boolean_expr then_part
        { printf(stdout," end of IF then statement generate label\n"); } 
     ;
bool_part :
        LEFT_PAREN boolean_expr
        { printf(stdout," add tmp_x = not tmp_x, jmp to label+2 \n"); }
        ;
then_part :
        RIGHT_PAREN THEN stmt
     { printf(stdout," ) THEN stmt :: jmp to end of else\n"); }
        | RIGHT_PAREN THEN 
     { printf(stdout," ) THEN :: null block jmp to end of else\n"); }
        ;
else_part :
        ELSE stmt
     { printf(stdout," ELSE stmt :: gen_labels \n"); }
       |  ELSE 
     { printf(stdout," ELSE :: gen_labels \n"); }
        ;
for_stmt:
        FOR step_part step_part_2 DO stmt
    { printf(stdout," generate for_branch_back :: jmp last_label: end_label 
\n"); }
        ;
step_part : NAMED_VAR  ARROW  expression STEP
        { printf(stdout," step_part : NAMED_VAR = expression STEP\n"); }
        ;
step_part_2 :
         expression UNTIL expression
{ printf(stdout," STEP eval(1) = eval(1) - eval(2) : gen_label, incr_code \n"); 
}
        ;
goto_stmt :
        GOTO NAMED_LABEL
          { printf(stdout," GOTO ID  : jmp to address(ID) \n"); }
        | GO TO NAMED_LABEL
          { printf(stdout," GOTO ID  : jmp to address(ID) \n"); }
        ;
while_stmt :
        WHILE bool_part RIGHT_PAREN DO stmt
  {  printf(stdout," WHILE generate branch back to previous label,gen 
label+1\n"); }
        ;

until_stmt :
        UNTIL bool_part RIGHT_PAREN DO stmt
        { printf(stdout," until_stmt:  generate label+3 \n"); }
        ;
assign_stmt :
        NAMED_VAR ARROW expression
         { printf(stdout," assign_stmt : named_var := expression\n"); }
        | NAMED_BOOL ARROW boolean_expr
         { printf(stdout," assign_stmt : named_bool := boolean_expr\n"); }
        | NAMED_BOOL ARROW expression
         { printf(stdout," assign_stmt :  named_ptr :=  expression\n"); }
        ;
string_stmt :
        NAMED_STRING ARROW string_val
       { printf(stdout," string_stmt : named_string := string_val\n"); }
        | substring_proc ARROW string_val
       { printf(stdout," string_stmt: substring_proc := string_val\n"); }
        ;
string_val :
        expression CONCAT NAMED_STRING
          { printf(stdout," string_val : expression || named_string\n"); }
        | string_val CONCAT expression
          { printf(stdout," string_val : string_val || expression\n"); }
        | string_val CONCAT NAMED_STRING
          { printf(stdout," string_val : string_val || named_string\n"); }
        | string_val CONCAT string_function
          { printf(stdout," string_val : string_vall || string_function\n"); }
        | QUOTEQUOTE
          { printf(stdout," string_val : '\0' (quotequote)\n"); }
        | STRING_CONSTANT
          { printf(stdout," string_val : string_constant (quoted string)\n"); }
        | NAMED_STRING
          { printf(stdout," string_val : NAMED_STRING\n"); }
        | string_function
          { printf(stdout," string_val : string_function\n"); }
        | substring_proc
          { printf(stdout," string_val : substring_proc\n"); }
        ;
substring_proc:
        SUBSTRING LEFT_PAREN NAMED_STRING COMMA expression
                   COMMA expression RIGHT_PAREN
  { printf(stdout," substring_proc : substr( Id, expression, expression )\n"); }
        ;
string_function :
        INDEX LEFT_PAREN string_val COMMA string_val RIGHT_PAREN
     { printf(stdout," string_function : returns integer (INDEX)\n"); }
        | LENGTH LEFT_PAREN string_val RIGHT_PAREN
     { printf(stdout," string_function : returns integer (LENGTH)\n"); }
        ;

proc_call :
        PROC_ID LEFT_PAREN arg_list RIGHT_PAREN
        { printf(stdout," proc_call : proc_id stack/arg eval/ jmp to\n"); }
        ;
arg_list :
        arg_list COMMA expression
        { printf(stdout," arg_list : list, call by refernce evaluation\n"); }
        | expression
        { printf(stdout," arg_list : call by reference evaluation\n"); }
        ;
return_stmt :
        RETURN
    { printf(stdout," return_stmt : naked return [ check proc_type ]\n"); } 
        | RETURN any_value
{ printf(stdout," return_stmt : return the reference [ che proc_type ]\n"); }
        ;
any_value :
        boolean_expr
       { printf(stdout," any_value : boolean_result\n"); }
        | NAMED_STRUCT
       { printf(stdout," any_value : named_struct\n"); }
        | expression
       { printf(stdout," any_value : numeric_result\n"); }
        | string_val
       { printf(stdout," any_value : string_result\n"); }
        | NAMED_PTR
       { printf(stdout," any_value : named_pointer ( holding result)\n"); } 
        ;
case_stmt :
        str_case
        { printf(stdout," str_case \n");}
        | arithmetic_case
        { printf(stdout," arithmetic_case \n");}
        ;
str_case :
        CASE string_val COLON string_cases ENDCASE
        { printf(stdout," CASE strval : string_cases END \n");}
        ;
string_cases :
        string_cases  string_case
        { printf(stdout, " string_cases string_case \n");}     
        | string_case
        { printf(stdout, " string_case \n");}
        ;
string_case :
        string_val COLON any_stmt SEMICOLON
        { printf(stdout," string_case: strval : any_stmt ;\n");}
        ;
arithmetic_case :
        CASE variable COLON arith_cases ENDCASE
        { printf(stdout," CASE variable : arith_cases END\n");}
        ;
arith_cases :
        arith_cases arith_case
        { printf(stdout," arith_cases arith_case \n");}
        | arith_case
        { printf(stdout," arith_case \n");}
        ;
arith_case :
        expression COLON any_stmt SEMICOLON
        { printf(stdout," arith_case: expression : any_stmt ;\n");}
        ;

expression :
        expression ADD_OP expression
      { printf(stdout," expression : t3 = t1 +/- t2 \n"); }
        | expression MUL_OP expression
      { printf(stdout," expression : t3 = t1 * or / t2 \n"); }
        | ADD_OP expression
      { printf(stdout," expression : t1 = -1 t1 \n"); }
        | variable
       { printf(stdout," expression : variable \n"); }
        | variable power_list
        { printf(stdout," exprssion : variable power_list \n"); }
        ;
variable :
        LEFT_PAREN expression RIGHT_PAREN
     { printf(stdout," variable : ( expression )\n"); }
        | NUMERIC_CONSTANT
     { printf(stdout," variable : t1 = eval(NUMERIC_CONSTANT)\n"); }
        | function_call
     { printf(stdout," variable : function call check return is numeric\n"); }
        | NAMED_VAR
     { printf(stdout," variable : named_var t1 = [named_var]\n"); }
        | ATSIGN NAMED_PTR
     { printf(stdout," variable : @ ptr : t1 = [ address(ptr) ]\n"); }
        ;
power_list :
        power_list STARSTAR variable
      { printf(stdout," power_list : list ** variable \n"); }
        | STARSTAR variable
      { printf(stdout," power_list : ** variable \n"); }
        ;
function_call :
        FUNCTION_ID LEFT_PAREN arg_list RIGHT_PAREN
       { printf(stdout," function_call : arg_list/ check return type\n"); }
        | FUNCTION_ID LEFT_PAREN RIGHT_PAREN
       { printf(stdout," function_call : no args/ check return type\n"); }
        ;

boolean_expr :
        boolean_expr OR boolean_expr
      { printf(stdout," boolean_expr : t3 = t1 OR t2\n"); }
        | boolean_expr AND boolean_expr
      { printf(stdout," expression : t3 = t1 AND t2 \n"); }
        | boolean_expr LOG_OP boolean_expr
      { printf(stdout," expression : t3 = t1 = t2 \n"); }
        | boolean_expr REL_OP boolean_expr
      { printf(stdout," expression : t3 = t1 < t2 \n"); }
        | notted_boolean
        ;
notted_boolean :
        NOT notted_boolean
      { printf(stdout," notted boolean: t2 = NOT t1\n"); }
        | boolean_var
        ;
boolean_var :
        TRUE
     { printf(stdout," boolean_var : TRUE \n"); }
        | FALSE
     { printf(stdout," boolean_var : FALSE \n"); }
        | NAMED_BOOL
     { printf(stdout," boolean_var : named_bool\n"); }
        | BOOLEAN_ID LEFT_PAREN arg_list RIGHT_PAREN
     { printf(stdout," boolean_var : bool_funct(arg_list)\n"); }
        | BOOLEAN_ID LEFT_PAREN RIGHT_PAREN
     { printf(stdout," boolean_var : bool_funct()\n"); }
        | LEFT_PAREN boolean_expr RIGHT_PAREN
     { printf(stdout," boolean_var : ( boolean_expr ) \n"); }
        ;
%%
        /* end of the prototype algol grammar */

#include <stdio.h>
#define FNAMESIZE 255
extern char *yytext;
extern int yylex();
long lmalloc();
extern FILE *yyin;
FILE *ftable;
FILE *faction;
FILE *ftemp;
extern yyerror( const char* );
static char filename[FNAMESIZE];
#define TEMPNAME "algol.tmp"
#define ACTNAME  "algol.act"
int i,j,lev,t, ty;
int c;
int tempty;
int *p;
int defsw, infsw;
char actname[8];
char *cp;
FILE *fdefine;
FILE *infile;
FILE *foutput;

begin
own integer a,b,c,d;
real e,f,g;

for a = 1 to 100000
   b = b+1;
 end;

substr(a,1,2)= '0';
end

# makefile for scan.ttp  ( algol scanner test)
alpha=abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ
numbers=0123456789/,\/;
CC= gcc
CFLAGS= -g  #-Ik:\mwc_309\include -I. -VCSD -NOVSTRICT
LD= ld
LDFLAGS=
LFLAGS= -L
LEX= flex
YFLAGS= -d 
YACC= yacc

all: test

test:   lex.yy.o y.tab.o
        gcc -o test lex.yy.o y.tab.o -I/root/glibc/glibc-2.3.1/ 
-L/lib/ld-2.3.1.so -lc

y.tab.o: y.tab.c
        gcc -g -c y.tab.c
        
lex.yy.o: lex.yy.c
        gcc -g -c lex.yy.c

y.tab.c: algol.y
        yacc -d algol.y

lex.yy.c: algol.l
        flex algol.l

scan.c: algol.l
        touch scan.c
        rm scan.c
        flex algol.l
        cp lex.yy.c scan.c

scan.o: scan.c

reply via email to

[Prev in Thread] Current Thread [Next in Thread]