New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
fortran.lex in vendors/AGRIF/dev/LEX – NEMO

source: vendors/AGRIF/dev/LEX/fortran.lex

Last change on this file was 14431, checked in by smasson, 3 years ago

agrif: merge AGRIF/dev_r14312_MPI_Interface into AGRIF/dev, ticket:2598#comment:21

  • Property svn:mime-type set to text/x-csrc
File size: 20.6 KB
Line 
1/******************************************************************************/
2/*                                                                            */
3/*     CONV (converter) for Agrif (Adaptive Grid Refinement In Fortran)       */
4/*                                                                            */
5/* Copyright or   or Copr. Laurent Debreu (Laurent.Debreu@imag.fr)            */
6/*                        Cyril Mazauric (Cyril_Mazauric@yahoo.fr)            */
7/* This software is governed by the CeCILL-C license under French law and     */
8/* abiding by the rules of distribution of free software.  You can  use,      */
9/* modify and/ or redistribute the software under the terms of the CeCILL-C   */
10/* license as circulated by CEA, CNRS and INRIA at the following URL          */
11/* "http://www.cecill.info".                                                  */
12/*                                                                            */
13/* As a counterpart to the access to the source code and  rights to copy,     */
14/* modify and redistribute granted by the license, users are provided only    */
15/* with a limited warranty  and the software's author,  the holder of the     */
16/* economic rights,  and the successive licensors  have only  limited         */
17/* liability.                                                                 */
18/*                                                                            */
19/* In this respect, the user's attention is drawn to the risks associated     */
20/* with loading,  using,  modifying and/or developing or reproducing the      */
21/* software by the user in light of its specific status of free software,     */
22/* that may mean  that it is complicated to manipulate,  and  that  also      */
23/* therefore means  that it is reserved for developers  and  experienced      */
24/* professionals having in-depth computer knowledge. Users are therefore      */
25/* encouraged to load and test the software's suitability as regards their    */
26/* requirements in conditions enabling the security of their systems and/or   */
27/* data to be ensured and,  more generally, to use and operate it in the      */
28/* same conditions as regards security.                                       */
29/*                                                                            */
30/* The fact that you are presently reading this means that you have had       */
31/* knowledge of the CeCILL-C license and that you accept its terms.           */
32/******************************************************************************/
33/* version 1.7                                                                */
34/******************************************************************************/
35%option warn
36%option noyywrap
37
38%x parameter
39%s character
40%x donottreat
41%x donottreat_interface
42%x includestate
43%s fortran77style
44%s fortran90style
45%{
46#include <math.h>
47#include <stdlib.h>
48#include <string.h>
49extern FILE * yyin;
50#define MAX_INCLUDE_DEPTH 30
51#define YY_BUF_SIZE 64000
52YY_BUFFER_STATE include_stack[MAX_INCLUDE_DEPTH];
53int line_num_input = 0;
54int newlinef90 = 0;
55int tmpc;
56
57int lastwasendofstmt = 1;
58
59extern char linebuf1[1024];
60extern char linebuf2[1024];
61
62int count_newlines(const char* str_in)
63{
64    int k, i = 0;
65    for( k=0 ; k<strlen(str_in) ; k++)
66        if (str_in[k] == '\n') i++;
67    return i;
68}
69
70#define PRINT_LINE_NUM()   //  { fprintf(stderr,"== Parsing l.%4d...\n", line_num_input); }
71#define INCREMENT_LINE_NUM() { line_num_input+=count_newlines(fortran_text) ; PRINT_LINE_NUM(); }
72#define YY_USER_ACTION       { if (increment_nbtokens !=0) token_since_endofstmt++; increment_nbtokens = 1; if (token_since_endofstmt>=1) lastwasendofstmt=0; /*printf("VALLIJSDFLSD = %d %d %s \n",lastwasendofstmt,token_since_endofstmt,fortran_text); */ if (firstpass) { strcpy(linebuf1, linebuf2); strncpy(linebuf2, fortran_text,80);} \
73                               else {my_position_before=setposcur();/*printf("muposition = %d\n",my_position_before);*/ECHO;} }
74#define YY_BREAK {/*printf("VALL = %d %d\n",lastwasendofstmt,token_since_endofstmt);*/if (token_since_endofstmt>=1) lastwasendofstmt=0; break;}
75
76void out_of_donottreat(void);
77
78%}
79
80SLASH       "/"
81HEXA        Z\'[0-9a-fA-F]+\'
82INTEGER     [0-9]+
83NAME        [a-zA-Z][a-zA-Z0-9\_]*
84EXPONENT    [edq][-+]?{INTEGER}
85
86BEG_DNT         ^[C!]"$AGRIF_DO_NOT_TREAT"[ \t]*([ \t\n]*(!.*\n)*)+\n
87END_DNT         ^[C!]"$AGRIF_END_DO_NOT_TREAT"[ \t]*([ \t\n]*(!.*\n)*)+\n
88
89BEG_INTERFACE   ^[ \t]*interface
90END_INTERFACE   ^[ \t]*end[ \t]*interface.*\n
91
92ASSIGNTYPE      "assignment"[ \t]*"("[ \t]*[-+=]+[ \t]*")"
93
94COMM_F77        ^[c*].*\n
95COMM_F90_1      ^([ \t\n]*(!.*\n)*)+\n
96COMM_F90_2      !.*
97NEXTLINEF90     &([ \t\n]|(!.*\n))*
98NEXTLINEF77     \n(([c*].*\n)|(([ \t]{0,4}|[ \t]{6,})!.*\n)|[\n])*[ ]{5}([a-z0-9&+$*.#/!;])
99LABEL           ^[ 0-9]{1,5}[ \t]+
100
101%%
102  if (infixed) BEGIN(fortran77style) ;
103  if (infree)  BEGIN(fortran90style) ;
104
105subroutine                  { return TOK_SUBROUTINE; }
106program                     { return TOK_PROGRAM; }
107allocate                    { inallocate = 1; return TOK_ALLOCATE; }
108continue                    { return TOK_CONTINUE; }
109nullify                    { return TOK_NULLIFY; }
110deallocate                  { inallocate = 1; return TOK_DEALLOCATE; }
111result                      { return TOK_RESULT; }
112function                    { return TOK_FUNCTION; }
113end                         { strcpy(yylval.na,fortran_text); return TOK_ENDUNIT;}
114include                     { pos_curinclude = setposcur()-9; BEGIN(includestate); }
115use                         { return TOK_USE;}
116rewind                      { return TOK_REWIND; }
117implicit                    { return TOK_IMPLICIT; }
118none                        { return TOK_NONE; }
119call                        { return TOK_CALL; }
120.true.                      { strcpy(yylval.na,fortran_text); return TOK_TRUE; }
121.false.                     { strcpy(yylval.na,fortran_text); return TOK_FALSE; }
122\=\>                        { return TOK_POINT_TO; }
123{ASSIGNTYPE}                { strcpy(yylval.na,fortran_text); return TOK_ASSIGNTYPE;}
124\*\*                        { strcpy(yylval.na,fortran_text); return TOK_DASTER; }
125\.eqv\.               { strcpy(yylval.na,fortran_text); return TOK_EQV; }
126\.[ \t]*eq[ \t]*\.                { strcpy(yylval.na,fortran_text); return TOK_EQ;  }
127\.gt\.                { strcpy(yylval.na,fortran_text); return TOK_GT;  }
128\.ge\.                { strcpy(yylval.na,fortran_text); return TOK_GE;  }
129\.lt\.                { strcpy(yylval.na,fortran_text); return TOK_LT;  }
130\.le\.                { strcpy(yylval.na,fortran_text); return TOK_LE;  }
131\.neqv\.              { strcpy(yylval.na,fortran_text); return TOK_NEQV;}
132\.[ \t]*ne[ \t]*\.                { strcpy(yylval.na,fortran_text); return TOK_NE;  }
133\.not\.               { strcpy(yylval.na,fortran_text); return TOK_NOT; }
134\.or\.                { strcpy(yylval.na,fortran_text); return TOK_OR;  }
135\.[ \t]*xor\.               { strcpy(yylval.na,fortran_text); return TOK_XOR; }
136\.and\.               { strcpy(yylval.na,fortran_text); return TOK_AND; }
137\=\=                  { strcpy(yylval.na,fortran_text); return TOK_EQUALEQUAL; }
138\/\=                  { strcpy(yylval.na,fortran_text); return TOK_SLASHEQUAL; }
139\<\=                  { strcpy(yylval.na,fortran_text); return TOK_INFEQUAL; }
140\>\=                  { strcpy(yylval.na,fortran_text); return TOK_SUPEQUAL; }
141module                      { return TOK_MODULE; }
142while                       { return TOK_WHILE; }
143concurrent                  { return TOK_CONCURRENT; }
144end[ \t]*do                 { return TOK_ENDDO; }
145do[\ t]+{INTEGER}           { strcpy(yylval.na,&fortran_text[2]);
146                              if (testandextractfromlist(&List_Do_labels,&fortran_text[2]) == 1)
147                              {
148                              return TOK_PLAINDO_LABEL_DJVIEW;
149                              }
150                              else
151                              {
152                              List_Do_labels=Insertname(List_Do_labels,yylval.na,1);
153                              return TOK_PLAINDO_LABEL;
154                             }
155                             }
156do                          { increment_nbtokens = 0; return TOK_PLAINDO;}
157real                        { strcpy(yylval.na,fortran_text); return TOK_REAL; }
158integer                     { strcpy(yylval.na,fortran_text); return TOK_INTEGER; }
159logical                     { strcpy(yylval.na,fortran_text); return TOK_LOGICAL; }
160character                   { strcpy(yylval.na,fortran_text); return TOK_CHARACTER; }
161{HEXA}                      { strcpy(yylval.na,fortran_text); return TOK_HEXA;}
162double[ \t]*precision       { strcpy(yylval.na,fortran_text); return TOK_DOUBLEPRECISION; }
163double[ \t]*complex         { strcpy(yylval.na,fortran_text); return TOK_DOUBLECOMPLEX; }
164complex                     { strcpy(yylval.na,fortran_text); return TOK_COMPLEX; }
165allocatable                 { return TOK_ALLOCATABLE; }
166contiguous                  { return TOK_CONTIGUOUS; }
167close                       { return TOK_CLOSE; }
168inquire                     { return TOK_INQUIRE; }
169dimension                   { return TOK_DIMENSION; }
170pause                       { return TOK_PAUSE; }
171equivalence                 { return TOK_EQUIVALENCE; }
172stop                        { return TOK_STOP; }
173where                       { return TOK_WHERE; }
174end[ \t]*where              { return TOK_ENDWHERE; }
175else[ \t]*where[ \t]*\(     { return TOK_ELSEWHEREPAR; }
176else[ \t]*where             { return TOK_ELSEWHERE; }
177^[ \t]*contains             { return TOK_CONTAINS; }
178only                        { return TOK_ONLY; }
179parameter                   { return TOK_PARAMETER; }
180recursive                   { return TOK_RECURSIVE; }
181common                      { return TOK_COMMON; }
182^[ \t]*global[ \t]+         { return TOK_GLOBAL; }
183external                    { return TOK_EXTERNAL; }
184intent                      { intent_spec = 1; return TOK_INTENT; }
185pointer                     { return TOK_POINTER; }
186optional                    { return TOK_OPTIONAL; }
187save                        { return TOK_SAVE; }
188^[ \t]*type[ \t]*\(         { pos_cur_decl = setposcur()-strlen(fortran_text); return TOK_TYPEPAR; }
189^[ \t]*type/[ \t\,:]+       { return TOK_TYPE; }
190end[ \t]*type               { return TOK_ENDTYPE; }
191stat                        { if (inallocate == 1) return TOK_STAT; else { strcpy(yylval.na,fortran_text); return TOK_NAME; } }
192open                        { return TOK_OPEN; }
193return                      { return TOK_RETURN; }
194exit                        { return TOK_EXIT; }
195print                       { return TOK_PRINT; }
196module[ \t]*procedure       { return TOK_PROCEDURE; }
197read[ \t]*\(                { in_io_control_spec = 1; return TOK_READ_PAR; }
198read                        { return TOK_READ; }
199namelist                    { return TOK_NAMELIST; }
200write[ \t]*\(               { in_io_control_spec = 1; return TOK_WRITE_PAR; }
201write                       { return TOK_WRITE; }
202flush                       { strcpy(yylval.na,fortran_text); return TOK_FLUSH; }
203target                      { return TOK_TARGET; }
204public                      { return TOK_PUBLIC; }
205private                     { return TOK_PRIVATE; }
206in                          { strcpy(yylval.na,fortran_text);
207                               if (intent_spec==1)
208                                {return TOK_IN; }
209                              else
210                              {
211                              return TOK_NAME;
212                              }
213                            }
214^[ \t]*data[ \t]+           { pos_curdata = setposcur()-strlen(fortran_text); /*Init_List_Data_Var();*/ return TOK_DATA; }
215go[ \t]*to                  { return TOK_PLAINGOTO; }
216out                         { strcpy(yylval.na,fortran_text);
217                               if (intent_spec==1)
218                                {return TOK_OUT; }
219                              else
220                              {
221                              return TOK_NAME;
222                              }
223                            }
224inout                       { strcpy(yylval.na,fortran_text);
225                               if (intent_spec==1)
226                                {return TOK_IN; }
227                              else
228                              {
229                              return TOK_INOUT;
230                              }
231                            }
232intrinsic                   { return TOK_INTRINSIC; }
233then                        { return TOK_THEN; }
234else[ \t]*if                { return TOK_ELSEIF; }
235else                        { return TOK_ELSE; }
236end[ \t]*if                 { return TOK_ENDIF; }
237if[ \t]*\(/(.*\)[ \t]*[\=|\+|\-]+.*\))   {strcpy(yylval.na,fortran_text);
238                            return TOK_LOGICALIF_PAR;
239                            }
240if/([ \t]*\([^(]*\)[ \t]*[\=|\+|\-]+)   {strcpy(yylval.na,fortran_text);
241                            return TOK_NAME;
242                            }
243if[ \t]*\(                 {strcpy(yylval.na,fortran_text);
244                            return TOK_LOGICALIF_PAR;
245                            }
246select[ \t]*case            { return TOK_SELECTCASE; }
247^[ \t]*case[ \t]*           { if (in_select_case_stmt > 0) return TOK_CASE ; else return TOK_NAME;}
248default                     { return TOK_DEFAULT; }
249end[ \t]*select             { return TOK_ENDSELECT; }
250file[ \t]*\=                { return TOK_FILE; }
251access[ \t]*\=                { return TOK_ACCESS; }
252action[ \t]*\=                { return TOK_ACTION; }
253iolength[ \t]*\=                { return TOK_IOLENGTH; }
254unit[ \t]*\=                { return TOK_UNIT; }
255opened[ \t]*\=                { return TOK_OPENED; }
256fmt[ \t]*\=                 { return TOK_FMT; }
257nml[ \t]*\=                 { return TOK_NML; }
258end[ \t]*\=                 { return TOK_END; }
259eor[ \t]*\=                 { return TOK_EOR; }
260len/([ \t]*\=)                 {
261                            if (in_char_selector ==1)
262                               return TOK_LEN;
263                            else
264                            {
265                            strcpy(yylval.na,fortran_text); return TOK_NAME;
266                            }
267                            }
268kind/([ \t]*\=)            {
269                            if ((in_char_selector==1) || (in_kind_selector == 1))
270                               return TOK_KIND;
271                            else
272                            {
273                            strcpy(yylval.na,fortran_text); return TOK_NAME;
274                            }
275                            }
276errmsg[ \t]*\=              { return TOK_ERRMSG; }
277mold[ \t]*\=              { return TOK_MOLD; }
278source[ \t]*\=              { return TOK_SOURCE; }
279position[ \t]*\=            { return TOK_POSITION; }
280iomsg[ \t]*\=               { return TOK_IOMSG; }
281iostat[ \t]*\=              { return TOK_IOSTAT; }
282err[ \t]*\=                 { return TOK_ERR; }
283form[ \t]*\=                { return TOK_FORM; }
284name/([ \t]*\=)             {
285                            if (in_inquire==1)
286                               return TOK_NAME_EQ;
287                            else
288                            {
289                            strcpy(yylval.na,fortran_text); return TOK_NAME;
290                            }
291                            }
292recl[ \t]*\=                { return TOK_RECL; }
293rec/([ \t]*\=)              { if (in_io_control_spec == 1)
294                              return TOK_REC;
295                             else
296                             {
297                             strcpy(yylval.na,fortran_text); return TOK_NAME;
298                             }
299                             }
300status/([ \t]*\=)           { if (close_or_connect == 1)
301                              return TOK_STATUS;
302                             else
303                             {
304                             strcpy(yylval.na,fortran_text); return TOK_NAME;
305                             }
306                             }
307status                      { strcpy(yylval.na,fortran_text); return TOK_NAME;}
308exist[ \t]*\=               { return TOK_EXIST; }
309cycle                       { return TOK_CYCLE; }
310backspace                   { return TOK_BACKSPACE; }
311::                          { return TOK_FOURDOTS;  }
312\/[ \t]*({NEXTLINEF90}|{NEXTLINEF77})*[ \t]*\/  { strcpy(yylval.na,fortran_text); return TOK_DSLASH; }
313\({SLASH}                   { return TOK_LEFTAB; }
314{SLASH}\)                   { return TOK_RIGHTAB; }
315{SLASH}                     { strcpy(yylval.na,fortran_text); return TOK_SLASH; }
316((\')[^']*&{0,1}\n[ \t]*&{0,1}[^']*(\'))+ {
317                              INCREMENT_LINE_NUM() ; strcpy(yylval.na,fortran_text); return TOK_CHAR_CUT; }
318<includestate>((\')[^']*(\'))+ {Add_Include_1(fortran_text);}
319<includestate>[ \t]* {}
320<includestate>\n {
321                  if (inmoduledeclare == 0 )
322                  {
323                  pos_end=setposcur();
324                  RemoveWordSET_0(fortran_out,pos_curinclude,pos_end-pos_curinclude);
325                  }
326                  out_of_donottreat();
327                  }
328((\')[^']*(\'))+               { strcpy(yylval.na,fortran_text);return TOK_CHAR_CONSTANT; }
329((\")[^"]*(\"))+               { strcpy(yylval.na,fortran_text);return TOK_CHAR_MESSAGE; }
330{BEG_INTERFACE}             { BEGIN(donottreat_interface); }
331<donottreat_interface>{END_INTERFACE} { out_of_donottreat(); return '\n'; }
332<donottreat_interface>.*\n            {INCREMENT_LINE_NUM() ; }
333<fortran77style>{NAME}{NEXTLINEF77}[a-zA-Z0-9\_]+ {strcpy(yylval.na,fortran_text); removenewline(yylval.na);
334                            return TOK_NAME; }
335{NAME}                      { strcpy(yylval.na,fortran_text); return TOK_NAME; }
336{INTEGER}\.[0-9]+           {strcpy(yylval.na,fortran_text); return TOK_CSTREAL; }
337({INTEGER}\.[0-9]*)/[^"and."|"false."|"true."|"eq."|"or."|"gt."|"ge."|"lt."|"le."|"not."|"ne."] {  // REAL1
338                              strcpy(yylval.na,fortran_text); return TOK_CSTREAL; }
339(({INTEGER}\.[0-9]+|[0-9]*\.{INTEGER}){EXPONENT}?)|{INTEGER}(\.)?{EXPONENT}                     {  // REAL2
340                              strcpy(yylval.na,fortran_text); return TOK_CSTREAL; }
341{INTEGER}                   { strcpy(yylval.na,fortran_text);
342                             if (lastwasendofstmt == 0)
343                              return TOK_CSTINT;
344                             else
345                              if (testandextractfromlist(&List_Do_labels,fortran_text) == 1)
346                              {
347                              removefromlist(&List_Do_labels,yylval.na);
348                              return TOK_LABEL_DJVIEW;
349                              }
350                              else
351                              {
352                              return TOK_LABEL;
353                              }
354                             }
355\$                          {}
356\.                          {}
357\(/([ \t]*[\+\-]?[a-zA-Z0-9]+[\.]*[0-9]*(\_({INTEGER}|{NAME}))?[ \t]*\,[ \t]*[\+\-]?[a-zA-Z0-9]+[\.]*[0-9]*(\_({INTEGER}|{NAME}))?[ \t]*\)) {
358                            in_complex_literal = -1;
359                            return (int) *fortran_text;
360                            }
361\(|\)|:|\[|\]|\+|\-|\*|\_   { strcpy(yylval.na,fortran_text); return (int) *fortran_text; }
362\%                          { strcpy(yylval.na,fortran_text); return (int) *fortran_text; }
363\;                          { lastwasendofstmt=1; token_since_endofstmt = 0; return TOK_SEMICOLON; }
364\,                          { if (in_complex_literal==-1) {return TOK_COMMACOMPLEX; in_complex_literal=0;} else; return (int) *fortran_text; }
365\=                          { return (int) *fortran_text; }
366\<                          { return (int) *fortran_text; }
367\>                          { return (int) *fortran_text; }
368\n                          { INCREMENT_LINE_NUM() ; lastwasendofstmt=1; token_since_endofstmt = 0; increment_nbtokens = 0; return '\n'; }
369[ \t]+                      {increment_nbtokens = 0;}
370<fortran77style>{LABEL}[ \t]*format[ \t]*\((.|{NEXTLINEF90}|{NEXTLINEF77})*\)  {
371                              return TOK_LABEL_FORMAT; }
372<fortran90style>^[ \t]*{INTEGER}[ \t]*format[ \t]*\((.|{NEXTLINEF90})*\) {return TOK_LABEL_FORMAT; }
373{NEXTLINEF90}               { INCREMENT_LINE_NUM() ; newlinef90=1; }
374<fortran77style>{NEXTLINEF77}               { INCREMENT_LINE_NUM() ;}
375
376{BEG_DNT}                   {INCREMENT_LINE_NUM() ; BEGIN(donottreat); }
377<donottreat>{END_DNT}       {out_of_donottreat(); return '\n'; }
378<donottreat>.*\n            {INCREMENT_LINE_NUM() ; }
379<fortran77style>{COMM_F77}  {INCREMENT_LINE_NUM() ; increment_nbtokens = 0;}
380{COMM_F90_1}                {INCREMENT_LINE_NUM() ; increment_nbtokens = 0;}
381{COMM_F90_2}                {increment_nbtokens = 0;}
382<<EOF>>                     {endoffile = 1; yyterminate();}
383%%
384
385void out_of_donottreat ( void )
386{
387    BEGIN(INITIAL);
388    if (infixed) BEGIN(fortran77style) ;
389    if (infree)  BEGIN(fortran90style) ;
390    INCREMENT_LINE_NUM() ;
391}
Note: See TracBrowser for help on using the repository browser.