1G77(1)                                GNU                               G77(1)
2
3
4

NAME

6       g77 - GNU project Fortran 77 compiler
7

SYNOPSIS

9       g77 [-c|-S|-E]
10           [-g] [-pg] [-Olevel]
11           [-Wwarn...] [-pedantic]
12           [-Idir...] [-Ldir...]
13           [-Dmacro[=defn]...] [-Umacro]
14           [-foption...] [-mmachine-option...]
15           [-o outfile] infile...
16
17       Only the most useful options are listed here; see below for the
18       remainder.
19

DESCRIPTION

21       The g77 command supports all the options supported by the gcc command.
22
23       All gcc and g77 options are accepted both by g77 and by gcc (as well as
24       any other drivers built at the same time, such as g++), since adding
25       g77 to the gcc distribution enables acceptance of g77 options by all of
26       the relevant drivers.
27
28       In some cases, options have positive and negative forms; the negative
29       form of -ffoo would be -fno-foo.  This manual documents only one of
30       these two forms, whichever one is not the default.
31

OPTIONS

33       Here is a summary of all the options specific to GNU Fortran, grouped
34       by type.  Explanations are in the following sections.
35
36       Overall Options
37           -fversion  -fset-g77-defaults  -fno-silent
38
39       Shorthand Options
40           -ff66  -fno-f66  -ff77  -fno-f77  -fno-ugly
41
42       Fortran Language Options
43           -ffree-form  -fno-fixed-form  -ff90 -fvxt  -fdollar-ok
44           -fno-backslash -fno-ugly-args  -fno-ugly-assign  -fno-ugly-assumed
45           -fugly-comma  -fugly-complex  -fugly-init  -fugly-logint -fonetrip
46           -ftypeless-boz -fintrin-case-initcap  -fintrin-case-upper
47           -fintrin-case-lower  -fintrin-case-any -fmatch-case-initcap
48           -fmatch-case-upper -fmatch-case-lower  -fmatch-case-any
49           -fsource-case-upper  -fsource-case-lower -fsource-case-preserve
50           -fsymbol-case-initcap  -fsymbol-case-upper -fsymbol-case-lower
51           -fsymbol-case-any -fcase-strict-upper  -fcase-strict-lower
52           -fcase-initcap  -fcase-upper  -fcase-lower  -fcase-preserve
53           -ff2c-intrinsics-delete  -ff2c-intrinsics-hide
54           -ff2c-intrinsics-disable  -ff2c-intrinsics-enable
55           -fbadu77-intrinsics-delete  -fbadu77-intrinsics-hide
56           -fbadu77-intrinsics-disable  -fbadu77-intrinsics-enable
57           -ff90-intrinsics-delete  -ff90-intrinsics-hide
58           -ff90-intrinsics-disable  -ff90-intrinsics-enable
59           -fgnu-intrinsics-delete  -fgnu-intrinsics-hide
60           -fgnu-intrinsics-disable  -fgnu-intrinsics-enable
61           -fmil-intrinsics-delete  -fmil-intrinsics-hide
62           -fmil-intrinsics-disable  -fmil-intrinsics-enable
63           -funix-intrinsics-delete  -funix-intrinsics-hide
64           -funix-intrinsics-disable  -funix-intrinsics-enable
65           -fvxt-intrinsics-delete  -fvxt-intrinsics-hide
66           -fvxt-intrinsics-disable  -fvxt-intrinsics-enable
67           -ffixed-line-length-n  -ffixed-line-length-none
68
69       Warning Options
70           -fsyntax-only  -pedantic  -pedantic-errors  -fpedantic -w
71           -Wno-globals  -Wimplicit  -Wunused  -Wuninitialized -Wall
72           -Wsurprising -Werror  -W
73
74       Debugging Options
75           -g
76
77       Optimization Options
78           -malign-double -ffloat-store  -fforce-mem  -fforce-addr
79           -fno-inline -ffast-math  -fstrength-reduce  -frerun-cse-after-loop
80           -funsafe-math-optimizations -ffinite-math-only -fno-trapping-math
81           -fexpensive-optimizations  -fdelayed-branch -fschedule-insns
82           -fschedule-insn2  -fcaller-saves -funroll-loops  -funroll-all-loops
83           -fno-move-all-movables  -fno-reduce-all-givs -fno-rerun-loop-opt
84
85       Directory Options
86           -Idir  -I-
87
88       Code Generation Options
89           -fno-automatic  -finit-local-zero  -fno-f2c -ff2c-library
90           -fno-underscoring  -fno-ident -fpcc-struct-return
91           -freg-struct-return -fshort-double  -fno-common  -fpack-struct
92           -fzeros  -fno-second-underscore -femulate-complex -falias-check
93           -fargument-alias -fargument-noalias  -fno-argument-noalias-global
94           -fno-globals  -fflatten-arrays -fbounds-check
95           -ffortran-bounds-check
96
97       Compilation can involve as many as four stages: preprocessing, code
98       generation (often what is really meant by the term ``compilation''),
99       assembly, and linking, always in that order.  The first three stages
100       apply to an individual source file, and end by producing an object
101       file; linking combines all the object files (those newly compiled, and
102       those specified as input) into an executable file.
103
104       For any given input file, the file name suffix determines what kind of
105       program is contained in the file---that is, the language in which the
106       program is written is generally indicated by the suffix.  Suffixes
107       specific to GNU Fortran are listed below.
108
109       file.f
110       file.for
111       file.FOR
112           Fortran source code that should not be preprocessed.
113
114           Such source code cannot contain any preprocessor directives, such
115           as "#include", "#define", "#if", and so on.
116
117           You can force .f files to be preprocessed by cpp by using -x
118           f77-cpp-input.
119
120       file.F
121       file.fpp
122       file.FPP
123           Fortran source code that must be preprocessed (by the C
124           preprocessor cpp, which is part of GCC).
125
126           Note that preprocessing is not extended to the contents of files
127           included by the "INCLUDE" directive---the "#include" preprocessor
128           directive must be used instead.
129
130       file.r
131           Ratfor source code, which must be preprocessed by the ratfor
132           command, which is available separately (as it is not yet part of
133           the GNU Fortran distribution).  A public domain version in C is at
134           <http://sepwww.stanford.edu/sep/prof/ratfor.shar.2>.
135
136       UNIX users typically use the file.f and file.F nomenclature.  Users of
137       other operating systems, especially those that cannot distinguish
138       upper-case letters from lower-case letters in their file names,
139       typically use the file.for and file.fpp nomenclature.
140
141       Use of the preprocessor cpp allows use of C-like constructs such as
142       "#define" and "#include", but can lead to unexpected, even mistaken,
143       results due to Fortran's source file format.  It is recommended that
144       use of the C preprocessor be limited to "#include" and, in conjunction
145       with "#define", only "#if" and related directives, thus avoiding in-
146       line macro expansion entirely.  This recommendation applies especially
147       when using the traditional fixed source form.  With free source form,
148       fewer unexpected transformations are likely to happen, but use of
149       constructs such as Hollerith and character constants can nevertheless
150       present problems, especially when these are continued across multiple
151       source lines.  These problems result, primarily, from differences
152       between the way such constants are interpreted by the C preprocessor
153       and by a Fortran compiler.
154
155       Another example of a problem that results from using the C preprocessor
156       is that a Fortran comment line that happens to contain any characters
157       ``interesting'' to the C preprocessor, such as a backslash at the end
158       of the line, is not recognized by the preprocessor as a comment line,
159       so instead of being passed through ``raw'', the line is edited
160       according to the rules for the preprocessor.  For example, the
161       backslash at the end of the line is removed, along with the subsequent
162       newline, resulting in the next line being effectively commented
163       out---unfortunate if that line is a non-comment line of important code!
164
165       Note: The -traditional and -undef flags are supplied to cpp by default,
166       to help avoid unpleasant surprises.
167
168       This means that ANSI C preprocessor features (such as the # operator)
169       aren't available, and only variables in the C reserved namespace
170       (generally, names with a leading underscore) are liable to substitution
171       by C predefines.  Thus, if you want to do system-specific tests, use,
172       for example, #ifdef __linux__ rather than #ifdef linux.  Use the -v
173       option to see exactly how the preprocessor is invoked.
174
175       Unfortunately, the -traditional flag will not avoid an error from
176       anything that cpp sees as an unterminated C comment, such as:
177
178               C Some Fortran compilers accept /* as starting
179               C an inline comment.
180
181       The following options that affect overall processing are recognized by
182       the g77 and gcc commands in a GNU Fortran installation:
183
184       -fversion
185           Ensure that the g77 version of the compiler phase is reported, if
186           run, and, starting in "egcs" version 1.1, that internal consistency
187           checks in the f771 program are run.
188
189           This option is supplied automatically when -v or --verbose is
190           specified as a command-line option for g77 or gcc and when the
191           resulting commands compile Fortran source files.
192
193           In GCC 3.1, this is changed back to the behavior gcc displays for
194           .c files.
195
196       -fset-g77-defaults
197           Version info: This option was obsolete as of "egcs" version 1.1.
198           The effect is instead achieved by the "lang_init_options" routine
199           in gcc/gcc/f/com.c.
200
201           Set up whatever gcc options are to apply to Fortran compilations,
202           and avoid running internal consistency checks that might take some
203           time.
204
205           This option is supplied automatically when compiling Fortran code
206           via the g77 or gcc command.  The description of this option is
207           provided so that users seeing it in the output of, say, g77 -v
208           understand why it is there.
209
210           Also, developers who run "f771" directly might want to specify it
211           by hand to get the same defaults as they would running "f771" via
212           g77 or gcc However, such developers should, after linking a new
213           "f771" executable, invoke it without this option once, e.g. via
214           "./f771 -quiet < /dev/null", to ensure that they have not
215           introduced any internal inconsistencies (such as in the table of
216           intrinsics) before proceeding---g77 will crash with a diagnostic if
217           it detects an inconsistency.
218
219       -fno-silent
220           Print (to "stderr") the names of the program units as they are
221           compiled, in a form similar to that used by popular UNIX f77
222           implementations and f2c
223
224   Shorthand Options
225       The following options serve as ``shorthand'' for other options accepted
226       by the compiler:
227
228       -fugly
229           Note: This option is no longer supported.  The information, below,
230           is provided to aid in the conversion of old scripts.
231
232           Specify that certain ``ugly'' constructs are to be quietly
233           accepted.  Same as:
234
235                   -fugly-args -fugly-assign -fugly-assumed
236                   -fugly-comma -fugly-complex -fugly-init
237                   -fugly-logint
238
239           These constructs are considered inappropriate to use in new or
240           well-maintained portable Fortran code, but widely used in old code.
241
242       -fno-ugly
243           Specify that all ``ugly'' constructs are to be noisily rejected.
244           Same as:
245
246                   -fno-ugly-args -fno-ugly-assign -fno-ugly-assumed
247                   -fno-ugly-comma -fno-ugly-complex -fno-ugly-init
248                   -fno-ugly-logint
249
250       -ff66
251           Specify that the program is written in idiomatic FORTRAN 66.  Same
252           as -fonetrip -fugly-assumed.
253
254           The -fno-f66 option is the inverse of -ff66.  As such, it is the
255           same as -fno-onetrip -fno-ugly-assumed.
256
257           The meaning of this option is likely to be refined as future
258           versions of g77 provide more compatibility with other existing and
259           obsolete Fortran implementations.
260
261       -ff77
262           Specify that the program is written in idiomatic UNIX FORTRAN 77
263           and/or the dialect accepted by the f2c product.  Same as
264           -fbackslash -fno-typeless-boz.
265
266           The meaning of this option is likely to be refined as future
267           versions of g77 provide more compatibility with other existing and
268           obsolete Fortran implementations.
269
270       -fno-f77
271           The -fno-f77 option is not the inverse of -ff77.  It specifies that
272           the program is not written in idiomatic UNIX FORTRAN 77 or f2c but
273           in a more widely portable dialect.  -fno-f77 is the same as
274           -fno-backslash.
275
276           The meaning of this option is likely to be refined as future
277           versions of g77 provide more compatibility with other existing and
278           obsolete Fortran implementations.
279
280   Options Controlling Fortran Dialect
281       The following options control the dialect of Fortran that the compiler
282       accepts:
283
284       -ffree-form
285       -fno-fixed-form
286           Specify that the source file is written in free form (introduced in
287           Fortran 90) instead of the more-traditional fixed form.
288
289       -ff90
290           Allow certain Fortran-90 constructs.
291
292           This option controls whether certain Fortran 90 constructs are
293           recognized.  (Other Fortran 90 constructs might or might not be
294           recognized depending on other options such as -fvxt,
295           -ff90-intrinsics-enable, and the current level of support for
296           Fortran 90.)
297
298       -fvxt
299           Specify the treatment of certain constructs that have different
300           meanings depending on whether the code is written in GNU Fortran
301           (based on FORTRAN 77 and akin to Fortran 90) or VXT Fortran (more
302           like VAX FORTRAN).
303
304           The default is -fno-vxt.  -fvxt specifies that the VXT Fortran
305           interpretations for those constructs are to be chosen.
306
307       -fdollar-ok
308           Allow $ as a valid character in a symbol name.
309
310       -fno-backslash
311           Specify that \ is not to be specially interpreted in character and
312           Hollerith constants a la C and many UNIX Fortran compilers.
313
314           For example, with -fbackslash in effect, A\nB specifies three
315           characters, with the second one being newline.  With
316           -fno-backslash, it specifies four characters, A, \, n, and B.
317
318           Note that g77 implements a fairly general form of backslash
319           processing that is incompatible with the narrower forms supported
320           by some other compilers.  For example, 'A\003B' is a three-
321           character string in g77 whereas other compilers that support
322           backslash might not support the three-octal-digit form, and thus
323           treat that string as longer than three characters.
324
325       -fno-ugly-args
326           Disallow passing Hollerith and typeless constants as actual
327           arguments (for example, CALL FOO(4HABCD)).
328
329       -fugly-assign
330           Use the same storage for a given variable regardless of whether it
331           is used to hold an assigned-statement label (as in ASSIGN 10 TO I)
332           or used to hold numeric data (as in I = 3).
333
334       -fugly-assumed
335           Assume any dummy array with a final dimension specified as 1 is
336           really an assumed-size array, as if * had been specified for the
337           final dimension instead of 1.
338
339           For example, DIMENSION X(1) is treated as if it had read DIMENSION
340           X(*).
341
342       -fugly-comma
343           In an external-procedure invocation, treat a trailing comma in the
344           argument list as specification of a trailing null argument, and
345           treat an empty argument list as specification of a single null
346           argument.
347
348           For example, CALL FOO(,) is treated as CALL FOO(%VAL(0), %VAL(0)).
349           That is, two null arguments are specified by the procedure call
350           when -fugly-comma is in force.  And F = FUNC() is treated as F =
351           FUNC(%VAL(0)).
352
353           The default behavior, -fno-ugly-comma, is to ignore a single
354           trailing comma in an argument list.  So, by default, CALL FOO(X,)
355           is treated exactly the same as CALL FOO(X).
356
357       -fugly-complex
358           Do not complain about REAL(expr) or AIMAG(expr) when expr is a
359           "COMPLEX" type other than "COMPLEX(KIND=1)"---usually this is used
360           to permit "COMPLEX(KIND=2)" ("DOUBLE COMPLEX") operands.
361
362           The -ff90 option controls the interpretation of this construct.
363
364       -fno-ugly-init
365           Disallow use of Hollerith and typeless constants as initial values
366           (in "PARAMETER" and "DATA" statements), and use of character
367           constants to initialize numeric types and vice versa.
368
369           For example, DATA I/'F'/, CHRVAR/65/, J/4HABCD/ is disallowed by
370           -fno-ugly-init.
371
372       -fugly-logint
373           Treat "INTEGER" and "LOGICAL" variables and expressions as
374           potential stand-ins for each other.
375
376           For example, automatic conversion between "INTEGER" and "LOGICAL"
377           is enabled, for many contexts, via this option.
378
379       -fonetrip
380           Executable iterative "DO" loops are to be executed at least once
381           each time they are reached.
382
383           ANSI FORTRAN 77 and more recent versions of the Fortran standard
384           specify that the body of an iterative "DO" loop is not executed if
385           the number of iterations calculated from the parameters of the loop
386           is less than 1.  (For example, DO 10 I = 1, 0.)  Such a loop is
387           called a zero-trip loop.
388
389           Prior to ANSI FORTRAN 77, many compilers implemented "DO" loops
390           such that the body of a loop would be executed at least once, even
391           if the iteration count was zero.  Fortran code written assuming
392           this behavior is said to require one-trip loops.  For example, some
393           code written to the FORTRAN 66 standard expects this behavior from
394           its "DO" loops, although that standard did not specify this
395           behavior.
396
397           The -fonetrip option specifies that the source file(s) being
398           compiled require one-trip loops.
399
400           This option affects only those loops specified by the (iterative)
401           "DO" statement and by implied-"DO" lists in I/O statements.  Loops
402           specified by implied-"DO" lists in "DATA" and specification (non-
403           executable) statements are not affected.
404
405       -ftypeless-boz
406           Specifies that prefix-radix non-decimal constants, such as Z'ABCD',
407           are typeless instead of "INTEGER(KIND=1)".
408
409           You can test for yourself whether a particular compiler treats the
410           prefix form as "INTEGER(KIND=1)" or typeless by running the
411           following program:
412
413                   EQUIVALENCE (I, R)
414                   R = Z'ABCD1234'
415                   J = Z'ABCD1234'
416                   IF (J .EQ. I) PRINT *, 'Prefix form is TYPELESS'
417                   IF (J .NE. I) PRINT *, 'Prefix form is INTEGER'
418                   END
419
420           Reports indicate that many compilers process this form as
421           "INTEGER(KIND=1)", though a few as typeless, and at least one based
422           on a command-line option specifying some kind of compatibility.
423
424       -fintrin-case-initcap
425       -fintrin-case-upper
426       -fintrin-case-lower
427       -fintrin-case-any
428           Specify expected case for intrinsic names.  -fintrin-case-lower is
429           the default.
430
431       -fmatch-case-initcap
432       -fmatch-case-upper
433       -fmatch-case-lower
434       -fmatch-case-any
435           Specify expected case for keywords.  -fmatch-case-lower is the
436           default.
437
438       -fsource-case-upper
439       -fsource-case-lower
440       -fsource-case-preserve
441           Specify whether source text other than character and Hollerith
442           constants is to be translated to uppercase, to lowercase, or
443           preserved as is.  -fsource-case-lower is the default.
444
445       -fsymbol-case-initcap
446       -fsymbol-case-upper
447       -fsymbol-case-lower
448       -fsymbol-case-any
449           Specify valid cases for user-defined symbol names.
450           -fsymbol-case-any is the default.
451
452       -fcase-strict-upper
453           Same as -fintrin-case-upper -fmatch-case-upper
454           -fsource-case-preserve -fsymbol-case-upper.  (Requires all
455           pertinent source to be in uppercase.)
456
457       -fcase-strict-lower
458           Same as -fintrin-case-lower -fmatch-case-lower
459           -fsource-case-preserve -fsymbol-case-lower.  (Requires all
460           pertinent source to be in lowercase.)
461
462       -fcase-initcap
463           Same as -fintrin-case-initcap -fmatch-case-initcap
464           -fsource-case-preserve -fsymbol-case-initcap.  (Requires all
465           pertinent source to be in initial capitals, as in Print
466           *,SqRt(Value).)
467
468       -fcase-upper
469           Same as -fintrin-case-any -fmatch-case-any -fsource-case-upper
470           -fsymbol-case-any.  (Maps all pertinent source to uppercase.)
471
472       -fcase-lower
473           Same as -fintrin-case-any -fmatch-case-any -fsource-case-lower
474           -fsymbol-case-any.  (Maps all pertinent source to lowercase.)
475
476       -fcase-preserve
477           Same as -fintrin-case-any -fmatch-case-any -fsource-case-preserve
478           -fsymbol-case-any.  (Preserves all case in user-defined symbols,
479           while allowing any-case matching of intrinsics and keywords.  For
480           example, call Foo(i,I) would pass two different variables named i
481           and I to a procedure named Foo.)
482
483       -fbadu77-intrinsics-delete
484       -fbadu77-intrinsics-hide
485       -fbadu77-intrinsics-disable
486       -fbadu77-intrinsics-enable
487           Specify status of UNIX intrinsics having inappropriate forms.
488           -fbadu77-intrinsics-enable is the default.
489
490       -ff2c-intrinsics-delete
491       -ff2c-intrinsics-hide
492       -ff2c-intrinsics-disable
493       -ff2c-intrinsics-enable
494           Specify status of f2c-specific intrinsics.  -ff2c-intrinsics-enable
495           is the default.
496
497       -ff90-intrinsics-delete
498       -ff90-intrinsics-hide
499       -ff90-intrinsics-disable
500       -ff90-intrinsics-enable
501           Specify status of F90-specific intrinsics.  -ff90-intrinsics-enable
502           is the default.
503
504       -fgnu-intrinsics-delete
505       -fgnu-intrinsics-hide
506       -fgnu-intrinsics-disable
507       -fgnu-intrinsics-enable
508           Specify status of Digital's COMPLEX-related intrinsics.
509           -fgnu-intrinsics-enable is the default.
510
511       -fmil-intrinsics-delete
512       -fmil-intrinsics-hide
513       -fmil-intrinsics-disable
514       -fmil-intrinsics-enable
515           Specify status of MIL-STD-1753-specific intrinsics.
516           -fmil-intrinsics-enable is the default.
517
518       -funix-intrinsics-delete
519       -funix-intrinsics-hide
520       -funix-intrinsics-disable
521       -funix-intrinsics-enable
522           Specify status of UNIX intrinsics.  -funix-intrinsics-enable is the
523           default.
524
525       -fvxt-intrinsics-delete
526       -fvxt-intrinsics-hide
527       -fvxt-intrinsics-disable
528       -fvxt-intrinsics-enable
529           Specify status of VXT intrinsics.  -fvxt-intrinsics-enable is the
530           default.
531
532       -ffixed-line-length-n
533           Set column after which characters are ignored in typical fixed-form
534           lines in the source file, and through which spaces are assumed (as
535           if padded to that length) after the ends of short fixed-form lines.
536
537           Popular values for n include 72 (the standard and the default), 80
538           (card image), and 132 (corresponds to ``extended-source'' options
539           in some popular compilers).  n may be none, meaning that the entire
540           line is meaningful and that continued character constants never
541           have implicit spaces appended to them to fill out the line.
542           -ffixed-line-length-0 means the same thing as
543           -ffixed-line-length-none.
544
545   Options to Request or Suppress Warnings
546       Warnings are diagnostic messages that report constructions which are
547       not inherently erroneous but which are risky or suggest there might
548       have been an error.
549
550       You can request many specific warnings with options beginning -W, for
551       example -Wimplicit to request warnings on implicit declarations.  Each
552       of these specific warning options also has a negative form beginning
553       -Wno- to turn off warnings; for example, -Wno-implicit.  This manual
554       lists only one of the two forms, whichever is not the default.
555
556       These options control the amount and kinds of warnings produced by GNU
557       Fortran:
558
559       -fsyntax-only
560           Check the code for syntax errors, but don't do anything beyond
561           that.
562
563       -pedantic
564           Issue warnings for uses of extensions to ANSI FORTRAN 77.
565           -pedantic also applies to C-language constructs where they occur in
566           GNU Fortran source files, such as use of \e in a character constant
567           within a directive like #include.
568
569           Valid ANSI FORTRAN 77 programs should compile properly with or
570           without this option.  However, without this option, certain GNU
571           extensions and traditional Fortran features are supported as well.
572           With this option, many of them are rejected.
573
574           Some users try to use -pedantic to check programs for strict ANSI
575           conformance.  They soon find that it does not do quite what they
576           want---it finds some non-ANSI practices, but not all.  However,
577           improvements to g77 in this area are welcome.
578
579       -pedantic-errors
580           Like -pedantic, except that errors are produced rather than
581           warnings.
582
583       -fpedantic
584           Like -pedantic, but applies only to Fortran constructs.
585
586       -w  Inhibit all warning messages.
587
588       -Wno-globals
589           Inhibit warnings about use of a name as both a global name (a
590           subroutine, function, or block data program unit, or a common
591           block) and implicitly as the name of an intrinsic in a source file.
592
593           Also inhibit warnings about inconsistent invocations and/or
594           definitions of global procedures (function and subroutines).  Such
595           inconsistencies include different numbers of arguments and
596           different types of arguments.
597
598       -Wimplicit
599           Warn whenever a variable, array, or function is implicitly
600           declared.  Has an effect similar to using the "IMPLICIT NONE"
601           statement in every program unit.  (Some Fortran compilers provide
602           this feature by an option named -u or /WARNINGS=DECLARATIONS.)
603
604       -Wunused
605           Warn whenever a variable is unused aside from its declaration.
606
607       -Wuninitialized
608           Warn whenever an automatic variable is used without first being
609           initialized.
610
611           These warnings are possible only in optimizing compilation, because
612           they require data-flow information that is computed only when
613           optimizing.  If you don't specify -O, you simply won't get these
614           warnings.
615
616           These warnings occur only for variables that are candidates for
617           register allocation.  Therefore, they do not occur for a variable
618           whose address is taken, or whose size is other than 1, 2, 4 or 8
619           bytes.  Also, they do not occur for arrays, even when they are in
620           registers.
621
622           Note that there might be no warning about a variable that is used
623           only to compute a value that itself is never used, because such
624           computations may be deleted by data-flow analysis before the
625           warnings are printed.
626
627           These warnings are made optional because GNU Fortran is not smart
628           enough to see all the reasons why the code might be correct despite
629           appearing to have an error.  Here is one example of how this can
630           happen:
631
632                   SUBROUTINE DISPAT(J)
633                   IF (J.EQ.1) I=1
634                   IF (J.EQ.2) I=4
635                   IF (J.EQ.3) I=5
636                   CALL FOO(I)
637                   END
638
639           If the value of "J" is always 1, 2 or 3, then "I" is always
640           initialized, but GNU Fortran doesn't know this.  Here is another
641           common case:
642
643                   SUBROUTINE MAYBE(FLAG)
644                   LOGICAL FLAG
645                   IF (FLAG) VALUE = 9.4
646                   ...
647                   IF (FLAG) PRINT *, VALUE
648                   END
649
650           This has no bug because "VALUE" is used only if it is set.
651
652       -Wall
653           The -Wunused and -Wuninitialized options combined.  These are all
654           the options which pertain to usage that we recommend avoiding and
655           that we believe is easy to avoid.  (As more warnings are added to
656           g77 some might be added to the list enabled by -Wall.)
657
658       The remaining -W... options are not implied by -Wall because they warn
659       about constructions that we consider reasonable to use, on occasion, in
660       clean programs.
661
662       -Wsurprising
663           Warn about ``suspicious'' constructs that are interpreted by the
664           compiler in a way that might well be surprising to someone reading
665           the code.  These differences can result in subtle, compiler-
666           dependent (even machine-dependent) behavioral differences.  The
667           constructs warned about include:
668
669           ·   Expressions having two arithmetic operators in a row, such as
670               X*-Y.  Such a construct is nonstandard, and can produce
671               unexpected results in more complicated situations such as
672               X**-Y*Z.  g77 along with many other compilers, interprets this
673               example differently than many programmers, and a few other
674               compilers.  Specifically, g77 interprets X**-Y*Z as
675               (X**(-Y))*Z, while others might think it should be interpreted
676               as X**(-(Y*Z)).
677
678               A revealing example is the constant expression 2**-2*1., which
679               g77 evaluates to .25, while others might evaluate it to 0., the
680               difference resulting from the way precedence affects type
681               promotion.
682
683               (The -fpedantic option also warns about expressions having two
684               arithmetic operators in a row.)
685
686           ·   Expressions with a unary minus followed by an operand and then
687               a binary operator other than plus or minus.  For example, -2**2
688               produces a warning, because the precedence is -(2**2), yielding
689               -4, not (-2)**2, which yields 4, and which might represent what
690               a programmer expects.
691
692               An example of an expression producing different results in a
693               surprising way is -I*S, where I holds the value -2147483648 and
694               S holds 0.5.  On many systems, negating I results in the same
695               value, not a positive number, because it is already the lower
696               bound of what an "INTEGER(KIND=1)" variable can hold.  So, the
697               expression evaluates to a positive number, while the
698               ``expected'' interpretation, (-I)*S, would evaluate to a
699               negative number.
700
701               Even cases such as -I*J produce warnings, even though, in most
702               configurations and situations, there is no computational
703               difference between the results of the two interpretations---the
704               purpose of this warning is to warn about differing
705               interpretations and encourage a better style of coding, not to
706               identify only those places where bugs might exist in the user's
707               code.
708
709           ·   "DO" loops with "DO" variables that are not of integral
710               type---that is, using "REAL" variables as loop control
711               variables.  Although such loops can be written to work in the
712               ``obvious'' way, the way g77 is required by the Fortran
713               standard to interpret such code is likely to be quite different
714               from the way many programmers expect.  (This is true of all
715               "DO" loops, but the differences are pronounced for non-integral
716               loop control variables.)
717
718       -Werror
719           Make all warnings into errors.
720
721       -W  Turns on ``extra warnings'' and, if optimization is specified via
722           -O, the -Wuninitialized option.  (This might change in future
723           versions of g77
724
725           ``Extra warnings'' are issued for:
726
727           ·   Unused parameters to a procedure (when -Wunused also is
728               specified).
729
730           ·   Overflows involving floating-point constants (not available for
731               certain configurations).
732
733       Some of these have no effect when compiling programs written in
734       Fortran:
735
736       -Wcomment
737       -Wformat
738       -Wparentheses
739       -Wswitch
740       -Wswitch-default
741       -Wswitch-enum
742       -Wtraditional
743       -Wshadow
744       -Wid-clash-len
745       -Wlarger-than-len
746       -Wconversion
747       -Waggregate-return
748       -Wredundant-decls
749           These options all could have some relevant meaning for GNU Fortran
750           programs, but are not yet supported.
751
752   Options for Debugging Your Program or GNU Fortran
753       GNU Fortran has various special options that are used for debugging
754       either your program or g77
755
756       -g  Produce debugging information in the operating system's native
757           format (stabs, COFF, XCOFF, or DWARF).  GDB can work with this
758           debugging information.
759
760           A sample debugging session looks like this (note the use of the
761           breakpoint):
762
763                   $ cat gdb.f
764                         PROGRAM PROG
765                         DIMENSION A(10)
766                         DATA A /1.,2.,3.,4.,5.,6.,7.,8.,9.,10./
767                         A(5) = 4.
768                         PRINT*,A
769                         END
770                   $ g77 -g -O gdb.f
771                   $ gdb a.out
772                   ...
773                   (gdb) break MAIN__
774                   Breakpoint 1 at 0x8048e96: file gdb.f, line 4.
775                   (gdb) run
776                   Starting program: /home/toon/g77-bugs/./a.out
777                   Breakpoint 1, MAIN__ () at gdb.f:4
778                   4             A(5) = 4.
779                   Current language:  auto; currently fortran
780                   (gdb) print a(5)
781                   $1 = 5
782                   (gdb) step
783                   5             PRINT*,A
784                   (gdb) print a(5)
785                   $2 = 4
786                   ...
787
788           One could also add the setting of the breakpoint and the first run
789           command to the file .gdbinit in the current directory, to simplify
790           the debugging session.
791
792   Options That Control Optimization
793       Most Fortran users will want to use no optimization when developing and
794       testing programs, and use -O or -O2 when compiling programs for late-
795       cycle testing and for production use.  However, note that certain
796       diagnostics---such as for uninitialized variables---depend on the flow
797       analysis done by -O, i.e. you must use -O or -O2 to get such
798       diagnostics.
799
800       The following flags have particular applicability when compiling
801       Fortran programs:
802
803       -malign-double
804           (Intel x86 architecture only.)
805
806           Noticeably improves performance of g77 programs making heavy use of
807           "REAL(KIND=2)" ("DOUBLE PRECISION") data on some systems.  In
808           particular, systems using Pentium, Pentium Pro, 586, and 686
809           implementations of the i386 architecture execute programs faster
810           when "REAL(KIND=2)" ("DOUBLE PRECISION") data are aligned on 64-bit
811           boundaries in memory.
812
813           This option can, at least, make benchmark results more consistent
814           across various system configurations, versions of the program, and
815           data sets.
816
817           Note: The warning in the gcc documentation about this option does
818           not apply, generally speaking, to Fortran code compiled by g77
819
820           Also also note: The negative form of -malign-double is
821           -mno-align-double, not -benign-double.
822
823       -ffloat-store
824           Might help a Fortran program that depends on exact IEEE conformance
825           on some machines, but might slow down a program that doesn't.
826
827           This option is effective when the floating-point unit is set to
828           work in IEEE 854 `extended precision'---as it typically is on x86
829           and m68k GNU systems---rather than IEEE 754 double precision.
830           -ffloat-store tries to remove the extra precision by spilling data
831           from floating-point registers into memory and this typically
832           involves a big performance hit.  However, it doesn't affect
833           intermediate results, so that it is only partially effective.
834           `Excess precision' is avoided in code like:
835
836                   a = b + c
837                   d = a * e
838
839           but not in code like:
840
841                         d = (b + c) * e
842
843           For another, potentially better, way of controlling the precision,
844           see Floating-point precision.
845
846       -fforce-mem
847       -fforce-addr
848           Might improve optimization of loops.
849
850       -fno-inline
851           Don't compile statement functions inline.  Might reduce the size of
852           a program unit---which might be at expense of some speed (though it
853           should compile faster).  Note that if you are not optimizing, no
854           functions can be expanded inline.
855
856       -ffast-math
857           Might allow some programs designed to not be too dependent on IEEE
858           behavior for floating-point to run faster, or die trying.  Sets
859           -funsafe-math-optimizations, -ffinite-math-only, and
860           -fno-trapping-math.
861
862       -funsafe-math-optimizations
863           Allow optimizations that may be give incorrect results for certain
864           IEEE inputs.
865
866       -ffinite-math-only
867           Allow optimizations for floating-point arithmetic that assume that
868           arguments and results are not NaNs or +-Infs.
869
870           This option should never be turned on by any -O option since it can
871           result in incorrect output for programs which depend on an exact
872           implementation of IEEE or ISO rules/specifications.
873
874           The default is -fno-finite-math-only.
875
876       -fno-trapping-math
877           Allow the compiler to assume that floating-point arithmetic will
878           not generate traps on any inputs.  This is useful, for example,
879           when running a program using IEEE "non-stop" floating-point
880           arithmetic.
881
882       -fstrength-reduce
883           Might make some loops run faster.
884
885       -frerun-cse-after-loop
886       -fexpensive-optimizations
887       -fdelayed-branch
888       -fschedule-insns
889       -fschedule-insns2
890       -fcaller-saves
891           Might improve performance on some code.
892
893       -funroll-loops
894           Typically improves performance on code using iterative "DO" loops
895           by unrolling them and is probably generally appropriate for
896           Fortran, though it is not turned on at any optimization level.
897           Note that outer loop unrolling isn't done specifically; decisions
898           about whether to unroll a loop are made on the basis of its
899           instruction count.
900
901           Also, no `loop discovery'[1] is done, so only loops written with
902           "DO" benefit from loop optimizations, including---but not limited
903           to---unrolling.  Loops written with "IF" and "GOTO" are not
904           currently recognized as such.  This option unrolls only iterative
905           "DO" loops, not "DO WHILE" loops.
906
907       -funroll-all-loops
908           Probably improves performance on code using "DO WHILE" loops by
909           unrolling them in addition to iterative "DO" loops.  In the absence
910           of "DO WHILE", this option is equivalent to -funroll-loops but
911           possibly slower.
912
913       -fno-move-all-movables
914       -fno-reduce-all-givs
915       -fno-rerun-loop-opt
916           In general, the optimizations enabled with these options will lead
917           to faster code being generated by GNU Fortran; hence they are
918           enabled by default when issuing the g77 command.
919
920           -fmove-all-movables and -freduce-all-givs will enable loop
921           optimization to move all loop-invariant index computations in
922           nested loops over multi-rank array dummy arguments out of these
923           loops.
924
925           -frerun-loop-opt will move offset calculations resulting from the
926           fact that Fortran arrays by default have a lower bound of 1 out of
927           the loops.
928
929           These three options are intended to be removed someday, once loop
930           optimization is sufficiently advanced to perform all those
931           transformations without help from these options.
932
933   Options Controlling the Preprocessor
934       These options control the C preprocessor, which is run on each C source
935       file before actual compilation.
936
937       Some of these options also affect how g77 processes the "INCLUDE"
938       directive.  Since this directive is processed even when preprocessing
939       is not requested, it is not described in this section.
940
941       However, the "INCLUDE" directive does not apply preprocessing to the
942       contents of the included file itself.
943
944       Therefore, any file that contains preprocessor directives (such as
945       "#include", "#define", and "#if") must be included via the "#include"
946       directive, not via the "INCLUDE" directive.  Therefore, any file
947       containing preprocessor directives, if included, is necessarily
948       included by a file that itself contains preprocessor directives.
949
950   Options for Directory Search
951       These options affect how the cpp preprocessor searches for files
952       specified via the "#include" directive.  Therefore, when compiling
953       Fortran programs, they are meaningful when the preprocessor is used.
954
955       Some of these options also affect how g77 searches for files specified
956       via the "INCLUDE" directive, although files included by that directive
957       are not, themselves, preprocessed.  These options are:
958
959       -I-
960       -Idir
961           These affect interpretation of the "INCLUDE" directive (as well as
962           of the "#include" directive of the cpp preprocessor).
963
964           Note that -Idir must be specified without any spaces between -I and
965           the directory name---that is, -Ifoo/bar is valid, but -I foo/bar is
966           rejected by the g77 compiler (though the preprocessor supports the
967           latter form).  Also note that the general behavior of -I and
968           "INCLUDE" is pretty much the same as of -I with "#include" in the
969           cpp preprocessor, with regard to looking for header.gcc files and
970           other such things.
971
972   Options for Code Generation Conventions
973       These machine-independent options control the interface conventions
974       used in code generation.
975
976       Most of them have both positive and negative forms; the negative form
977       of -ffoo would be -fno-foo.  In the table below, only one of the forms
978       is listed---the one which is not the default.  You can figure out the
979       other form by either removing no- or adding it.
980
981       -fno-automatic
982           Treat each program unit as if the "SAVE" statement was specified
983           for every local variable and array referenced in it.  Does not
984           affect common blocks.  (Some Fortran compilers provide this option
985           under the name -static.)
986
987       -finit-local-zero
988           Specify that variables and arrays that are local to a program unit
989           (not in a common block and not passed as an argument) are to be
990           initialized to binary zeros.
991
992           Since there is a run-time penalty for initialization of variables
993           that are not given the "SAVE" attribute, it might be a good idea to
994           also use -fno-automatic with -finit-local-zero.
995
996       -fno-f2c
997           Do not generate code designed to be compatible with code generated
998           by f2c use the GNU calling conventions instead.
999
1000           The f2c calling conventions require functions that return type
1001           "REAL(KIND=1)" to actually return the C type "double", and
1002           functions that return type "COMPLEX" to return the values via an
1003           extra argument in the calling sequence that points to where to
1004           store the return value.  Under the GNU calling conventions, such
1005           functions simply return their results as they would in GNU
1006           C---"REAL(KIND=1)" functions return the C type "float", and
1007           "COMPLEX" functions return the GNU C type "complex" (or its
1008           "struct" equivalent).
1009
1010           This does not affect the generation of code that interfaces with
1011           the "libg2c" library.
1012
1013           However, because the "libg2c" library uses f2c calling conventions,
1014           g77 rejects attempts to pass intrinsics implemented by routines in
1015           this library as actual arguments when -fno-f2c is used, to avoid
1016           bugs when they are actually called by code expecting the GNU
1017           calling conventions to work.
1018
1019           For example, INTRINSIC ABS;CALL FOO(ABS) is rejected when -fno-f2c
1020           is in force.  (Future versions of the g77 run-time library might
1021           offer routines that provide GNU-callable versions of the routines
1022           that implement the f2c intrinsics that may be passed as actual
1023           arguments, so that valid programs need not be rejected when
1024           -fno-f2c is used.)
1025
1026           Caution: If -fno-f2c is used when compiling any source file used in
1027           a program, it must be used when compiling all Fortran source files
1028           used in that program.
1029
1030       -ff2c-library
1031           Specify that use of "libg2c" (or the original "libf2c") is
1032           required.  This is the default for the current version of g77
1033
1034           Currently it is not valid to specify -fno-f2c-library.  This option
1035           is provided so users can specify it in shell scripts that build
1036           programs and libraries that require the "libf2c" library, even when
1037           being compiled by future versions of g77 that might otherwise
1038           default to generating code for an incompatible library.
1039
1040       -fno-underscoring
1041           Do not transform names of entities specified in the Fortran source
1042           file by appending underscores to them.
1043
1044           With -funderscoring in effect, g77 appends two underscores to names
1045           with underscores and one underscore to external names with no
1046           underscores.  (g77 also appends two underscores to internal names
1047           with underscores to avoid naming collisions with external names.
1048           The -fno-second-underscore option disables appending of the second
1049           underscore in all cases.)
1050
1051           This is done to ensure compatibility with code produced by many
1052           UNIX Fortran compilers, including f2c which perform the same
1053           transformations.
1054
1055           Use of -fno-underscoring is not recommended unless you are
1056           experimenting with issues such as integration of (GNU) Fortran into
1057           existing system environments (vis-a-vis existing libraries, tools,
1058           and so on).
1059
1060           For example, with -funderscoring, and assuming other defaults like
1061           -fcase-lower and that j() and max_count() are external functions
1062           while my_var and lvar are local variables, a statement like
1063
1064                   I = J() + MAX_COUNT (MY_VAR, LVAR)
1065
1066           is implemented as something akin to:
1067
1068                   i = j_() + max_count__(&my_var__, &lvar);
1069
1070           With -fno-underscoring, the same statement is implemented as:
1071
1072                   i = j() + max_count(&my_var, &lvar);
1073
1074           Use of -fno-underscoring allows direct specification of user-
1075           defined names while debugging and when interfacing g77 code with
1076           other languages.
1077
1078           Note that just because the names match does not mean that the
1079           interface implemented by g77 for an external name matches the
1080           interface implemented by some other language for that same name.
1081           That is, getting code produced by g77 to link to code produced by
1082           some other compiler using this or any other method can be only a
1083           small part of the overall solution---getting the code generated by
1084           both compilers to agree on issues other than naming can require
1085           significant effort, and, unlike naming disagreements, linkers
1086           normally cannot detect disagreements in these other areas.
1087
1088           Also, note that with -fno-underscoring, the lack of appended
1089           underscores introduces the very real possibility that a user-
1090           defined external name will conflict with a name in a system
1091           library, which could make finding unresolved-reference bugs quite
1092           difficult in some cases---they might occur at program run time, and
1093           show up only as buggy behavior at run time.
1094
1095           In future versions of g77 we hope to improve naming and linking
1096           issues so that debugging always involves using the names as they
1097           appear in the source, even if the names as seen by the linker are
1098           mangled to prevent accidental linking between procedures with
1099           incompatible interfaces.
1100
1101       -fno-second-underscore
1102           Do not append a second underscore to names of entities specified in
1103           the Fortran source file.
1104
1105           This option has no effect if -fno-underscoring is in effect.
1106
1107           Otherwise, with this option, an external name such as MAX_COUNT is
1108           implemented as a reference to the link-time external symbol
1109           max_count_, instead of max_count__.
1110
1111       -fno-ident
1112           Ignore the #ident directive.
1113
1114       -fzeros
1115           Treat initial values of zero as if they were any other value.
1116
1117           As of version 0.5.18, g77 normally treats "DATA" and other
1118           statements that are used to specify initial values of zero for
1119           variables and arrays as if no values were actually specified, in
1120           the sense that no diagnostics regarding multiple initializations
1121           are produced.
1122
1123           This is done to speed up compiling of programs that initialize
1124           large arrays to zeros.
1125
1126           Use -fzeros to revert to the simpler, slower behavior that can
1127           catch multiple initializations by keeping track of all
1128           initializations, zero or otherwise.
1129
1130           Caution: Future versions of g77 might disregard this option (and
1131           its negative form, the default) or interpret it somewhat
1132           differently.  The interpretation changes will affect only non-
1133           standard programs; standard-conforming programs should not be
1134           affected.
1135
1136       -femulate-complex
1137           Implement "COMPLEX" arithmetic via emulation, instead of using the
1138           facilities of the gcc back end that provide direct support of
1139           "complex" arithmetic.
1140
1141           (gcc had some bugs in its back-end support for "complex"
1142           arithmetic, due primarily to the support not being completed as of
1143           version 2.8.1 and "egcs" 1.1.2.)
1144
1145           Use -femulate-complex if you suspect code-generation bugs, or
1146           experience compiler crashes, that might result from g77 using the
1147           "COMPLEX" support in the gcc back end.  If using that option fixes
1148           the bugs or crashes you are seeing, that indicates a likely g77
1149           bugs (though, all compiler crashes are considered bugs), so, please
1150           report it.  (Note that the known bugs, now believed fixed, produced
1151           compiler crashes rather than causing the generation of incorrect
1152           code.)
1153
1154           Use of this option should not affect how Fortran code compiled by
1155           g77 works in terms of its interfaces to other code, e.g. that
1156           compiled by f2c
1157
1158           As of GCC version 3.0, this option is not necessary anymore.
1159
1160           Caution: Future versions of g77 might ignore both forms of this
1161           option.
1162
1163       -falias-check
1164       -fargument-alias
1165       -fargument-noalias
1166       -fno-argument-noalias-global
1167           Version info: These options are not supported by versions of g77
1168           based on gcc version 2.8.
1169
1170           These options specify to what degree aliasing (overlap) is
1171           permitted between arguments (passed as pointers) and "COMMON"
1172           (external, or public) storage.
1173
1174           The default for Fortran code, as mandated by the FORTRAN 77 and
1175           Fortran 90 standards, is -fargument-noalias-global.  The default
1176           for code written in the C language family is -fargument-alias.
1177
1178           Note that, on some systems, compiling with -fforce-addr in effect
1179           can produce more optimal code when the default aliasing options are
1180           in effect (and when optimization is enabled).
1181
1182       -fno-globals
1183           Disable diagnostics about inter-procedural analysis problems, such
1184           as disagreements about the type of a function or a procedure's
1185           argument, that might cause a compiler crash when attempting to
1186           inline a reference to a procedure within a program unit.  (The
1187           diagnostics themselves are still produced, but as warnings, unless
1188           -Wno-globals is specified, in which case no relevant diagnostics
1189           are produced.)
1190
1191           Further, this option disables such inlining, to avoid compiler
1192           crashes resulting from incorrect code that would otherwise be
1193           diagnosed.
1194
1195           As such, this option might be quite useful when compiling existing,
1196           ``working'' code that happens to have a few bugs that do not
1197           generally show themselves, but which g77 diagnoses.
1198
1199           Use of this option therefore has the effect of instructing g77 to
1200           behave more like it did up through version 0.5.19.1, when it paid
1201           little or no attention to disagreements between program units about
1202           a procedure's type and argument information, and when it performed
1203           no inlining of procedures (except statement functions).
1204
1205           Without this option, g77 defaults to performing the potentially
1206           inlining procedures as it started doing in version 0.5.20, but as
1207           of version 0.5.21, it also diagnoses disagreements that might cause
1208           such inlining to crash the compiler as (fatal) errors, and warns
1209           about similar disagreements that are currently believed to not
1210           likely to result in the compiler later crashing or producing
1211           incorrect code.
1212
1213       -fflatten-arrays
1214           Use back end's C-like constructs (pointer plus offset) instead of
1215           its "ARRAY_REF" construct to handle all array references.
1216
1217           Note: This option is not supported.  It is intended for use only by
1218           g77 developers, to evaluate code-generation issues.  It might be
1219           removed at any time.
1220
1221       -fbounds-check
1222       -ffortran-bounds-check
1223           Enable generation of run-time checks for array subscripts and
1224           substring start and end points against the (locally) declared
1225           minimum and maximum values.
1226
1227           The current implementation uses the "libf2c" library routine
1228           "s_rnge" to print the diagnostic.
1229
1230           However, whereas f2c generates a single check per reference for a
1231           multi-dimensional array, of the computed offset against the valid
1232           offset range (0 through the size of the array), g77 generates a
1233           single check per subscript expression.  This catches some cases of
1234           potential bugs that f2c does not, such as references to below the
1235           beginning of an assumed-size array.
1236
1237           g77 also generates checks for "CHARACTER" substring references,
1238           something f2c currently does not do.
1239
1240           Use the new -ffortran-bounds-check option to specify bounds-
1241           checking for only the Fortran code you are compiling, not
1242           necessarily for code written in other languages.
1243
1244           Note: To provide more detailed information on the offending
1245           subscript, g77 provides the "libg2c" run-time library routine
1246           "s_rnge" with somewhat differently-formatted information.  Here's a
1247           sample diagnostic:
1248
1249                   Subscript out of range on file line 4, procedure rnge.f/bf.
1250                   Attempt to access the -6-th element of variable b[subscript-2-of-2].
1251                   Aborted
1252
1253           The above message indicates that the offending source line is line
1254           4 of the file rnge.f, within the program unit (or statement
1255           function) named bf.  The offended array is named b.  The offended
1256           array dimension is the second for a two-dimensional array, and the
1257           offending, computed subscript expression was -6.
1258
1259           For a "CHARACTER" substring reference, the second line has this
1260           appearance:
1261
1262                   Attempt to access the 11-th element of variable a[start-substring].
1263
1264           This indicates that the offended "CHARACTER" variable or array is
1265           named a, the offended substring position is the starting (leftmost)
1266           position, and the offending substring expression is 11.
1267
1268           (Though the verbage of "s_rnge" is not ideal for the purpose of the
1269           g77 compiler, the above information should provide adequate
1270           diagnostic abilities to it users.)
1271
1272       Some of these do not work when compiling programs written in Fortran:
1273
1274       -fpcc-struct-return
1275       -freg-struct-return
1276           You should not use these except strictly the same way as you used
1277           them to build the version of "libg2c" with which you will be
1278           linking all code compiled by g77 with the same option.
1279
1280       -fshort-double
1281           This probably either has no effect on Fortran programs, or makes
1282           them act loopy.
1283
1284       -fno-common
1285           Do not use this when compiling Fortran programs, or there will be
1286           Trouble.
1287
1288       -fpack-struct
1289           This probably will break any calls to the "libg2c" library, at the
1290           very least, even if it is built with the same option.
1291

ENVIRONMENT

1293       GNU Fortran currently does not make use of any environment variables to
1294       control its operation above and beyond those that affect the operation
1295       of gcc.
1296

BUGS

1298       For instructions on reporting bugs, see <http://gcc.gnu.org/bugs.html>.
1299       Use of the gccbug script to report bugs is recommended.
1300

FOOTNOTES

1302       1.  loop discovery refers to the process by which a compiler, or indeed
1303           any reader of a program, determines which portions of the program
1304           are more likely to be executed repeatedly as it is being run.  Such
1305           discovery typically is done early when compiling using optimization
1306           techniques, so the ``discovered'' loops get more attention---and
1307           more run-time resources, such as registers---from the compiler.  It
1308           is easy to ``discover'' loops that are constructed out of looping
1309           constructs in the language (such as Fortran's "DO").  For some
1310           programs, ``discovering'' loops constructed out of lower-level
1311           constructs (such as "IF" and "GOTO") can lead to generation of more
1312           optimal code than otherwise.
1313

SEE ALSO

1315       gpl(7), gfdl(7), fsf-funding(7), cpp(1), gcov(1), gcc(1), as(1), ld(1),
1316       gdb(1), adb(1), dbx(1), sdb(1) and the Info entries for gcc, cpp, g77,
1317       as, ld, binutils and gdb.
1318

AUTHOR

1320       See the Info entry for g77 for contributors to GCC and G77.
1321
1323       Copyright (c) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2004 Free
1324       Software Foundation, Inc.
1325
1326       Permission is granted to copy, distribute and/or modify this document
1327       under the terms of the GNU Free Documentation License, Version 1.2 or
1328       any later version published by the Free Software Foundation; with the
1329       Invariant Sections being ``GNU General Public License'' and ``Funding
1330       Free Software'', the Front-Cover texts being (a) (see below), and with
1331       the Back-Cover Texts being (b) (see below).  A copy of the license is
1332       included in the gfdl(7) man page.
1333
1334       (a) The FSF's Front-Cover Text is:
1335
1336            A GNU Manual
1337
1338       (b) The FSF's Back-Cover Text is:
1339
1340            You have freedom to copy and modify this GNU Manual, like GNU
1341            software.  Copies published by the Free Software Foundation raise
1342            funds for GNU development.
1343
1344
1345
1346gcc-3.4.6                         2018-02-08                            G77(1)
Impressum