OSDN Git Service

PR fortran/30820
[pf3gnuchains/gcc-fork.git] / gcc / fortran / gfortran.h
1 /* gfortran header file
2    Copyright (C) 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007
3    Free Software Foundation, Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 2, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING.  If not, write to the Free
20 Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
21 02110-1301, USA.  */
22
23 #ifndef GCC_GFORTRAN_H
24 #define GCC_GFORTRAN_H
25
26 /* It's probably insane to have this large of a header file, but it
27    seemed like everything had to be recompiled anyway when a change
28    was made to a header file, and there were ordering issues with
29    multiple header files.  Besides, Microsoft's winnt.h was 250k last
30    time I looked, so by comparison this is perfectly reasonable.  */
31
32 #include "system.h"
33 #include "intl.h"
34 #include "coretypes.h"
35 #include "input.h"
36 #include "splay-tree.h"
37 /* The following ifdefs are recommended by the autoconf documentation
38    for any code using alloca.  */
39
40 /* AIX requires this to be the first thing in the file.  */
41 #ifdef __GNUC__
42 #else /* not __GNUC__ */
43 #ifdef HAVE_ALLOCA_H
44 #include <alloca.h>
45 #else /* do not HAVE_ALLOCA_H */
46 #ifdef _AIX
47 #pragma alloca
48 #else
49 #ifndef alloca                  /* predefined by HP cc +Olibcalls */
50 char *alloca ();
51 #endif /* not predefined */
52 #endif /* not _AIX */
53 #endif /* do not HAVE_ALLOCA_H */
54 #endif /* not __GNUC__ */
55
56 /* Major control parameters.  */
57
58 #define GFC_MAX_SYMBOL_LEN 63   /* Must be at least 63 for F2003.  */
59 #define GFC_MAX_DIMENSIONS 7    /* Maximum dimensions in an array.  */
60 #define GFC_LETTERS 26          /* Number of letters in the alphabet.  */
61
62 #define MAX_SUBRECORD_LENGTH 2147483639   /* 2**31-9 */
63
64
65 #define free(x) Use_gfc_free_instead_of_free()
66 #define gfc_is_whitespace(c) ((c==' ') || (c=='\t'))
67
68 #ifndef NULL
69 #define NULL ((void *) 0)
70 #endif
71
72 /* Stringization.  */
73 #define stringize(x) expand_macro(x)
74 #define expand_macro(x) # x
75
76 /* For a the runtime library, a standard prefix is a requirement to
77    avoid cluttering the namespace with things nobody asked for.  It's
78    ugly to look at and a pain to type when you add the prefix by hand,
79    so we hide it behind a macro.  */
80 #define PREFIX(x) "_gfortran_" x
81 #define PREFIX_LEN 10
82
83 #define BLANK_COMMON_NAME "__BLNK__"
84
85 /* Macro to initialize an mstring structure.  */
86 #define minit(s, t) { s, NULL, t }
87
88 /* Structure for storing strings to be matched by gfc_match_string.  */
89 typedef struct
90 {
91   const char *string;
92   const char *mp;
93   int tag;
94 }
95 mstring;
96
97
98 /* Flags to specify which standard/extension contains a feature.  */
99 #define GFC_STD_LEGACY          (1<<6) /* Backward compatibility.  */
100 #define GFC_STD_GNU             (1<<5)    /* GNU Fortran extension.  */
101 #define GFC_STD_F2003           (1<<4)    /* New in F2003.  */
102 /* Note that no additional features were deleted or made obsolescent
103    in F2003.  */
104 #define GFC_STD_F95             (1<<3)    /* New in F95.  */
105 #define GFC_STD_F95_DEL         (1<<2)    /* Deleted in F95.  */
106 #define GFC_STD_F95_OBS         (1<<1)    /* Obsolescent in F95.  */
107 #define GFC_STD_F77             (1<<0)    /* Included in F77, but not
108                                              deleted or obsolescent in
109                                              later standards.  */
110
111 /* Bitmasks for the various FPE that can be enabled.  */
112 #define GFC_FPE_INVALID    (1<<0)
113 #define GFC_FPE_DENORMAL   (1<<1)
114 #define GFC_FPE_ZERO       (1<<2)
115 #define GFC_FPE_OVERFLOW   (1<<3)
116 #define GFC_FPE_UNDERFLOW  (1<<4)
117 #define GFC_FPE_PRECISION  (1<<5)
118
119 /* Keep this in sync with libgfortran/io/io.h ! */
120
121 typedef enum
122   { CONVERT_NATIVE=0, CONVERT_SWAP, CONVERT_BIG, CONVERT_LITTLE }
123 options_convert;
124
125
126 /*************************** Enums *****************************/
127
128 /* The author remains confused to this day about the convention of
129    returning '0' for 'SUCCESS'... or was it the other way around?  The
130    following enum makes things much more readable.  We also start
131    values off at one instead of zero.  */
132
133 typedef enum
134 { SUCCESS = 1, FAILURE }
135 try;
136
137 /* This is returned by gfc_notification_std to know if, given the flags
138    that were given (-std=, -pedantic) we should issue an error, a warning
139    or nothing.  */
140
141 typedef enum
142 { SILENT, WARNING, ERROR }
143 notification;
144
145 /* Matchers return one of these three values.  The difference between
146    MATCH_NO and MATCH_ERROR is that MATCH_ERROR means that a match was
147    successful, but that something non-syntactic is wrong and an error
148    has already been issued.  */
149
150 typedef enum
151 { MATCH_NO = 1, MATCH_YES, MATCH_ERROR }
152 match;
153
154 typedef enum
155 { FORM_FREE, FORM_FIXED, FORM_UNKNOWN }
156 gfc_source_form;
157
158 typedef enum
159 { BT_UNKNOWN = 1, BT_INTEGER, BT_REAL, BT_COMPLEX,
160   BT_LOGICAL, BT_CHARACTER, BT_DERIVED, BT_PROCEDURE, BT_HOLLERITH
161 }
162 bt;
163
164 /* Expression node types.  */
165 typedef enum
166 { EXPR_OP = 1, EXPR_FUNCTION, EXPR_CONSTANT, EXPR_VARIABLE,
167   EXPR_SUBSTRING, EXPR_STRUCTURE, EXPR_ARRAY, EXPR_NULL
168 }
169 expr_t;
170
171 /* Array types.  */
172 typedef enum
173 { AS_EXPLICIT = 1, AS_ASSUMED_SHAPE, AS_DEFERRED,
174   AS_ASSUMED_SIZE, AS_UNKNOWN
175 }
176 array_type;
177
178 typedef enum
179 { AR_FULL = 1, AR_ELEMENT, AR_SECTION, AR_UNKNOWN }
180 ar_type;
181
182 /* Statement label types.  */
183 typedef enum
184 { ST_LABEL_UNKNOWN = 1, ST_LABEL_TARGET,
185   ST_LABEL_BAD_TARGET, ST_LABEL_FORMAT
186 }
187 gfc_sl_type;
188
189 /* Intrinsic operators.  */
190 typedef enum
191 { GFC_INTRINSIC_BEGIN = 0,
192   INTRINSIC_NONE = -1, INTRINSIC_UPLUS = GFC_INTRINSIC_BEGIN,
193   INTRINSIC_UMINUS, INTRINSIC_PLUS, INTRINSIC_MINUS, INTRINSIC_TIMES,
194   INTRINSIC_DIVIDE, INTRINSIC_POWER, INTRINSIC_CONCAT,
195   INTRINSIC_AND, INTRINSIC_OR, INTRINSIC_EQV, INTRINSIC_NEQV,
196   INTRINSIC_EQ, INTRINSIC_NE, INTRINSIC_GT, INTRINSIC_GE,
197   INTRINSIC_LT, INTRINSIC_LE, INTRINSIC_NOT, INTRINSIC_USER,
198   INTRINSIC_ASSIGN, INTRINSIC_PARENTHESES,
199   GFC_INTRINSIC_END /* Sentinel */
200 }
201 gfc_intrinsic_op;
202
203
204 /* Strings for all intrinsic operators.  */
205 extern mstring intrinsic_operators[];
206
207
208 /* This macro is the number of intrinsic operators that exist.
209    Assumptions are made about the numbering of the interface_op enums.  */
210 #define GFC_INTRINSIC_OPS GFC_INTRINSIC_END
211
212 /* Arithmetic results.  */
213 typedef enum
214 { ARITH_OK = 1, ARITH_OVERFLOW, ARITH_UNDERFLOW, ARITH_NAN,
215   ARITH_DIV0, ARITH_INCOMMENSURATE, ARITH_ASYMMETRIC
216 }
217 arith;
218
219 /* Statements.  */
220 typedef enum
221 {
222   ST_ARITHMETIC_IF, ST_ALLOCATE, ST_ATTR_DECL, ST_BACKSPACE, ST_BLOCK_DATA,
223   ST_CALL, ST_CASE, ST_CLOSE, ST_COMMON, ST_CONTINUE, ST_CONTAINS, ST_CYCLE,
224   ST_DATA, ST_DATA_DECL, ST_DEALLOCATE, ST_DO, ST_ELSE, ST_ELSEIF,
225   ST_ELSEWHERE, ST_END_BLOCK_DATA, ST_ENDDO, ST_IMPLIED_ENDDO,
226   ST_END_FILE, ST_FLUSH, ST_END_FORALL, ST_END_FUNCTION, ST_ENDIF,
227   ST_END_INTERFACE, ST_END_MODULE, ST_END_PROGRAM, ST_END_SELECT,
228   ST_END_SUBROUTINE, ST_END_WHERE, ST_END_TYPE, ST_ENTRY, ST_EQUIVALENCE,
229   ST_EXIT, ST_FORALL, ST_FORALL_BLOCK, ST_FORMAT, ST_FUNCTION, ST_GOTO,
230   ST_IF_BLOCK, ST_IMPLICIT, ST_IMPLICIT_NONE, ST_IMPORT, ST_INQUIRE, ST_INTERFACE,
231   ST_PARAMETER, ST_MODULE, ST_MODULE_PROC, ST_NAMELIST, ST_NULLIFY, ST_OPEN,
232   ST_PAUSE, ST_PRIVATE, ST_PROGRAM, ST_PUBLIC, ST_READ, ST_RETURN, ST_REWIND,
233   ST_STOP, ST_SUBROUTINE, ST_TYPE, ST_USE, ST_WHERE_BLOCK, ST_WHERE, ST_WRITE,
234   ST_ASSIGNMENT, ST_POINTER_ASSIGNMENT, ST_SELECT_CASE, ST_SEQUENCE,
235   ST_SIMPLE_IF, ST_STATEMENT_FUNCTION, ST_DERIVED_DECL, ST_LABEL_ASSIGNMENT,
236   ST_ENUM, ST_ENUMERATOR, ST_END_ENUM,
237   ST_OMP_ATOMIC, ST_OMP_BARRIER, ST_OMP_CRITICAL, ST_OMP_END_CRITICAL,
238   ST_OMP_END_DO, ST_OMP_END_MASTER, ST_OMP_END_ORDERED, ST_OMP_END_PARALLEL,
239   ST_OMP_END_PARALLEL_DO, ST_OMP_END_PARALLEL_SECTIONS,
240   ST_OMP_END_PARALLEL_WORKSHARE, ST_OMP_END_SECTIONS, ST_OMP_END_SINGLE,
241   ST_OMP_END_WORKSHARE, ST_OMP_DO, ST_OMP_FLUSH, ST_OMP_MASTER, ST_OMP_ORDERED,
242   ST_OMP_PARALLEL, ST_OMP_PARALLEL_DO, ST_OMP_PARALLEL_SECTIONS,
243   ST_OMP_PARALLEL_WORKSHARE, ST_OMP_SECTIONS, ST_OMP_SECTION, ST_OMP_SINGLE,
244   ST_OMP_THREADPRIVATE, ST_OMP_WORKSHARE,
245   ST_NONE
246 }
247 gfc_statement;
248
249
250 /* Types of interfaces that we can have.  Assignment interfaces are
251    considered to be intrinsic operators.  */
252 typedef enum
253 {
254   INTERFACE_NAMELESS = 1, INTERFACE_GENERIC,
255   INTERFACE_INTRINSIC_OP, INTERFACE_USER_OP
256 }
257 interface_type;
258
259 /* Symbol flavors: these are all mutually exclusive.
260    10 elements = 4 bits.  */
261 typedef enum sym_flavor
262 {
263   FL_UNKNOWN = 0, FL_PROGRAM, FL_BLOCK_DATA, FL_MODULE, FL_VARIABLE,
264   FL_PARAMETER, FL_LABEL, FL_PROCEDURE, FL_DERIVED, FL_NAMELIST
265 }
266 sym_flavor;
267
268 /* Procedure types.  7 elements = 3 bits.  */
269 typedef enum procedure_type
270 { PROC_UNKNOWN, PROC_MODULE, PROC_INTERNAL, PROC_DUMMY,
271   PROC_INTRINSIC, PROC_ST_FUNCTION, PROC_EXTERNAL
272 }
273 procedure_type;
274
275 /* Intent types.  */
276 typedef enum sym_intent
277 { INTENT_UNKNOWN = 0, INTENT_IN, INTENT_OUT, INTENT_INOUT
278 }
279 sym_intent;
280
281 /* Access types.  */
282 typedef enum gfc_access
283 { ACCESS_UNKNOWN = 0, ACCESS_PUBLIC, ACCESS_PRIVATE
284 }
285 gfc_access;
286
287 /* Flags to keep track of where an interface came from.
288    4 elements = 2 bits.  */
289 typedef enum ifsrc
290 { IFSRC_UNKNOWN = 0, IFSRC_DECL, IFSRC_IFBODY, IFSRC_USAGE
291 }
292 ifsrc;
293
294 /* Strings for all symbol attributes.  We use these for dumping the
295    parse tree, in error messages, and also when reading and writing
296    modules.  In symbol.c.  */
297 extern const mstring flavors[];
298 extern const mstring procedures[];
299 extern const mstring intents[];
300 extern const mstring access_types[];
301 extern const mstring ifsrc_types[];
302
303 /* Enumeration of all the generic intrinsic functions.  Used by the
304    backend for identification of a function.  */
305
306 enum gfc_generic_isym_id
307 {
308   /* GFC_ISYM_NONE is used for intrinsics which will never be seen by
309      the backend (eg. KIND).  */
310   GFC_ISYM_NONE = 0,
311   GFC_ISYM_ABS,
312   GFC_ISYM_ACCESS,
313   GFC_ISYM_ACHAR,
314   GFC_ISYM_ACOS,
315   GFC_ISYM_ACOSH,
316   GFC_ISYM_ADJUSTL,
317   GFC_ISYM_ADJUSTR,
318   GFC_ISYM_AIMAG,
319   GFC_ISYM_AINT,
320   GFC_ISYM_ALL,
321   GFC_ISYM_ALLOCATED,
322   GFC_ISYM_ANINT,
323   GFC_ISYM_AND,
324   GFC_ISYM_ANY,
325   GFC_ISYM_ASIN,
326   GFC_ISYM_ASINH,
327   GFC_ISYM_ASSOCIATED,
328   GFC_ISYM_ATAN,
329   GFC_ISYM_ATANH,
330   GFC_ISYM_ATAN2,
331   GFC_ISYM_J0,
332   GFC_ISYM_J1,
333   GFC_ISYM_JN,
334   GFC_ISYM_Y0,
335   GFC_ISYM_Y1,
336   GFC_ISYM_YN,
337   GFC_ISYM_BTEST,
338   GFC_ISYM_CEILING,
339   GFC_ISYM_CHAR,
340   GFC_ISYM_CHDIR,
341   GFC_ISYM_CHMOD,
342   GFC_ISYM_CMPLX,
343   GFC_ISYM_COMMAND_ARGUMENT_COUNT,
344   GFC_ISYM_COMPLEX,
345   GFC_ISYM_CONJG,
346   GFC_ISYM_COS,
347   GFC_ISYM_COSH,
348   GFC_ISYM_COUNT,
349   GFC_ISYM_CSHIFT,
350   GFC_ISYM_CTIME,
351   GFC_ISYM_DBLE,
352   GFC_ISYM_DIM,
353   GFC_ISYM_DOT_PRODUCT,
354   GFC_ISYM_DPROD,
355   GFC_ISYM_EOSHIFT,
356   GFC_ISYM_ERF,
357   GFC_ISYM_ERFC,
358   GFC_ISYM_ETIME,
359   GFC_ISYM_EXP,
360   GFC_ISYM_EXPONENT,
361   GFC_ISYM_FDATE,
362   GFC_ISYM_FGET,
363   GFC_ISYM_FGETC,
364   GFC_ISYM_FLOOR,
365   GFC_ISYM_FNUM,
366   GFC_ISYM_FPUT,
367   GFC_ISYM_FPUTC,
368   GFC_ISYM_FRACTION,
369   GFC_ISYM_FSTAT,
370   GFC_ISYM_FTELL,
371   GFC_ISYM_GETCWD,
372   GFC_ISYM_GETGID,
373   GFC_ISYM_GETPID,
374   GFC_ISYM_GETUID,
375   GFC_ISYM_HOSTNM,
376   GFC_ISYM_IACHAR,
377   GFC_ISYM_IAND,
378   GFC_ISYM_IARGC,
379   GFC_ISYM_IBCLR,
380   GFC_ISYM_IBITS,
381   GFC_ISYM_IBSET,
382   GFC_ISYM_ICHAR,
383   GFC_ISYM_IEOR,
384   GFC_ISYM_IERRNO,
385   GFC_ISYM_INDEX,
386   GFC_ISYM_INT,
387   GFC_ISYM_INT2,
388   GFC_ISYM_INT8,
389   GFC_ISYM_IOR,
390   GFC_ISYM_IRAND,
391   GFC_ISYM_ISATTY,
392   GFC_ISYM_ISHFT,
393   GFC_ISYM_ISHFTC,
394   GFC_ISYM_KILL,
395   GFC_ISYM_LBOUND,
396   GFC_ISYM_LEN,
397   GFC_ISYM_LEN_TRIM,
398   GFC_ISYM_LINK,
399   GFC_ISYM_LGE,
400   GFC_ISYM_LGT,
401   GFC_ISYM_LLE,
402   GFC_ISYM_LLT,
403   GFC_ISYM_LOC,
404   GFC_ISYM_LOG,
405   GFC_ISYM_LOG10,
406   GFC_ISYM_LOGICAL,
407   GFC_ISYM_LONG,
408   GFC_ISYM_LSHIFT,
409   GFC_ISYM_LSTAT,
410   GFC_ISYM_MALLOC,
411   GFC_ISYM_MATMUL,
412   GFC_ISYM_MAX,
413   GFC_ISYM_MAXLOC,
414   GFC_ISYM_MAXVAL,
415   GFC_ISYM_MCLOCK,
416   GFC_ISYM_MCLOCK8,
417   GFC_ISYM_MERGE,
418   GFC_ISYM_MIN,
419   GFC_ISYM_MINLOC,
420   GFC_ISYM_MINVAL,
421   GFC_ISYM_MOD,
422   GFC_ISYM_MODULO,
423   GFC_ISYM_NEAREST,
424   GFC_ISYM_NINT,
425   GFC_ISYM_NOT,
426   GFC_ISYM_OR,
427   GFC_ISYM_PACK,
428   GFC_ISYM_PRESENT,
429   GFC_ISYM_PRODUCT,
430   GFC_ISYM_RAND,
431   GFC_ISYM_REAL,
432   GFC_ISYM_RENAME,
433   GFC_ISYM_REPEAT,
434   GFC_ISYM_RESHAPE,
435   GFC_ISYM_RSHIFT,
436   GFC_ISYM_RRSPACING,
437   GFC_ISYM_SCALE,
438   GFC_ISYM_SCAN,
439   GFC_ISYM_SECOND,
440   GFC_ISYM_SECNDS,
441   GFC_ISYM_SET_EXPONENT,
442   GFC_ISYM_SHAPE,
443   GFC_ISYM_SI_KIND,
444   GFC_ISYM_SIGN,
445   GFC_ISYM_SIGNAL,
446   GFC_ISYM_SIN,
447   GFC_ISYM_SINH,
448   GFC_ISYM_SIZE,
449   GFC_ISYM_SPACING,
450   GFC_ISYM_SPREAD,
451   GFC_ISYM_SQRT,
452   GFC_ISYM_SR_KIND,
453   GFC_ISYM_STAT,
454   GFC_ISYM_SUM,
455   GFC_ISYM_SYMLNK,
456   GFC_ISYM_SYSTEM,
457   GFC_ISYM_TAN,
458   GFC_ISYM_TANH,
459   GFC_ISYM_TIME,
460   GFC_ISYM_TIME8,
461   GFC_ISYM_TRANSFER,
462   GFC_ISYM_TRANSPOSE,
463   GFC_ISYM_TRIM,
464   GFC_ISYM_TTYNAM,
465   GFC_ISYM_UBOUND,
466   GFC_ISYM_UMASK,
467   GFC_ISYM_UNLINK,
468   GFC_ISYM_UNPACK,
469   GFC_ISYM_VERIFY,
470   GFC_ISYM_XOR,
471   GFC_ISYM_CONVERSION
472 };
473 typedef enum gfc_generic_isym_id gfc_generic_isym_id;
474
475 /* Runtime errors.  The EOR and EOF errors are required to be negative.
476    These codes must be kept synchronized with their equivalents in
477    libgfortran/libgfortran.h .  */
478
479 typedef enum
480 {
481   IOERROR_FIRST = -3,           /* Marker for the first error.  */
482   IOERROR_EOR = -2,
483   IOERROR_END = -1,
484   IOERROR_OK = 0,                       /* Indicates success, must be zero.  */
485   IOERROR_OS = 5000,            /* Operating system error, more info in errno.  */
486   IOERROR_OPTION_CONFLICT,
487   IOERROR_BAD_OPTION,
488   IOERROR_MISSING_OPTION,
489   IOERROR_ALREADY_OPEN,
490   IOERROR_BAD_UNIT,
491   IOERROR_FORMAT,
492   IOERROR_BAD_ACTION,
493   IOERROR_ENDFILE,
494   IOERROR_BAD_US,
495   IOERROR_READ_VALUE,
496   IOERROR_READ_OVERFLOW,
497   IOERROR_INTERNAL,
498   IOERROR_INTERNAL_UNIT,
499   IOERROR_ALLOCATION,
500   IOERROR_DIRECT_EOR,
501   IOERROR_SHORT_RECORD,
502   IOERROR_CORRUPT_FILE,
503   IOERROR_LAST                  /* Not a real error, the last error # + 1.  */
504 }
505 ioerror_codes;
506
507
508 /************************* Structures *****************************/
509
510 /* Used for keeping things in balanced binary trees.  */
511 #define BBT_HEADER(self) int priority; struct self *left, *right
512
513 /* Symbol attribute structure.  */
514 typedef struct
515 {
516   /* Variable attributes.  */
517   unsigned allocatable:1, dimension:1, external:1, intrinsic:1,
518     optional:1, pointer:1, save:1, target:1, value:1, volatile_:1,
519     dummy:1, result:1, assign:1, threadprivate:1, not_always_present:1,
520     implied_index:1;
521
522   unsigned data:1,              /* Symbol is named in a DATA statement.  */
523     protected:1,                /* Symbol has been marked as protected.  */
524     use_assoc:1,                /* Symbol has been use-associated.  */
525     use_only:1;                 /* Symbol has been use-associated, with ONLY.  */
526
527   unsigned in_namelist:1, in_common:1, in_equivalence:1;
528   unsigned function:1, subroutine:1, generic:1, generic_copy:1;
529   unsigned implicit_type:1;     /* Type defined via implicit rules.  */
530   unsigned untyped:1;           /* No implicit type could be found.  */
531
532   /* Function/subroutine attributes */
533   unsigned sequence:1, elemental:1, pure:1, recursive:1;
534   unsigned unmaskable:1, masked:1, contained:1, mod_proc:1;
535
536   /* This is set if the subroutine doesn't return.  Currently, this
537      is only possible for intrinsic subroutines.  */
538   unsigned noreturn:1;
539
540   /* Set if this procedure is an alternate entry point.  These procedures
541      don't have any code associated, and the backend will turn them into
542      thunks to the master function.  */
543   unsigned entry:1;
544
545   /* Set if this is the master function for a procedure with multiple
546      entry points.  */
547   unsigned entry_master:1;
548
549   /* Set if this is the master function for a function with multiple
550      entry points where characteristics of the entry points differ.  */
551   unsigned mixed_entry_master:1;
552
553   /* Set if a function must always be referenced by an explicit interface.  */
554   unsigned always_explicit:1;
555
556   /* Set if the symbol has been referenced in an expression.  No further
557      modification of type or type parameters is permitted.  */
558   unsigned referenced:1;
559
560   /* Set if the symbol has ambiguous interfaces.  */
561   unsigned ambiguous_interfaces:1;
562
563   /* Set if the is the symbol for the main program.  This is the least
564      cumbersome way to communicate this function property without
565      strcmp'ing with __MAIN everywhere.  */
566   unsigned is_main_program:1;
567
568   /* Mutually exclusive multibit attributes.  */
569   ENUM_BITFIELD (gfc_access) access:2;
570   ENUM_BITFIELD (sym_intent) intent:2;
571   ENUM_BITFIELD (sym_flavor) flavor:4;
572   ENUM_BITFIELD (ifsrc) if_source:2;
573
574   ENUM_BITFIELD (procedure_type) proc:3;
575
576   /* Special attributes for Cray pointers, pointees.  */
577   unsigned cray_pointer:1, cray_pointee:1;
578
579   /* The symbol is a derived type with allocatable components, possibly nested.
580    */
581   unsigned alloc_comp:1;
582
583   /* The namespace where the VOLATILE attribute has been set.  */
584   struct gfc_namespace *volatile_ns;
585 }
586 symbol_attribute;
587
588
589 /* The following three structures are used to identify a location in
590    the sources.
591
592    gfc_file is used to maintain a tree of the source files and how
593    they include each other
594
595    gfc_linebuf holds a single line of source code and information
596    which file it resides in
597
598    locus point to the sourceline and the character in the source
599    line.
600 */
601
602 typedef struct gfc_file
603 {
604   struct gfc_file *included_by, *next, *up;
605   int inclusion_line, line;
606   char *filename;
607 } gfc_file;
608
609 typedef struct gfc_linebuf
610 {
611 #ifdef USE_MAPPED_LOCATION
612   source_location location;
613 #else
614   int linenum;
615 #endif
616   struct gfc_file *file;
617   struct gfc_linebuf *next;
618
619   int truncated;
620
621   char line[1];
622 } gfc_linebuf;
623
624 #define gfc_linebuf_header_size (offsetof (gfc_linebuf, line))
625
626 typedef struct
627 {
628   char *nextc;
629   gfc_linebuf *lb;
630 } locus;
631
632 /* In order for the "gfc" format checking to work correctly, you must
633    have declared a typedef locus first.  */
634 #if GCC_VERSION >= 4001
635 #define ATTRIBUTE_GCC_GFC(m, n) __attribute__ ((__format__ (__gcc_gfc__, m, n))) ATTRIBUTE_NONNULL(m)
636 #else
637 #define ATTRIBUTE_GCC_GFC(m, n) ATTRIBUTE_NONNULL(m)
638 #endif
639
640
641 extern int gfc_suppress_error;
642
643
644 /* Character length structures hold the expression that gives the
645    length of a character variable.  We avoid putting these into
646    gfc_typespec because doing so prevents us from doing structure
647    copies and forces us to deallocate any typespecs we create, as well
648    as structures that contain typespecs.  They also can have multiple
649    character typespecs pointing to them.
650
651    These structures form a singly linked list within the current
652    namespace and are deallocated with the namespace.  It is possible to
653    end up with gfc_charlen structures that have nothing pointing to them.  */
654
655 typedef struct gfc_charlen
656 {
657   struct gfc_expr *length;
658   struct gfc_charlen *next;
659   tree backend_decl;
660
661   int resolved;
662 }
663 gfc_charlen;
664
665 #define gfc_get_charlen() gfc_getmem(sizeof(gfc_charlen))
666
667 /* Type specification structure.  FIXME: derived and cl could be union???  */
668 typedef struct
669 {
670   bt type;
671   int kind;
672   struct gfc_symbol *derived;
673   gfc_charlen *cl;      /* For character types only.  */
674 }
675 gfc_typespec;
676
677 /* Array specification.  */
678 typedef struct
679 {
680   int rank;     /* A rank of zero means that a variable is a scalar.  */
681   array_type type;
682   struct gfc_expr *lower[GFC_MAX_DIMENSIONS], *upper[GFC_MAX_DIMENSIONS];
683
684   /* These two fields are used with the Cray Pointer extension.  */
685   bool cray_pointee; /* True iff this spec belongs to a cray pointee.  */
686   bool cp_was_assumed; /* AS_ASSUMED_SIZE cp arrays are converted to
687                         AS_EXPLICIT, but we want to remember that we
688                         did this.  */
689
690 }
691 gfc_array_spec;
692
693 #define gfc_get_array_spec() gfc_getmem(sizeof(gfc_array_spec))
694
695
696 /* Components of derived types.  */
697 typedef struct gfc_component
698 {
699   const char *name;
700   gfc_typespec ts;
701
702   int pointer, allocatable, dimension;
703   gfc_array_spec *as;
704
705   tree backend_decl;
706   locus loc;
707   struct gfc_expr *initializer;
708   struct gfc_component *next;
709 }
710 gfc_component;
711
712 #define gfc_get_component() gfc_getmem(sizeof(gfc_component))
713
714 /* Formal argument lists are lists of symbols.  */
715 typedef struct gfc_formal_arglist
716 {
717   /* Symbol representing the argument at this position in the arglist.  */
718   struct gfc_symbol *sym;
719   /* Points to the next formal argument.  */
720   struct gfc_formal_arglist *next;
721 }
722 gfc_formal_arglist;
723
724 #define gfc_get_formal_arglist() gfc_getmem(sizeof(gfc_formal_arglist))
725
726
727 /* The gfc_actual_arglist structure is for actual arguments.  */
728 typedef struct gfc_actual_arglist
729 {
730   const char *name;
731   /* Alternate return label when the expr member is null.  */
732   struct gfc_st_label *label;
733
734   /* This is set to the type of an eventual omitted optional
735      argument. This is used to determine if a hidden string length
736      argument has to be added to a function call.  */
737   bt missing_arg_type;
738
739   struct gfc_expr *expr;
740   struct gfc_actual_arglist *next;
741 }
742 gfc_actual_arglist;
743
744 #define gfc_get_actual_arglist() gfc_getmem(sizeof(gfc_actual_arglist))
745
746
747 /* Because a symbol can belong to multiple namelists, they must be
748    linked externally to the symbol itself.  */
749 typedef struct gfc_namelist
750 {
751   struct gfc_symbol *sym;
752   struct gfc_namelist *next;
753 }
754 gfc_namelist;
755
756 #define gfc_get_namelist() gfc_getmem(sizeof(gfc_namelist))
757
758 enum
759 {
760   OMP_LIST_PRIVATE,
761   OMP_LIST_FIRSTPRIVATE,
762   OMP_LIST_LASTPRIVATE,
763   OMP_LIST_COPYPRIVATE,
764   OMP_LIST_SHARED,
765   OMP_LIST_COPYIN,
766   OMP_LIST_PLUS,
767   OMP_LIST_REDUCTION_FIRST = OMP_LIST_PLUS,
768   OMP_LIST_MULT,
769   OMP_LIST_SUB,
770   OMP_LIST_AND,
771   OMP_LIST_OR,
772   OMP_LIST_EQV,
773   OMP_LIST_NEQV,
774   OMP_LIST_MAX,
775   OMP_LIST_MIN,
776   OMP_LIST_IAND,
777   OMP_LIST_IOR,
778   OMP_LIST_IEOR,
779   OMP_LIST_REDUCTION_LAST = OMP_LIST_IEOR,
780   OMP_LIST_NUM
781 };
782
783 /* Because a symbol can belong to multiple namelists, they must be
784    linked externally to the symbol itself.  */
785 typedef struct gfc_omp_clauses
786 {
787   struct gfc_expr *if_expr;
788   struct gfc_expr *num_threads;
789   gfc_namelist *lists[OMP_LIST_NUM];
790   enum
791     {
792       OMP_SCHED_NONE,
793       OMP_SCHED_STATIC,
794       OMP_SCHED_DYNAMIC,
795       OMP_SCHED_GUIDED,
796       OMP_SCHED_RUNTIME
797     } sched_kind;
798   struct gfc_expr *chunk_size;
799   enum
800     {
801       OMP_DEFAULT_UNKNOWN,
802       OMP_DEFAULT_NONE,
803       OMP_DEFAULT_PRIVATE,
804       OMP_DEFAULT_SHARED
805     } default_sharing;
806   bool nowait, ordered;
807 }
808 gfc_omp_clauses;
809
810 #define gfc_get_omp_clauses() gfc_getmem(sizeof(gfc_omp_clauses))
811
812
813 /* The gfc_st_label structure is a doubly linked list attached to a
814    namespace that records the usage of statement labels within that
815    space.  */
816 /* TODO: Make format/statement specifics a union.  */
817 typedef struct gfc_st_label
818 {
819   BBT_HEADER(gfc_st_label);
820
821   int value;
822
823   gfc_sl_type defined, referenced;
824
825   struct gfc_expr *format;
826
827   tree backend_decl;
828
829   locus where;
830 }
831 gfc_st_label;
832
833
834 /* gfc_interface()-- Interfaces are lists of symbols strung together.  */
835 typedef struct gfc_interface
836 {
837   struct gfc_symbol *sym;
838   locus where;
839   struct gfc_interface *next;
840 }
841 gfc_interface;
842
843 #define gfc_get_interface() gfc_getmem(sizeof(gfc_interface))
844
845
846 /* User operator nodes.  These are like stripped down symbols.  */
847 typedef struct
848 {
849   const char *name;
850
851   gfc_interface *operator;
852   struct gfc_namespace *ns;
853   gfc_access access;
854 }
855 gfc_user_op;
856
857 /* Symbol nodes.  These are important things.  They are what the
858    standard refers to as "entities".  The possibly multiple names that
859    refer to the same entity are accomplished by a binary tree of
860    symtree structures that is balanced by the red-black method-- more
861    than one symtree node can point to any given symbol.  */
862
863 typedef struct gfc_symbol
864 {
865   const char *name;     /* Primary name, before renaming */
866   const char *module;   /* Module this symbol came from */
867   locus declared_at;
868
869   gfc_typespec ts;
870   symbol_attribute attr;
871
872   /* The interface member points to the formal argument list if the
873      symbol is a function or subroutine name.  If the symbol is a
874      generic name, the generic member points to the list of
875      interfaces.  */
876
877   gfc_interface *generic;
878   gfc_access component_access;
879
880   gfc_formal_arglist *formal;
881   struct gfc_namespace *formal_ns;
882
883   struct gfc_expr *value;       /* Parameter/Initializer value */
884   gfc_array_spec *as;
885   struct gfc_symbol *result;    /* function result symbol */
886   gfc_component *components;    /* Derived type components */
887
888   /* Defined only for Cray pointees; points to their pointer.  */
889   struct gfc_symbol *cp_pointer;
890
891   struct gfc_symbol *common_next;       /* Links for COMMON syms */
892
893   /* This is in fact a gfc_common_head but it is only used for pointer
894      comparisons to check if symbols are in the same common block.  */
895   struct gfc_common_head* common_head;
896
897   /* Make sure setup code for dummy arguments is generated in the correct
898      order.  */
899   int dummy_order;
900
901   int entry_id;
902
903   gfc_namelist *namelist, *namelist_tail;
904
905   /* Change management fields.  Symbols that might be modified by the
906      current statement have the mark member nonzero and are kept in a
907      singly linked list through the tlink field.  Of these symbols,
908      symbols with old_symbol equal to NULL are symbols created within
909      the current statement.  Otherwise, old_symbol points to a copy of
910      the old symbol.  */
911
912   struct gfc_symbol *old_symbol, *tlink;
913   unsigned mark:1, new:1;
914   /* Nonzero if all equivalences associated with this symbol have been
915      processed.  */
916   unsigned equiv_built:1;
917   /* Set if this variable is used as an index name in a FORALL.  */
918   unsigned forall_index:1;
919   int refs;
920   struct gfc_namespace *ns;     /* namespace containing this symbol */
921
922   tree backend_decl;
923 }
924 gfc_symbol;
925
926
927 /* This structure is used to keep track of symbols in common blocks.  */
928
929 typedef struct gfc_common_head
930 {
931   locus where;
932   char use_assoc, saved, threadprivate;
933   char name[GFC_MAX_SYMBOL_LEN + 1];
934   struct gfc_symbol *head;
935 }
936 gfc_common_head;
937
938 #define gfc_get_common_head() gfc_getmem(sizeof(gfc_common_head))
939
940
941 /* A list of all the alternate entry points for a procedure.  */
942
943 typedef struct gfc_entry_list
944 {
945   /* The symbol for this entry point.  */
946   gfc_symbol *sym;
947   /* The zero-based id of this entry point.  */
948   int id;
949   /* The LABEL_EXPR marking this entry point.  */
950   tree label;
951   /* The nest item in the list.  */
952   struct gfc_entry_list *next;
953 }
954 gfc_entry_list;
955
956 #define gfc_get_entry_list() \
957   (gfc_entry_list *) gfc_getmem(sizeof(gfc_entry_list))
958
959 /* Within a namespace, symbols are pointed to by symtree nodes that
960    are linked together in a balanced binary tree.  There can be
961    several symtrees pointing to the same symbol node via USE
962    statements.  */
963
964 typedef struct gfc_symtree
965 {
966   BBT_HEADER (gfc_symtree);
967   const char *name;
968   int ambiguous;
969   union
970   {
971     gfc_symbol *sym;            /* Symbol associated with this node */
972     gfc_user_op *uop;
973     gfc_common_head *common;
974   }
975   n;
976
977 }
978 gfc_symtree;
979
980 /* A linked list of derived types in the namespace.  */
981 typedef struct gfc_dt_list
982 {
983   struct gfc_symbol *derived;
984   struct gfc_dt_list *next;
985 }
986 gfc_dt_list;
987
988 #define gfc_get_dt_list() gfc_getmem(sizeof(gfc_dt_list))
989
990   /* A list of all derived types.  */
991   extern gfc_dt_list *gfc_derived_types;
992
993 /* A namespace describes the contents of procedure, module or
994    interface block.  */
995 /* ??? Anything else use these?  */
996
997 typedef struct gfc_namespace
998 {
999   /* Tree containing all the symbols in this namespace.  */
1000   gfc_symtree *sym_root;
1001   /* Tree containing all the user-defined operators in the namespace.  */
1002   gfc_symtree *uop_root;
1003   /* Tree containing all the common blocks.  */
1004   gfc_symtree *common_root;
1005
1006   /* If set_flag[letter] is set, an implicit type has been set for letter.  */
1007   int set_flag[GFC_LETTERS];
1008   /* Keeps track of the implicit types associated with the letters.  */
1009   gfc_typespec default_type[GFC_LETTERS];
1010
1011   /* If this is a namespace of a procedure, this points to the procedure.  */
1012   struct gfc_symbol *proc_name;
1013   /* If this is the namespace of a unit which contains executable
1014      code, this points to it.  */
1015   struct gfc_code *code;
1016
1017   /* Points to the equivalences set up in this namespace.  */
1018   struct gfc_equiv *equiv;
1019
1020   /* Points to the equivalence groups produced by trans_common.  */
1021   struct gfc_equiv_list *equiv_lists;
1022
1023   gfc_interface *operator[GFC_INTRINSIC_OPS];
1024
1025   /* Points to the parent namespace, i.e. the namespace of a module or
1026      procedure in which the procedure belonging to this namespace is
1027      contained. The parent namespace points to this namespace either
1028      directly via CONTAINED, or indirectly via the chain built by
1029      SIBLING.  */
1030   struct gfc_namespace *parent;
1031   /* CONTAINED points to the first contained namespace. Sibling
1032      namespaces are chained via SIBLING.  */
1033   struct gfc_namespace  *contained, *sibling;
1034
1035   gfc_common_head blank_common;
1036   gfc_access default_access, operator_access[GFC_INTRINSIC_OPS];
1037
1038   gfc_st_label *st_labels;
1039   /* This list holds information about all the data initializers in
1040      this namespace.  */
1041   struct gfc_data *data;
1042
1043   gfc_charlen *cl_list;
1044
1045   int save_all, seen_save, seen_implicit_none;
1046
1047   /* Normally we don't need to refcount namespaces.  However when we read
1048      a module containing a function with multiple entry points, this
1049      will appear as several functions with the same formal namespace.  */
1050   int refs;
1051
1052   /* A list of all alternate entry points to this procedure (or NULL).  */
1053   gfc_entry_list *entries;
1054
1055   /* Set to 1 if namespace is a BLOCK DATA program unit.  */
1056   int is_block_data;
1057
1058   /* Set to 1 if namespace is an interface body with "IMPORT" used.  */
1059   int has_import_set;
1060 }
1061 gfc_namespace;
1062
1063 extern gfc_namespace *gfc_current_ns;
1064
1065 /* Global symbols are symbols of global scope. Currently we only use
1066    this to detect collisions already when parsing.
1067    TODO: Extend to verify procedure calls.  */
1068
1069 typedef struct gfc_gsymbol
1070 {
1071   BBT_HEADER(gfc_gsymbol);
1072
1073   const char *name;
1074   enum { GSYM_UNKNOWN=1, GSYM_PROGRAM, GSYM_FUNCTION, GSYM_SUBROUTINE,
1075         GSYM_MODULE, GSYM_COMMON, GSYM_BLOCK_DATA } type;
1076
1077   int defined, used;
1078   locus where;
1079 }
1080 gfc_gsymbol;
1081
1082 extern gfc_gsymbol *gfc_gsym_root;
1083
1084 /* Information on interfaces being built.  */
1085 typedef struct
1086 {
1087   interface_type type;
1088   gfc_symbol *sym;
1089   gfc_namespace *ns;
1090   gfc_user_op *uop;
1091   gfc_intrinsic_op op;
1092 }
1093 gfc_interface_info;
1094
1095 extern gfc_interface_info current_interface;
1096
1097
1098 /* Array reference.  */
1099 typedef struct gfc_array_ref
1100 {
1101   ar_type type;
1102   int dimen;                    /* # of components in the reference */
1103   locus where;
1104   gfc_array_spec *as;
1105
1106   locus c_where[GFC_MAX_DIMENSIONS];    /* All expressions can be NULL */
1107   struct gfc_expr *start[GFC_MAX_DIMENSIONS], *end[GFC_MAX_DIMENSIONS],
1108     *stride[GFC_MAX_DIMENSIONS];
1109
1110   enum
1111   { DIMEN_ELEMENT = 1, DIMEN_RANGE, DIMEN_VECTOR, DIMEN_UNKNOWN }
1112   dimen_type[GFC_MAX_DIMENSIONS];
1113
1114   struct gfc_expr *offset;
1115 }
1116 gfc_array_ref;
1117
1118 #define gfc_get_array_ref() gfc_getmem(sizeof(gfc_array_ref))
1119
1120
1121 /* Component reference nodes.  A variable is stored as an expression
1122    node that points to the base symbol.  After that, a singly linked
1123    list of component reference nodes gives the variable's complete
1124    resolution.  The array_ref component may be present and comes
1125    before the component component.  */
1126
1127 typedef enum
1128   { REF_ARRAY, REF_COMPONENT, REF_SUBSTRING }
1129 ref_type;
1130
1131 typedef struct gfc_ref
1132 {
1133   ref_type type;
1134
1135   union
1136   {
1137     struct gfc_array_ref ar;
1138
1139     struct
1140     {
1141       gfc_component *component;
1142       gfc_symbol *sym;
1143     }
1144     c;
1145
1146     struct
1147     {
1148       struct gfc_expr *start, *end;     /* Substring */
1149       gfc_charlen *length;
1150     }
1151     ss;
1152
1153   }
1154   u;
1155
1156   struct gfc_ref *next;
1157 }
1158 gfc_ref;
1159
1160 #define gfc_get_ref() gfc_getmem(sizeof(gfc_ref))
1161
1162
1163 /* Structures representing intrinsic symbols and their arguments lists.  */
1164 typedef struct gfc_intrinsic_arg
1165 {
1166   char name[GFC_MAX_SYMBOL_LEN + 1];
1167
1168   gfc_typespec ts;
1169   int optional;
1170   gfc_actual_arglist *actual;
1171
1172   struct gfc_intrinsic_arg *next;
1173
1174 }
1175 gfc_intrinsic_arg;
1176
1177
1178 /* Specifies the various kinds of check functions used to verify the
1179    argument lists of intrinsic functions. fX with X an integer refer
1180    to check functions of intrinsics with X arguments. f1m is used for
1181    the MAX and MIN intrinsics which can have an arbitrary number of
1182    arguments, f3ml is used for the MINLOC and MAXLOC intrinsics as
1183    these have special semantics.  */
1184
1185 typedef union
1186 {
1187   try (*f0)(void);
1188   try (*f1)(struct gfc_expr *);
1189   try (*f1m)(gfc_actual_arglist *);
1190   try (*f2)(struct gfc_expr *, struct gfc_expr *);
1191   try (*f3)(struct gfc_expr *, struct gfc_expr *, struct gfc_expr *);
1192   try (*f3ml)(gfc_actual_arglist *);
1193   try (*f3red)(gfc_actual_arglist *);
1194   try (*f4)(struct gfc_expr *, struct gfc_expr *, struct gfc_expr *,
1195             struct gfc_expr *);
1196   try (*f5)(struct gfc_expr *, struct gfc_expr *, struct gfc_expr *,
1197             struct gfc_expr *, struct gfc_expr *);
1198 }
1199 gfc_check_f;
1200
1201 /* Like gfc_check_f, these specify the type of the simplification
1202    function associated with an intrinsic. The fX are just like in
1203    gfc_check_f. cc is used for type conversion functions.  */
1204
1205 typedef union
1206 {
1207   struct gfc_expr *(*f0)(void);
1208   struct gfc_expr *(*f1)(struct gfc_expr *);
1209   struct gfc_expr *(*f2)(struct gfc_expr *, struct gfc_expr *);
1210   struct gfc_expr *(*f3)(struct gfc_expr *, struct gfc_expr *,
1211                          struct gfc_expr *);
1212   struct gfc_expr *(*f4)(struct gfc_expr *, struct gfc_expr *,
1213                          struct gfc_expr *, struct gfc_expr *);
1214   struct gfc_expr *(*f5)(struct gfc_expr *, struct gfc_expr *,
1215                          struct gfc_expr *, struct gfc_expr *,
1216                          struct gfc_expr *);
1217   struct gfc_expr *(*cc)(struct gfc_expr *, bt, int);
1218 }
1219 gfc_simplify_f;
1220
1221 /* Again like gfc_check_f, these specify the type of the resolution
1222    function associated with an intrinsic. The fX are just like in
1223    gfc_check_f. f1m is used for MIN and MAX, s1 is used for abort().
1224    */
1225
1226 typedef union
1227 {
1228   void (*f0)(struct gfc_expr *);
1229   void (*f1)(struct gfc_expr *, struct gfc_expr *);
1230   void (*f1m)(struct gfc_expr *, struct gfc_actual_arglist *);
1231   void (*f2)(struct gfc_expr *, struct gfc_expr *, struct gfc_expr *);
1232   void (*f3)(struct gfc_expr *, struct gfc_expr *, struct gfc_expr *,
1233              struct gfc_expr *);
1234   void (*f4)(struct gfc_expr *, struct gfc_expr *, struct gfc_expr *,
1235              struct gfc_expr *, struct gfc_expr *);
1236   void (*f5)(struct gfc_expr *, struct gfc_expr *, struct gfc_expr *,
1237              struct gfc_expr *, struct gfc_expr *, struct gfc_expr *);
1238   void (*s1)(struct gfc_code *);
1239 }
1240 gfc_resolve_f;
1241
1242
1243 typedef struct gfc_intrinsic_sym
1244 {
1245   const char *name, *lib_name;
1246   gfc_intrinsic_arg *formal;
1247   gfc_typespec ts;
1248   int elemental, pure, generic, specific, actual_ok, standard, noreturn;
1249
1250   gfc_simplify_f simplify;
1251   gfc_check_f check;
1252   gfc_resolve_f resolve;
1253   struct gfc_intrinsic_sym *specific_head, *next;
1254   gfc_generic_isym_id generic_id;
1255
1256 }
1257 gfc_intrinsic_sym;
1258
1259
1260 /* Expression nodes.  The expression node types deserve explanations,
1261    since the last couple can be easily misconstrued:
1262
1263    EXPR_OP         Operator node pointing to one or two other nodes
1264    EXPR_FUNCTION   Function call, symbol points to function's name
1265    EXPR_CONSTANT   A scalar constant: Logical, String, Real, Int or Complex
1266    EXPR_VARIABLE   An Lvalue with a root symbol and possible reference list
1267                    which expresses structure, array and substring refs.
1268    EXPR_NULL       The NULL pointer value (which also has a basic type).
1269    EXPR_SUBSTRING  A substring of a constant string
1270    EXPR_STRUCTURE  A structure constructor
1271    EXPR_ARRAY      An array constructor.  */
1272
1273 #include <gmp.h>
1274 #include <mpfr.h>
1275 #define GFC_RND_MODE GMP_RNDN
1276
1277 typedef struct gfc_expr
1278 {
1279   expr_t expr_type;
1280
1281   gfc_typespec ts;      /* These two refer to the overall expression */
1282
1283   int rank;
1284   mpz_t *shape;         /* Can be NULL if shape is unknown at compile time */
1285
1286   /* Nonnull for functions and structure constructors */
1287   gfc_symtree *symtree;
1288
1289   gfc_ref *ref;
1290
1291   locus where;
1292
1293   /* True if it is converted from Hollerith constant.  */
1294   unsigned int from_H : 1;
1295   /* True if the expression is a call to a function that returns an array,
1296      and if we have decided not to allocate temporary data for that array.  */
1297   unsigned int inline_noncopying_intrinsic : 1;
1298   /* Used to quickly find a given constructor by it's offset.  */
1299   splay_tree con_by_offset;
1300
1301   union
1302   {
1303     int logical;
1304     mpz_t integer;
1305
1306     mpfr_t real;
1307
1308     struct
1309     {
1310       mpfr_t r, i;
1311     }
1312     complex;
1313
1314     struct
1315     {
1316       gfc_intrinsic_op operator;
1317       gfc_user_op *uop;
1318       struct gfc_expr *op1, *op2;
1319     }
1320     op;
1321
1322     struct
1323     {
1324       gfc_actual_arglist *actual;
1325       const char *name; /* Points to the ultimate name of the function */
1326       gfc_intrinsic_sym *isym;
1327       gfc_symbol *esym;
1328     }
1329     function;
1330
1331     struct
1332     {
1333       int length;
1334       char *string;
1335     }
1336     character;
1337
1338     struct gfc_constructor *constructor;
1339   }
1340   value;
1341
1342 }
1343 gfc_expr;
1344
1345
1346 #define gfc_get_shape(rank) ((mpz_t *) gfc_getmem((rank)*sizeof(mpz_t)))
1347
1348 /* Structures for information associated with different kinds of
1349    numbers.  The first set of integer parameters define all there is
1350    to know about a particular kind.  The rest of the elements are
1351    computed from the first elements.  */
1352
1353 typedef struct
1354 {
1355   /* Values really representable by the target.  */
1356   mpz_t huge, pedantic_min_int, min_int;
1357
1358   int kind, radix, digits, bit_size, range;
1359
1360   /* True if the C type of the given name maps to this precision.
1361      Note that more than one bit can be set.  */
1362   unsigned int c_char : 1;
1363   unsigned int c_short : 1;
1364   unsigned int c_int : 1;
1365   unsigned int c_long : 1;
1366   unsigned int c_long_long : 1;
1367 }
1368 gfc_integer_info;
1369
1370 extern gfc_integer_info gfc_integer_kinds[];
1371
1372
1373 typedef struct
1374 {
1375   int kind, bit_size;
1376
1377   /* True if the C++ type bool, C99 type _Bool, maps to this precision.  */
1378   unsigned int c_bool : 1;
1379 }
1380 gfc_logical_info;
1381
1382 extern gfc_logical_info gfc_logical_kinds[];
1383
1384
1385 typedef struct
1386 {
1387   mpfr_t epsilon, huge, tiny, subnormal;
1388   int kind, radix, digits, min_exponent, max_exponent;
1389   int range, precision;
1390
1391   /* The precision of the type as reported by GET_MODE_PRECISION.  */
1392   int mode_precision;
1393
1394   /* True if the C type of the given name maps to this precision.
1395      Note that more than one bit can be set.  */
1396   unsigned int c_float : 1;
1397   unsigned int c_double : 1;
1398   unsigned int c_long_double : 1;
1399 }
1400 gfc_real_info;
1401
1402 extern gfc_real_info gfc_real_kinds[];
1403
1404
1405 /* Equivalence structures.  Equivalent lvalues are linked along the
1406    *eq pointer, equivalence sets are strung along the *next node.  */
1407 typedef struct gfc_equiv
1408 {
1409   struct gfc_equiv *next, *eq;
1410   gfc_expr *expr;
1411   const char *module;
1412   int used;
1413 }
1414 gfc_equiv;
1415
1416 #define gfc_get_equiv() gfc_getmem(sizeof(gfc_equiv))
1417
1418 /* Holds a single equivalence member after processing.  */
1419 typedef struct gfc_equiv_info
1420 {
1421   gfc_symbol *sym;
1422   HOST_WIDE_INT offset;
1423   HOST_WIDE_INT length;
1424   struct gfc_equiv_info *next;
1425 } gfc_equiv_info;
1426
1427 /* Holds equivalence groups, after they have been processed.  */
1428 typedef struct gfc_equiv_list
1429 {
1430   gfc_equiv_info *equiv;
1431   struct gfc_equiv_list *next;
1432 } gfc_equiv_list;
1433
1434 /* gfc_case stores the selector list of a case statement.  The *low
1435    and *high pointers can point to the same expression in the case of
1436    a single value.  If *high is NULL, the selection is from *low
1437    upwards, if *low is NULL the selection is *high downwards.
1438
1439    This structure has separate fields to allow single and double linked
1440    lists of CASEs at the same time.  The singe linked list along the NEXT
1441    field is a list of cases for a single CASE label.  The double linked
1442    list along the LEFT/RIGHT fields is used to detect overlap and to
1443    build a table of the cases for SELECT constructs with a CHARACTER
1444    case expression.  */
1445
1446 typedef struct gfc_case
1447 {
1448   /* Where we saw this case.  */
1449   locus where;
1450   int n;
1451
1452   /* Case range values.  If (low == high), it's a single value.  If one of
1453      the labels is NULL, it's an unbounded case.  If both are NULL, this
1454      represents the default case.  */
1455   gfc_expr *low, *high;
1456
1457   /* Next case label in the list of cases for a single CASE label.  */
1458   struct gfc_case *next;
1459
1460   /* Used for detecting overlap, and for code generation.  */
1461   struct gfc_case *left, *right;
1462
1463   /* True if this case label can never be matched.  */
1464   int unreachable;
1465 }
1466 gfc_case;
1467
1468 #define gfc_get_case() gfc_getmem(sizeof(gfc_case))
1469
1470
1471 typedef struct
1472 {
1473   gfc_expr *var, *start, *end, *step;
1474 }
1475 gfc_iterator;
1476
1477 #define gfc_get_iterator() gfc_getmem(sizeof(gfc_iterator))
1478
1479
1480 /* Allocation structure for ALLOCATE, DEALLOCATE and NULLIFY statements.  */
1481
1482 typedef struct gfc_alloc
1483 {
1484   gfc_expr *expr;
1485   struct gfc_alloc *next;
1486 }
1487 gfc_alloc;
1488
1489 #define gfc_get_alloc() gfc_getmem(sizeof(gfc_alloc))
1490
1491
1492 typedef struct
1493 {
1494   gfc_expr *unit, *file, *status, *access, *form, *recl,
1495     *blank, *position, *action, *delim, *pad, *iostat, *iomsg, *convert;
1496   gfc_st_label *err;
1497 }
1498 gfc_open;
1499
1500
1501 typedef struct
1502 {
1503   gfc_expr *unit, *status, *iostat, *iomsg;
1504   gfc_st_label *err;
1505 }
1506 gfc_close;
1507
1508
1509 typedef struct
1510 {
1511   gfc_expr *unit, *iostat, *iomsg;
1512   gfc_st_label *err;
1513 }
1514 gfc_filepos;
1515
1516
1517 typedef struct
1518 {
1519   gfc_expr *unit, *file, *iostat, *exist, *opened, *number, *named,
1520     *name, *access, *sequential, *direct, *form, *formatted,
1521     *unformatted, *recl, *nextrec, *blank, *position, *action, *read,
1522     *write, *readwrite, *delim, *pad, *iolength, *iomsg, *convert, *strm_pos;
1523
1524   gfc_st_label *err;
1525
1526 }
1527 gfc_inquire;
1528
1529
1530 typedef struct
1531 {
1532   gfc_expr *io_unit, *format_expr, *rec, *advance, *iostat, *size, *iomsg;
1533
1534   gfc_symbol *namelist;
1535   /* A format_label of `format_asterisk' indicates the "*" format */
1536   gfc_st_label *format_label;
1537   gfc_st_label *err, *end, *eor;
1538
1539   locus eor_where, end_where, err_where;
1540 }
1541 gfc_dt;
1542
1543
1544 typedef struct gfc_forall_iterator
1545 {
1546   gfc_expr *var, *start, *end, *stride;
1547   struct gfc_forall_iterator *next;
1548 }
1549 gfc_forall_iterator;
1550
1551
1552 /* Executable statements that fill gfc_code structures.  */
1553 typedef enum
1554 {
1555   EXEC_NOP = 1, EXEC_ASSIGN, EXEC_LABEL_ASSIGN, EXEC_POINTER_ASSIGN,
1556   EXEC_GOTO, EXEC_CALL, EXEC_ASSIGN_CALL, EXEC_RETURN, EXEC_ENTRY,
1557   EXEC_PAUSE, EXEC_STOP, EXEC_CONTINUE, EXEC_INIT_ASSIGN,
1558   EXEC_IF, EXEC_ARITHMETIC_IF, EXEC_DO, EXEC_DO_WHILE, EXEC_SELECT,
1559   EXEC_FORALL, EXEC_WHERE, EXEC_CYCLE, EXEC_EXIT,
1560   EXEC_ALLOCATE, EXEC_DEALLOCATE,
1561   EXEC_OPEN, EXEC_CLOSE,
1562   EXEC_READ, EXEC_WRITE, EXEC_IOLENGTH, EXEC_TRANSFER, EXEC_DT_END,
1563   EXEC_BACKSPACE, EXEC_ENDFILE, EXEC_INQUIRE, EXEC_REWIND, EXEC_FLUSH,
1564   EXEC_OMP_CRITICAL, EXEC_OMP_DO, EXEC_OMP_FLUSH, EXEC_OMP_MASTER,
1565   EXEC_OMP_ORDERED, EXEC_OMP_PARALLEL, EXEC_OMP_PARALLEL_DO,
1566   EXEC_OMP_PARALLEL_SECTIONS, EXEC_OMP_PARALLEL_WORKSHARE,
1567   EXEC_OMP_SECTIONS, EXEC_OMP_SINGLE, EXEC_OMP_WORKSHARE,
1568   EXEC_OMP_ATOMIC, EXEC_OMP_BARRIER, EXEC_OMP_END_NOWAIT,
1569   EXEC_OMP_END_SINGLE
1570 }
1571 gfc_exec_op;
1572
1573 typedef struct gfc_code
1574 {
1575   gfc_exec_op op;
1576
1577   struct gfc_code *block, *next;
1578   locus loc;
1579
1580   gfc_st_label *here, *label, *label2, *label3;
1581   gfc_symtree *symtree;
1582   gfc_expr *expr, *expr2;
1583   /* A name isn't sufficient to identify a subroutine, we need the actual
1584      symbol for the interface definition.
1585   const char *sub_name;  */
1586   gfc_symbol *resolved_sym;
1587
1588   union
1589   {
1590     gfc_actual_arglist *actual;
1591     gfc_case *case_list;
1592     gfc_iterator *iterator;
1593     gfc_alloc *alloc_list;
1594     gfc_open *open;
1595     gfc_close *close;
1596     gfc_filepos *filepos;
1597     gfc_inquire *inquire;
1598     gfc_dt *dt;
1599     gfc_forall_iterator *forall_iterator;
1600     struct gfc_code *whichloop;
1601     int stop_code;
1602     gfc_entry_list *entry;
1603     gfc_omp_clauses *omp_clauses;
1604     const char *omp_name;
1605     gfc_namelist *omp_namelist;
1606     bool omp_bool;
1607   }
1608   ext;          /* Points to additional structures required by statement */
1609
1610   /* Backend_decl is used for cycle and break labels in do loops, and
1611      probably for other constructs as well, once we translate them.  */
1612   tree backend_decl;
1613 }
1614 gfc_code;
1615
1616
1617 /* Storage for DATA statements.  */
1618 typedef struct gfc_data_variable
1619 {
1620   gfc_expr *expr;
1621   gfc_iterator iter;
1622   struct gfc_data_variable *list, *next;
1623 }
1624 gfc_data_variable;
1625
1626
1627 typedef struct gfc_data_value
1628 {
1629   unsigned int repeat;
1630   gfc_expr *expr;
1631   struct gfc_data_value *next;
1632 }
1633 gfc_data_value;
1634
1635
1636 typedef struct gfc_data
1637 {
1638   gfc_data_variable *var;
1639   gfc_data_value *value;
1640   locus where;
1641
1642   struct gfc_data *next;
1643 }
1644 gfc_data;
1645
1646 #define gfc_get_data_variable() gfc_getmem(sizeof(gfc_data_variable))
1647 #define gfc_get_data_value() gfc_getmem(sizeof(gfc_data_value))
1648 #define gfc_get_data() gfc_getmem(sizeof(gfc_data))
1649
1650
1651 /* Structure for holding compile options */
1652 typedef struct
1653 {
1654   char *module_dir;
1655   gfc_source_form source_form;
1656   /* Maximum line lengths in fixed- and free-form source, respectively.
1657      When fixed_line_length or free_line_length are 0, the whole line is used,
1658      regardless of length.
1659
1660      If the user requests a fixed_line_length <7 then gfc_init_options()
1661      emits a fatal error.  */
1662   int fixed_line_length;
1663   int free_line_length;
1664   /* Maximum number of continuation lines in fixed- and free-form source,
1665      respectively.  */
1666   int max_continue_fixed;
1667   int max_continue_free;
1668   int max_identifier_length;
1669   int verbose;
1670
1671   int warn_aliasing;
1672   int warn_ampersand;
1673   int warn_conversion;
1674   int warn_implicit_interface;
1675   int warn_line_truncation;
1676   int warn_surprising;
1677   int warn_tabs;
1678   int warn_underflow;
1679   int warn_character_truncation;
1680   int max_errors;
1681
1682   int flag_all_intrinsics;
1683   int flag_default_double;
1684   int flag_default_integer;
1685   int flag_default_real;
1686   int flag_dollar_ok;
1687   int flag_underscoring;
1688   int flag_second_underscore;
1689   int flag_implicit_none;
1690   int flag_max_stack_var_size;
1691   int flag_range_check;
1692   int flag_pack_derived;
1693   int flag_repack_arrays;
1694   int flag_preprocessed;
1695   int flag_f2c;
1696   int flag_automatic;
1697   int flag_backslash;
1698   int flag_backtrace;
1699   int flag_allow_leading_underscore;
1700   int flag_dump_core;
1701   int flag_external_blas;
1702   int blas_matmul_limit;
1703   int flag_cray_pointer;
1704   int flag_d_lines;
1705   int flag_openmp;
1706
1707   int fpe;
1708
1709   int warn_std;
1710   int allow_std;
1711   int warn_nonstd_intrinsics;
1712   int fshort_enums;
1713   int convert;
1714   int record_marker;
1715   int max_subrecord_length;
1716 }
1717 gfc_option_t;
1718
1719 extern gfc_option_t gfc_option;
1720
1721 /* Constructor nodes for array and structure constructors.  */
1722 typedef struct gfc_constructor
1723 {
1724   gfc_expr *expr;
1725   gfc_iterator *iterator;
1726   locus where;
1727   struct gfc_constructor *next;
1728   struct
1729   {
1730     mpz_t offset; /* Record the offset of array element which appears in
1731                      data statement like "data a(5)/4/".  */
1732     gfc_component *component; /* Record the component being initialized.  */
1733   }
1734   n;
1735   mpz_t repeat; /* Record the repeat number of initial values in data
1736                  statement like "data a/5*10/".  */
1737 }
1738 gfc_constructor;
1739
1740
1741 typedef struct iterator_stack
1742 {
1743   gfc_symtree *variable;
1744   mpz_t value;
1745   struct iterator_stack *prev;
1746 }
1747 iterator_stack;
1748 extern iterator_stack *iter_stack;
1749
1750 /************************ Function prototypes *************************/
1751
1752 /* data.c  */
1753 void gfc_formalize_init_value (gfc_symbol *);
1754 void gfc_get_section_index (gfc_array_ref *, mpz_t *, mpz_t *);
1755 void gfc_assign_data_value (gfc_expr *, gfc_expr *, mpz_t);
1756 void gfc_assign_data_value_range (gfc_expr *, gfc_expr *, mpz_t, mpz_t);
1757 void gfc_advance_section (mpz_t *, gfc_array_ref *, mpz_t *);
1758
1759 /* decl.c */
1760 bool gfc_in_match_data (void);
1761 void gfc_set_in_match_data (bool);
1762
1763 /* scanner.c */
1764 void gfc_scanner_done_1 (void);
1765 void gfc_scanner_init_1 (void);
1766
1767 void gfc_add_include_path (const char *, bool);
1768 void gfc_add_intrinsic_modules_path (const char *);
1769 void gfc_release_include_path (void);
1770 FILE *gfc_open_included_file (const char *, bool, bool);
1771 FILE *gfc_open_intrinsic_module (const char *);
1772
1773 int gfc_at_end (void);
1774 int gfc_at_eof (void);
1775 int gfc_at_bol (void);
1776 int gfc_at_eol (void);
1777 void gfc_advance_line (void);
1778 int gfc_check_include (void);
1779
1780 void gfc_skip_comments (void);
1781 int gfc_next_char_literal (int);
1782 int gfc_next_char (void);
1783 int gfc_peek_char (void);
1784 void gfc_error_recovery (void);
1785 void gfc_gobble_whitespace (void);
1786 try gfc_new_file (void);
1787 const char * gfc_read_orig_filename (const char *, const char **);
1788
1789 extern gfc_source_form gfc_current_form;
1790 extern const char *gfc_source_file;
1791 extern locus gfc_current_locus;
1792
1793 /* misc.c */
1794 void *gfc_getmem (size_t) ATTRIBUTE_MALLOC;
1795 void gfc_free (void *);
1796 int gfc_terminal_width(void);
1797 void gfc_clear_ts (gfc_typespec *);
1798 FILE *gfc_open_file (const char *);
1799 const char *gfc_basic_typename (bt);
1800 const char *gfc_typename (gfc_typespec *);
1801
1802 #define gfc_op2string(OP) (OP == INTRINSIC_ASSIGN ? \
1803                            "=" : gfc_code2string (intrinsic_operators, OP))
1804
1805 const char *gfc_code2string (const mstring *, int);
1806 int gfc_string2code (const mstring *, const char *);
1807 const char *gfc_intent_string (sym_intent);
1808
1809 void gfc_init_1 (void);
1810 void gfc_init_2 (void);
1811 void gfc_done_1 (void);
1812 void gfc_done_2 (void);
1813
1814 /* options.c */
1815 unsigned int gfc_init_options (unsigned int, const char **);
1816 int gfc_handle_option (size_t, const char *, int);
1817 bool gfc_post_options (const char **);
1818
1819 /* iresolve.c */
1820 const char * gfc_get_string (const char *, ...) ATTRIBUTE_PRINTF_1;
1821
1822 /* error.c */
1823
1824 typedef struct gfc_error_buf
1825 {
1826   int flag;
1827   size_t allocated, index;
1828   char *message;
1829 } gfc_error_buf;
1830
1831 void gfc_error_init_1 (void);
1832 void gfc_buffer_error (int);
1833
1834 void gfc_warning (const char *, ...) ATTRIBUTE_GCC_GFC(1,2);
1835 void gfc_warning_now (const char *, ...) ATTRIBUTE_GCC_GFC(1,2);
1836 void gfc_clear_warning (void);
1837 void gfc_warning_check (void);
1838
1839 void gfc_error (const char *, ...) ATTRIBUTE_GCC_GFC(1,2);
1840 void gfc_error_now (const char *, ...) ATTRIBUTE_GCC_GFC(1,2);
1841 void gfc_fatal_error (const char *, ...) ATTRIBUTE_NORETURN ATTRIBUTE_GCC_GFC(1,2);
1842 void gfc_internal_error (const char *, ...) ATTRIBUTE_NORETURN ATTRIBUTE_GCC_GFC(1,2);
1843 void gfc_clear_error (void);
1844 int gfc_error_check (void);
1845 int gfc_error_flag_test (void);
1846
1847 notification gfc_notification_std (int);
1848 try gfc_notify_std (int, const char *, ...) ATTRIBUTE_GCC_GFC(2,3);
1849
1850 /* A general purpose syntax error.  */
1851 #define gfc_syntax_error(ST)    \
1852   gfc_error ("Syntax error in %s statement at %C", gfc_ascii_statement (ST));
1853
1854 void gfc_push_error (gfc_error_buf *);
1855 void gfc_pop_error (gfc_error_buf *);
1856 void gfc_free_error (gfc_error_buf *);
1857
1858 void gfc_status (const char *, ...) ATTRIBUTE_PRINTF_1;
1859 void gfc_status_char (char);
1860
1861 void gfc_get_errors (int *, int *);
1862
1863 /* arith.c */
1864 void gfc_arith_init_1 (void);
1865 void gfc_arith_done_1 (void);
1866 gfc_expr *gfc_enum_initializer (gfc_expr *, locus);
1867 arith gfc_check_integer_range (mpz_t p, int kind);
1868
1869 /* trans-types.c */
1870 int gfc_validate_kind (bt, int, bool);
1871 extern int gfc_index_integer_kind;
1872 extern int gfc_default_integer_kind;
1873 extern int gfc_max_integer_kind;
1874 extern int gfc_default_real_kind;
1875 extern int gfc_default_double_kind;
1876 extern int gfc_default_character_kind;
1877 extern int gfc_default_logical_kind;
1878 extern int gfc_default_complex_kind;
1879 extern int gfc_c_int_kind;
1880 extern int gfc_intio_kind;
1881 extern int gfc_charlen_int_kind;
1882 extern int gfc_numeric_storage_size;
1883 extern int gfc_character_storage_size;
1884
1885 /* symbol.c */
1886 void gfc_clear_new_implicit (void);
1887 try gfc_add_new_implicit_range (int, int);
1888 try gfc_merge_new_implicit (gfc_typespec *);
1889 void gfc_set_implicit_none (void);
1890 void gfc_check_function_type (gfc_namespace *);
1891
1892 gfc_typespec *gfc_get_default_type (gfc_symbol *, gfc_namespace *);
1893 try gfc_set_default_type (gfc_symbol *, int, gfc_namespace *);
1894
1895 void gfc_set_component_attr (gfc_component *, symbol_attribute *);
1896 void gfc_get_component_attr (symbol_attribute *, gfc_component *);
1897
1898 void gfc_set_sym_referenced (gfc_symbol * sym);
1899
1900 try gfc_add_attribute (symbol_attribute *, locus *);
1901 try gfc_add_allocatable (symbol_attribute *, locus *);
1902 try gfc_add_dimension (symbol_attribute *, const char *, locus *);
1903 try gfc_add_external (symbol_attribute *, locus *);
1904 try gfc_add_intrinsic (symbol_attribute *, locus *);
1905 try gfc_add_optional (symbol_attribute *, locus *);
1906 try gfc_add_pointer (symbol_attribute *, locus *);
1907 try gfc_add_cray_pointer (symbol_attribute *, locus *);
1908 try gfc_add_cray_pointee (symbol_attribute *, locus *);
1909 try gfc_mod_pointee_as (gfc_array_spec *as);
1910 try gfc_add_protected (symbol_attribute *, const char *, locus *);
1911 try gfc_add_result (symbol_attribute *, const char *, locus *);
1912 try gfc_add_save (symbol_attribute *, const char *, locus *);
1913 try gfc_add_threadprivate (symbol_attribute *, const char *, locus *);
1914 try gfc_add_saved_common (symbol_attribute *, locus *);
1915 try gfc_add_target (symbol_attribute *, locus *);
1916 try gfc_add_dummy (symbol_attribute *, const char *, locus *);
1917 try gfc_add_generic (symbol_attribute *, const char *, locus *);
1918 try gfc_add_common (symbol_attribute *, locus *);
1919 try gfc_add_in_common (symbol_attribute *, const char *, locus *);
1920 try gfc_add_in_equivalence (symbol_attribute *, const char *, locus *);
1921 try gfc_add_data (symbol_attribute *, const char *, locus *);
1922 try gfc_add_in_namelist (symbol_attribute *, const char *, locus *);
1923 try gfc_add_sequence (symbol_attribute *, const char *, locus *);
1924 try gfc_add_elemental (symbol_attribute *, locus *);
1925 try gfc_add_pure (symbol_attribute *, locus *);
1926 try gfc_add_recursive (symbol_attribute *, locus *);
1927 try gfc_add_function (symbol_attribute *, const char *, locus *);
1928 try gfc_add_subroutine (symbol_attribute *, const char *, locus *);
1929 try gfc_add_value (symbol_attribute *, const char *, locus *);
1930 try gfc_add_volatile (symbol_attribute *, const char *, locus *);
1931
1932 try gfc_add_access (symbol_attribute *, gfc_access, const char *, locus *);
1933 try gfc_add_flavor (symbol_attribute *, sym_flavor, const char *, locus *);
1934 try gfc_add_entry (symbol_attribute *, const char *, locus *);
1935 try gfc_add_procedure (symbol_attribute *, procedure_type,
1936                        const char *, locus *);
1937 try gfc_add_intent (symbol_attribute *, sym_intent, locus *);
1938 try gfc_add_explicit_interface (gfc_symbol *, ifsrc,
1939                                 gfc_formal_arglist *, locus *);
1940 try gfc_add_type (gfc_symbol *, gfc_typespec *, locus *);
1941
1942 void gfc_clear_attr (symbol_attribute *);
1943 try gfc_missing_attr (symbol_attribute *, locus *);
1944 try gfc_copy_attr (symbol_attribute *, symbol_attribute *, locus *);
1945
1946 try gfc_add_component (gfc_symbol *, const char *, gfc_component **);
1947 gfc_symbol *gfc_use_derived (gfc_symbol *);
1948 gfc_symtree *gfc_use_derived_tree (gfc_symtree *);
1949 gfc_component *gfc_find_component (gfc_symbol *, const char *);
1950
1951 gfc_st_label *gfc_get_st_label (int);
1952 void gfc_free_st_label (gfc_st_label *);
1953 void gfc_define_st_label (gfc_st_label *, gfc_sl_type, locus *);
1954 try gfc_reference_st_label (gfc_st_label *, gfc_sl_type);
1955
1956 gfc_namespace *gfc_get_namespace (gfc_namespace *, int);
1957 gfc_symtree *gfc_new_symtree (gfc_symtree **, const char *);
1958 gfc_symtree *gfc_find_symtree (gfc_symtree *, const char *);
1959 gfc_user_op *gfc_get_uop (const char *);
1960 gfc_user_op *gfc_find_uop (const char *, gfc_namespace *);
1961 void gfc_free_symbol (gfc_symbol *);
1962 gfc_symbol *gfc_new_symbol (const char *, gfc_namespace *);
1963 int gfc_find_symbol (const char *, gfc_namespace *, int, gfc_symbol **);
1964 int gfc_find_sym_tree (const char *, gfc_namespace *, int, gfc_symtree **);
1965 int gfc_get_symbol (const char *, gfc_namespace *, gfc_symbol **);
1966 int gfc_get_sym_tree (const char *, gfc_namespace *, gfc_symtree **);
1967 int gfc_get_ha_symbol (const char *, gfc_symbol **);
1968 int gfc_get_ha_sym_tree (const char *, gfc_symtree **);
1969
1970 int gfc_symbols_could_alias (gfc_symbol *, gfc_symbol *);
1971
1972 void gfc_undo_symbols (void);
1973 void gfc_commit_symbols (void);
1974 void gfc_commit_symbol (gfc_symbol * sym);
1975 void gfc_free_namespace (gfc_namespace *);
1976
1977 void gfc_symbol_init_2 (void);
1978 void gfc_symbol_done_2 (void);
1979
1980 void gfc_traverse_symtree (gfc_symtree *, void (*)(gfc_symtree *));
1981 void gfc_traverse_ns (gfc_namespace *, void (*)(gfc_symbol *));
1982 void gfc_traverse_user_op (gfc_namespace *, void (*)(gfc_user_op *));
1983 void gfc_save_all (gfc_namespace *);
1984
1985 void gfc_symbol_state (void);
1986
1987 gfc_gsymbol *gfc_get_gsymbol (const char *);
1988 gfc_gsymbol *gfc_find_gsymbol (gfc_gsymbol *, const char *);
1989
1990 /* intrinsic.c */
1991 extern int gfc_init_expr;
1992
1993 /* Given a symbol that we have decided is intrinsic, mark it as such
1994    by placing it into a special module that is otherwise impossible to
1995    read or write.  */
1996
1997 #define gfc_intrinsic_symbol(SYM) SYM->module = gfc_get_string ("(intrinsic)")
1998
1999 void gfc_intrinsic_init_1 (void);
2000 void gfc_intrinsic_done_1 (void);
2001
2002 char gfc_type_letter (bt);
2003 gfc_symbol * gfc_get_intrinsic_sub_symbol (const char *);
2004 try gfc_convert_type (gfc_expr *, gfc_typespec *, int);
2005 try gfc_convert_type_warn (gfc_expr *, gfc_typespec *, int, int);
2006 int gfc_generic_intrinsic (const char *);
2007 int gfc_specific_intrinsic (const char *);
2008 int gfc_intrinsic_name (const char *, int);
2009 int gfc_intrinsic_actual_ok (const char *, const bool);
2010 gfc_intrinsic_sym *gfc_find_function (const char *);
2011
2012 match gfc_intrinsic_func_interface (gfc_expr *, int);
2013 match gfc_intrinsic_sub_interface (gfc_code *, int);
2014
2015 /* match.c -- FIXME */
2016 void gfc_free_iterator (gfc_iterator *, int);
2017 void gfc_free_forall_iterator (gfc_forall_iterator *);
2018 void gfc_free_alloc_list (gfc_alloc *);
2019 void gfc_free_namelist (gfc_namelist *);
2020 void gfc_free_equiv (gfc_equiv *);
2021 void gfc_free_data (gfc_data *);
2022 void gfc_free_case_list (gfc_case *);
2023
2024 /* matchexp.c -- FIXME too?  */
2025 gfc_expr *gfc_get_parentheses (gfc_expr *);
2026
2027 /* openmp.c */
2028 void gfc_free_omp_clauses (gfc_omp_clauses *);
2029 void gfc_resolve_omp_directive (gfc_code *, gfc_namespace *);
2030 void gfc_resolve_do_iterator (gfc_code *, gfc_symbol *);
2031 void gfc_resolve_omp_parallel_blocks (gfc_code *, gfc_namespace *);
2032 void gfc_resolve_omp_do_blocks (gfc_code *, gfc_namespace *);
2033
2034 /* expr.c */
2035 void gfc_free_actual_arglist (gfc_actual_arglist *);
2036 gfc_actual_arglist *gfc_copy_actual_arglist (gfc_actual_arglist *);
2037 const char *gfc_extract_int (gfc_expr *, int *);
2038 gfc_expr *gfc_expr_to_initialize (gfc_expr *);
2039
2040 gfc_expr *gfc_build_conversion (gfc_expr *);
2041 void gfc_free_ref_list (gfc_ref *);
2042 void gfc_type_convert_binary (gfc_expr *);
2043 int gfc_is_constant_expr (gfc_expr *);
2044 try gfc_simplify_expr (gfc_expr *, int);
2045 int gfc_has_vector_index (gfc_expr *);
2046
2047 gfc_expr *gfc_get_expr (void);
2048 void gfc_free_expr (gfc_expr *);
2049 void gfc_replace_expr (gfc_expr *, gfc_expr *);
2050 gfc_expr *gfc_int_expr (int);
2051 gfc_expr *gfc_logical_expr (int, locus *);
2052 mpz_t *gfc_copy_shape (mpz_t *, int);
2053 mpz_t *gfc_copy_shape_excluding (mpz_t *, int, gfc_expr *);
2054 gfc_expr *gfc_copy_expr (gfc_expr *);
2055
2056 try gfc_specification_expr (gfc_expr *);
2057
2058 int gfc_numeric_ts (gfc_typespec *);
2059 int gfc_kind_max (gfc_expr *, gfc_expr *);
2060
2061 try gfc_check_conformance (const char *, gfc_expr *, gfc_expr *);
2062 try gfc_check_assign (gfc_expr *, gfc_expr *, int);
2063 try gfc_check_pointer_assign (gfc_expr *, gfc_expr *);
2064 try gfc_check_assign_symbol (gfc_symbol *, gfc_expr *);
2065
2066 gfc_expr *gfc_default_initializer (gfc_typespec *);
2067 gfc_expr *gfc_get_variable_expr (gfc_symtree *);
2068
2069 void gfc_expr_set_symbols_referenced (gfc_expr * expr);
2070
2071 /* st.c */
2072 extern gfc_code new_st;
2073
2074 void gfc_clear_new_st (void);
2075 gfc_code *gfc_get_code (void);
2076 gfc_code *gfc_append_code (gfc_code *, gfc_code *);
2077 void gfc_free_statement (gfc_code *);
2078 void gfc_free_statements (gfc_code *);
2079
2080 /* resolve.c */
2081 try gfc_resolve_expr (gfc_expr *);
2082 void gfc_resolve (gfc_namespace *);
2083 void gfc_resolve_blocks (gfc_code *, gfc_namespace *);
2084 int gfc_impure_variable (gfc_symbol *);
2085 int gfc_pure (gfc_symbol *);
2086 int gfc_elemental (gfc_symbol *);
2087 try gfc_resolve_iterator (gfc_iterator *, bool);
2088 try gfc_resolve_index (gfc_expr *, int);
2089 try gfc_resolve_dim_arg (gfc_expr *);
2090 int gfc_is_formal_arg (void);
2091
2092 /* array.c */
2093 void gfc_free_array_spec (gfc_array_spec *);
2094 gfc_array_ref *gfc_copy_array_ref (gfc_array_ref *);
2095
2096 try gfc_set_array_spec (gfc_symbol *, gfc_array_spec *, locus *);
2097 gfc_array_spec *gfc_copy_array_spec (gfc_array_spec *);
2098 try gfc_resolve_array_spec (gfc_array_spec *, int);
2099
2100 int gfc_compare_array_spec (gfc_array_spec *, gfc_array_spec *);
2101
2102 gfc_expr *gfc_start_constructor (bt, int, locus *);
2103 void gfc_append_constructor (gfc_expr *, gfc_expr *);
2104 void gfc_free_constructor (gfc_constructor *);
2105 void gfc_simplify_iterator_var (gfc_expr *);
2106 try gfc_expand_constructor (gfc_expr *);
2107 int gfc_constant_ac (gfc_expr *);
2108 int gfc_expanded_ac (gfc_expr *);
2109 void gfc_resolve_character_array_constructor (gfc_expr *);
2110 try gfc_resolve_array_constructor (gfc_expr *);
2111 try gfc_check_constructor_type (gfc_expr *);
2112 try gfc_check_iter_variable (gfc_expr *);
2113 try gfc_check_constructor (gfc_expr *, try (*)(gfc_expr *));
2114 gfc_constructor *gfc_copy_constructor (gfc_constructor * src);
2115 gfc_expr *gfc_get_array_element (gfc_expr *, int);
2116 try gfc_array_size (gfc_expr *, mpz_t *);
2117 try gfc_array_dimen_size (gfc_expr *, int, mpz_t *);
2118 try gfc_array_ref_shape (gfc_array_ref *, mpz_t *);
2119 gfc_array_ref *gfc_find_array_ref (gfc_expr *);
2120 void gfc_insert_constructor (gfc_expr *, gfc_constructor *);
2121 gfc_constructor *gfc_get_constructor (void);
2122 tree gfc_conv_array_initializer (tree type, gfc_expr * expr);
2123 try spec_size (gfc_array_spec *, mpz_t *);
2124 try spec_dimen_size (gfc_array_spec *, int, mpz_t *);
2125 int gfc_is_compile_time_shape (gfc_array_spec *);
2126
2127 /* interface.c -- FIXME: some of these should be in symbol.c */
2128 void gfc_free_interface (gfc_interface *);
2129 int gfc_compare_derived_types (gfc_symbol *, gfc_symbol *);
2130 int gfc_compare_types (gfc_typespec *, gfc_typespec *);
2131 void gfc_check_interfaces (gfc_namespace *);
2132 void gfc_procedure_use (gfc_symbol *, gfc_actual_arglist **, locus *);
2133 gfc_symbol *gfc_search_interface (gfc_interface *, int,
2134                                   gfc_actual_arglist **);
2135 try gfc_extend_expr (gfc_expr *);
2136 void gfc_free_formal_arglist (gfc_formal_arglist *);
2137 try gfc_extend_assign (gfc_code *, gfc_namespace *);
2138 try gfc_add_interface (gfc_symbol * sym);
2139
2140 /* io.c */
2141 extern gfc_st_label format_asterisk;
2142
2143 void gfc_free_open (gfc_open *);
2144 try gfc_resolve_open (gfc_open *);
2145 void gfc_free_close (gfc_close *);
2146 try gfc_resolve_close (gfc_close *);
2147 void gfc_free_filepos (gfc_filepos *);
2148 try gfc_resolve_filepos (gfc_filepos *);
2149 void gfc_free_inquire (gfc_inquire *);
2150 try gfc_resolve_inquire (gfc_inquire *);
2151 void gfc_free_dt (gfc_dt *);
2152 try gfc_resolve_dt (gfc_dt *);
2153
2154 /* module.c */
2155 void gfc_module_init_2 (void);
2156 void gfc_module_done_2 (void);
2157 void gfc_dump_module (const char *, int);
2158 bool gfc_check_access (gfc_access, gfc_access);
2159
2160 /* primary.c */
2161 symbol_attribute gfc_variable_attr (gfc_expr *, gfc_typespec *);
2162 symbol_attribute gfc_expr_attr (gfc_expr *);
2163 match gfc_match_rvalue (gfc_expr **);
2164
2165 /* trans.c */
2166 void gfc_generate_code (gfc_namespace *);
2167 void gfc_generate_module_code (gfc_namespace *);
2168
2169 /* bbt.c */
2170 typedef int (*compare_fn) (void *, void *);
2171 void gfc_insert_bbt (void *, void *, compare_fn);
2172 void gfc_delete_bbt (void *, void *, compare_fn);
2173
2174 /* dump-parse-tree.c */
2175 void gfc_show_actual_arglist (gfc_actual_arglist *);
2176 void gfc_show_array_ref (gfc_array_ref *);
2177 void gfc_show_array_spec (gfc_array_spec *);
2178 void gfc_show_attr (symbol_attribute *);
2179 void gfc_show_code (int, gfc_code *);
2180 void gfc_show_components (gfc_symbol *);
2181 void gfc_show_constructor (gfc_constructor *);
2182 void gfc_show_equiv (gfc_equiv *);
2183 void gfc_show_expr (gfc_expr *);
2184 void gfc_show_namelist (gfc_namelist *);
2185 void gfc_show_namespace (gfc_namespace *);
2186 void gfc_show_ref (gfc_ref *);
2187 void gfc_show_symbol (gfc_symbol *);
2188 void gfc_show_typespec (gfc_typespec *);
2189
2190 /* parse.c */
2191 try gfc_parse_file (void);
2192 void global_used (gfc_gsymbol *, locus *);
2193
2194 /* dependency.c */
2195 int gfc_dep_compare_expr (gfc_expr *, gfc_expr *);
2196
2197 #endif /* GCC_GFORTRAN_H  */