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 branches/UKMO/dev_r5518_v3.6_asm_nemovar_community_ersem_hem08/NEMOGCM/EXTERNAL/AGRIF/LEX – NEMO

source: branches/UKMO/dev_r5518_v3.6_asm_nemovar_community_ersem_hem08/NEMOGCM/EXTERNAL/AGRIF/LEX/fortran.lex @ 9319

Last change on this file since 9319 was 7731, checked in by dford, 7 years ago

Merge in revisions 6625:7726 of dev_r5518_v3.4_asm_nemovar_community, so this branch will be identical to revison 7726 of dev_r5518_v3.6_asm_nemovar_community.

File size: 15.8 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%s fortran77style
42%s fortran90style
43%{
44#include <math.h>
45#include <stdlib.h>
46#include <string.h>
47extern FILE * yyin;
48#define MAX_INCLUDE_DEPTH 30
49YY_BUFFER_STATE include_stack[MAX_INCLUDE_DEPTH];
50int line_num_input = 1;
51int newlinef90 = 0;
52char tmpc;
53#define PRINT_LINE_NUM()     // { fprintf(stderr,"== Parsing l.%4d...\n", line_num_input); }
54#define INCREMENT_LINE_NUM() { line_num_input++; PRINT_LINE_NUM(); }
55
56/******************************************************************************/
57/**************PETITS PB NON PREVUS *******************************************/
58/******************************************************************************/
59/* NEXTLINF77 un ligne fortran 77 peut commencer par -      &a=b or on        */
60/*            a prevu seulement       & a=b avec l'espace entre le symbole    */
61/*            de la 7eme et le debut de la ligne de commande                  */
62/*            le ! est aussi interdit comme symbole de la 7 eme colonne       */
63/*            Normalement NEXTLINEF77 \n+[ ]{5}[^ ]                           */
64/******************************************************************************/
65#define YY_USER_ACTION  if (firstpass == 0) ECHO;
66
67void out_of_donottreat(void);
68
69%}
70
71REAL8 "real*8"[ \t]*"(a-h,o-z)"
72
73SLASH       "/"
74DSLASH      "/"[ \t]*"/"
75HEXA        Z\'[0-9a-fA-F]+\'
76NAME        [a-zA-Z\_][a-zA-Z0-9\_]*
77INTEGER     [0-9]+
78
79EXPONENT    [edq][-+]?{INTEGER}
80
81BEG_DNT         ^[C!]"$AGRIF_DO_NOT_TREAT"[ \t]*\n
82END_DNT         ^[C!]"$AGRIF_END_DO_NOT_TREAT"[ \t]*\n
83
84BEG_INTERFACE   ^[ \t]*interface
85END_INTERFACE   ^[ \t]*end[ \t]*interface.*\n
86
87ASSIGNTYPE      "assignment"[ \t]*"("[ \t]*[-+=]+[ \t]*")"
88
89COMM_F77        ^([Cc*](([ \t]*\n)|([^AaHhOo\n].*\n)))
90COMM_F90        ^[ \t]*!.*\n
91COMM_F90_2      !.*
92NEXTLINEF90     "&".*\n+
93NEXTLINEF77     [\n \t]*\n[ \t]{5}("&"|"+"|"$"|"*"|"1"|"2"|"3"|"4"|"5"|"6"|"7"|"8"|"9"|"."|"#")
94
95LABEL           ^(((" "|[0-9]){1,5})|([ \t]{1,5}))[ &]+
96
97%%
98  if (infixed) BEGIN(fortran77style) ;
99  if (infree)  BEGIN(fortran90style) ;
100
101{REAL8}                     { return TOK_REAL8; }
102subroutine                  { return TOK_SUBROUTINE; }
103program                     { return TOK_PROGRAM; }
104allocate                    { inallocate = 1; return TOK_ALLOCATE; }
105nullify                    { return TOK_NULLIFY; }
106null[ ]*\([ ]*\)            { return TOK_NULL_PTR; }
107deallocate                  { inallocate = 1; return TOK_DEALLOCATE; }
108result                      { return TOK_RESULT; }
109function                    { return TOK_FUNCTION; }
110end[ \t]*program            { strcpy(yylval.na,fortran_text); return TOK_ENDPROGRAM;}
111end[ \t]*module             { strcpy(yylval.na,fortran_text); return TOK_ENDMODULE; }
112end[ \t]*subroutine         { strcpy(yylval.na,fortran_text); return TOK_ENDSUBROUTINE;}
113end[ \t]*function           { strcpy(yylval.na,fortran_text); return TOK_ENDFUNCTION;}
114end                         { strcpy(yylval.na,fortran_text); return TOK_ENDUNIT;}
115include                     { pos_curinclude = setposcur()-9; return TOK_INCLUDE;}
116^[ \t]*use[ ]+              { strcpy(yylval.na,fortran_text);
117                              tmpc = (char) input(); unput(tmpc);
118                              if ( ( tmpc >= 'a' && tmpc <= 'z' ) ||
119                                   ( tmpc >= 'A' && tmpc <= 'Z' )  )  return TOK_USE;
120                              else                                    return TOK_NAME;
121                            }
122rewind                      { return TOK_REWIND; }
123implicit                    { return TOK_IMPLICIT; }
124none                        { return TOK_NONE; }
125call                        { return TOK_CALL; }
126.true.                      { return TOK_TRUE; }
127.false.                     { return TOK_FALSE; }
128\=\>                        { return TOK_POINT_TO; }
129{ASSIGNTYPE}                { strcpy(yylval.na,fortran_text); return TOK_ASSIGNTYPE;}
130\*\*                        { strcpy(yylval.na,fortran_text); return TOK_DASTER; }
131\.[ \t]*eqv\.               { strcpy(yylval.na,fortran_text); return TOK_EQV; }
132\.[ \t]*eq\.                { strcpy(yylval.na,fortran_text); return TOK_EQ;  }
133\.[ \t]*gt\.                { strcpy(yylval.na,fortran_text); return TOK_GT;  }
134\.[ \t]*ge\.                { strcpy(yylval.na,fortran_text); return TOK_GE;  }
135\.[ \t]*lt\.                { strcpy(yylval.na,fortran_text); return TOK_LT;  }
136\.[ \t]*le\.                { strcpy(yylval.na,fortran_text); return TOK_LE;  }
137\.[ \t]*neqv\.              { strcpy(yylval.na,fortran_text); return TOK_NEQV;}
138\.[ \t]*ne\.                { strcpy(yylval.na,fortran_text); return TOK_NE;  }
139\.[ \t]*not\.               { strcpy(yylval.na,fortran_text); return TOK_NOT; }
140\.[ \t]*or\.                { strcpy(yylval.na,fortran_text); return TOK_OR;  }
141\.[ \t]*xor\.               { strcpy(yylval.na,fortran_text); return TOK_XOR; }
142\.[ \t]*and\.               { strcpy(yylval.na,fortran_text); return TOK_AND; }
143module                      { return TOK_MODULE; }
144while                       { return TOK_WHILE; }
145concurrent                  { return TOK_CONCURRENT; }
146end[ \t]*do                 { return TOK_ENDDO; }
147do                          { return TOK_PLAINDO;}
148real                        { strcpy(yylval.na,fortran_text); return TOK_REAL; }
149integer                     { strcpy(yylval.na,fortran_text); return TOK_INTEGER; }
150logical                     { strcpy(yylval.na,fortran_text); return TOK_LOGICAL; }
151character                   { strcpy(yylval.na,fortran_text); return TOK_CHARACTER; }
152{HEXA}                      { strcpy(yylval.na,fortran_text); return TOK_HEXA;}
153double[ \t]*precision       { strcpy(yylval.na,fortran_text); return TOK_DOUBLEPRECISION; }
154double[ \t]*complex         { strcpy(yylval.na,fortran_text); return TOK_DOUBLECOMPLEX; }
155complex                     { return TOK_COMPLEX; }
156allocatable                 { return TOK_ALLOCATABLE; }
157close                       { return TOK_CLOSE; }
158inquire                     { return TOK_INQUIRE; }
159dimension                   { return TOK_DIMENSION; }
160pause                       { return TOK_PAUSE; }
161equivalence                 { return TOK_EQUIVALENCE; }
162stop                        { return TOK_STOP; }
163where                       { return TOK_WHERE; }
164end[ \t]*where              { return TOK_ENDWHERE; }
165else[ \t]*where[ \t]*\(     { return TOK_ELSEWHEREPAR; }
166else[ \t]*where             { return TOK_ELSEWHERE; }
167^[ \t]*contains             { return TOK_CONTAINS; }
168only                        { return TOK_ONLY; }
169parameter                   { return TOK_PARAMETER; }
170recursive                   { return TOK_RECURSIVE; }
171common                      { return TOK_COMMON; }
172^[ \t]*global[ \t]+         { return TOK_GLOBAL; }
173external                    { return TOK_EXTERNAL; }
174intent                      { return TOK_INTENT; }
175pointer                     { return TOK_POINTER; }
176optional                    { return TOK_OPTIONAL; }
177save                        { return TOK_SAVE; }
178^[ \t]*type[ \t]*\(         { pos_cur_decl = setposcur()-5; return TOK_TYPEPAR; }
179^[ \t]*type[ \t\,]+         { return TOK_TYPE; }
180end[ \t]*type               { return TOK_ENDTYPE; }
181stat                        { if (inallocate == 1) return TOK_STAT; else { strcpy(yylval.na,fortran_text); return TOK_NAME; } }
182open                        { return TOK_OPEN; }
183return                      { return TOK_RETURN; }
184exit[^(]                    { return TOK_EXIT; }
185print                       { return TOK_PRINT; }
186module[ \t]*procedure       { return TOK_PROCEDURE; }
187read                        { return TOK_READ; }
188namelist                    { return TOK_NAMELIST; }
189write                       { return TOK_WRITE; }
190flush                       { return TOK_FLUSH; }
191target                      { return TOK_TARGET; }
192public                      { return TOK_PUBLIC; }
193private                     { return TOK_PRIVATE; }
194in                          { strcpy(yylval.na,fortran_text); return TOK_IN; }
195^[ \t]*data[ \t]+           { pos_curdata = setposcur()-strlen(fortran_text); Init_List_Data_Var(); return TOK_DATA; }
196continue                    { return TOK_CONTINUE; }
197go[ \t]*to                  { return TOK_PLAINGOTO; }
198out                         { strcpy(yylval.na,fortran_text); return TOK_OUT; }
199inout                       { strcpy(yylval.na,fortran_text); return TOK_INOUT; }
200intrinsic                   { return TOK_INTRINSIC; }
201then                        { return TOK_THEN; }
202else[ \t]*if                { return TOK_ELSEIF; }
203else                        { return TOK_ELSE; }
204end[ \t]*if                 { return TOK_ENDIF; }
205if                          { return TOK_LOGICALIF; }
206sum[ \t]*\(                 { return TOK_SUM; }
207max[ \t]*\(                 { return TOK_MAX; }
208tanh                        { return TOK_TANH; }
209maxval                      { return TOK_MAXVAL; }
210trim                        { return TOK_TRIM; }
211sqrt\(                      { return TOK_SQRT; }
212select[ \t]*case            { return TOK_SELECTCASE; }
213^[ \t]*case[ \t]*           { return TOK_CASE; }
214default                     { return TOK_DEFAULT; }
215end[ \t]*select             { return TOK_ENDSELECT; }
216file[ \t]*\=                { return TOK_FILE; }
217unit[ \t]*\=                { return TOK_UNIT; }
218fmt[ \t]*\=                 { return TOK_FMT; }
219nml[ \t]*\=                 { return TOK_NML; }
220end[ \t]*\=                 { return TOK_END; }
221eor[ \t]*\=                 { return TOK_EOR; }
222err[ \t]*\=                 { return TOK_ERR; }
223exist[ \t]*\=               { return TOK_EXIST; }
224min[ \t]*\(                 { return TOK_MIN; }
225nint                        { return TOK_NINT; }
226float                       { return TOK_FLOAT; }
227exp                         { return TOK_EXP; }
228cos                         { return TOK_COS; }
229cosh                        { return TOK_COSH; }
230acos                        { return TOK_ACOS; }
231sin                         { return TOK_SIN; }
232sinh                        { return TOK_SINH; }
233asin                        { return TOK_ASIN; }
234log                         { return TOK_LOG; }
235tan                         { return TOK_TAN; }
236atan                        { return TOK_ATAN; }
237cycle                       { return TOK_CYCLE; }
238abs[ \t]*\(                 { return TOK_ABS; }
239mod                         { return TOK_MOD; }
240sign[ \t]*\(                { return TOK_SIGN; }
241minloc                      { return TOK_MINLOC; }
242maxloc                      { return TOK_MAXLOC; }
243minval                      { return TOK_MINVAL; }
244backspace                   { return TOK_BACKSPACE; }
245::                          { return TOK_FOURDOTS;  }
246\({SLASH}                   { return TOK_LEFTAB; }
247{SLASH}\)                   { return TOK_RIGHTAB; }
248format[ \t]*\((.|{NEXTLINEF90}|{NEXTLINEF77})*\)  {
249                              return TOK_FORMAT; }
250{SLASH}                     { strcpy(yylval.na,fortran_text); return TOK_SLASH; }
251DSLASH                      { strcpy(yylval.na,fortran_text); return TOK_DSLASH; }
252(\')[^']*&{0,1}\n[ \t]*&{0,1}[^']*(\') {
253                              strcpy(yylval.na,fortran_text); return TOK_CHAR_CUT; }
254(\')[^']*(\')             { strcpy(yylval.na,fortran_text);return TOK_CHAR_CONSTANT; }
255(\")[^"]*(\")             { strcpy(yylval.na,fortran_text);return TOK_CHAR_MESSAGE; }
256{BEG_INTERFACE}             { BEGIN(donottreat); }
257<donottreat>{END_INTERFACE} { out_of_donottreat(); return '\n'; }
258{NAME}                      { strcpy(yylval.na,fortran_text); return TOK_NAME; }
259({INTEGER}\.[0-9]*)/[^"and."|"false."|"true."|"eq."|"or."|"gt."|"ge."|"lt."|"le."|"not."|"ne."] {  // REAL1
260                              strcpy(yylval.na,fortran_text); return TOK_CSTREAL; }
261(({INTEGER}\.[0-9]+|[0-9]*\.{INTEGER}){EXPONENT}?)|{INTEGER}(\.)?{EXPONENT}                     {  // REAL2
262                              strcpy(yylval.na,fortran_text); return TOK_CSTREAL; }
263{INTEGER}                   { strcpy(yylval.na,fortran_text); return TOK_CSTINT; }
264\$                          {}
265\.                          {}
266\(|\)|:|\[|\]|\+|\-|\*      { strcpy(yylval.na,fortran_text); return (int) *fortran_text; }
267\%                          { strcpy(yylval.na,fortran_text); return (int) *fortran_text; }
268\;                          { return TOK_SEMICOLON; }
269\,                          { return (int) *fortran_text; }
270\=                          { return (int) *fortran_text; }
271\<                          { return (int) *fortran_text; }
272\>                          { return (int) *fortran_text; }
273\n                          { INCREMENT_LINE_NUM() ; return '\n'; }
274^[ ]*$                      {}
275[ \t]+                      {}
276{LABEL}                     { if (newlinef90 == 0) return TOK_LABEL; else newlinef90 = 0; }
277{NEXTLINEF90}               { INCREMENT_LINE_NUM() ; newlinef90=1; }
278{NEXTLINEF77}               { INCREMENT_LINE_NUM() ; }
279
280{BEG_DNT}                   { INCREMENT_LINE_NUM() ; BEGIN(donottreat); }
281<donottreat>{END_DNT}       { out_of_donottreat(); return '\n'; }
282<donottreat>.*\n            { INCREMENT_LINE_NUM() ; }
283<fortran77style>{COMM_F77}  { INCREMENT_LINE_NUM() ; }
284{COMM_F90}                  { INCREMENT_LINE_NUM() ; }
285{COMM_F90_2}                {}
286%%
287
288void out_of_donottreat ( void )
289{
290    BEGIN(INITIAL);
291    if (infixed) BEGIN(fortran77style) ;
292    if (infree)  BEGIN(fortran90style) ;
293    INCREMENT_LINE_NUM() ;
294}
Note: See TracBrowser for help on using the repository browser.