Difference between revisions of "GNU Fortran compiler"

From Geos-chem
Jump to: navigation, search
(Modules in NcdfUtil)
(Modules in NcdfUtil)
Line 485: Line 485:
 
     READ( tUnit(L1:L2), <span style="color:green">'(i2)</span>', IOSTAT=STAT ) tMn  
 
     READ( tUnit(L1:L2), <span style="color:green">'(i2)</span>', IOSTAT=STAT ) tMn  
 
     READ( tUnit(L1:L2), <span style="color:green">'(i2)</span>', IOSTAT=STAT ) tSc
 
     READ( tUnit(L1:L2), <span style="color:green">'(i2)</span>', IOSTAT=STAT ) tSc
 
+
  <span style="color:green"># Gfortran cannot have a generic integer with in a FORMAT statement.</span>
+
    <span style="color:green"># Gfortran cannot have a generic integer with in a FORMAT statement.</span>
  
 
|-valign="top"
 
|-valign="top"

Revision as of 21:25, 26 September 2016

Page is under construction.jpg

Compilation options

The sections below contain useful information about the GNU Fortran compiler options that are used for GEOS-Chem.

Optimization options

Please see the Optimize Options section of the GNU Compiler Collection manual for detailed information about GNU Fortran's optimization settings.

The default GNU Fortran optimization settings for GEOS-Chem are: -O3 -funroll-loops.

--Bob Yantosca (talk) 22:01, 21 September 2016 (UTC)

Debugging options

Please see the Debugging Options section of the GNU Compiler Collection manual for detailed information about GNU Fortran's debugging settings.

--Bob Yantosca (talk) 20:16, 22 September 2016 (UTC)

List of commonly-used compilation options

Here are the GNU Fortran compilation options currently used by GEOS-Chem:

Option Description How invoked in GEOS-Chem?
Normal compiler settings
-cpp Turns on the C-preprocessor, to evaluate #if and #define statements in the source code. Default setting
-fautomatic This option places local variables (scalars and arrays of all types), except those declared as SAVE, on the run-time stack. It is as if the variables were declared with the AUTOMATIC attribute. It does not affect variables that have the SAVE attribute or ALLOCATABLE attribute, or variables that appear in an EQUIVALENCE statement or in a common block. Default setting
-fconvert-big-endian Specifies that the format will be big endian for integer data and big endian IEEE floating-point for real and complex data. This only affects file I/O to/from binary files (such as binary punch files) but not ASCII, netCDF, or other file formats. Default setting
-fno-align-commons Prevents the compiler from padding bytes anywhere in common blocks and structures. Padding can affect numerical precision. Default setting
-fopenmp Enables OpenMP parallelization commands. Default setting
-funroll-loops Typically improves performance on code using iterative DO loops by unrolling them and is probably generally appropriate for Fortran, though it is not turned on at any optimization level. Note that outer loop unrolling isn't done specifically; decisions about whether to unroll a loop are made on the basis of its instruction count.

Also, no `loop discovery' is done, so only loops written with DO benefit from loop optimizations, including—but not limited to—unrolling. Loops written with IF and GOTO are not currently recognized as such. This option unrolls only iterative DO loops, not DO WHILE loops.

Default setting
-O3 Performs nearly all supported optimizations that do not involve a space-speed tradeoff, plus a few more optimizations for function inlining and vectorization. For more information, please see the Optimize Options section of the GNU Compiler Collection manual. Default setting
-std=legacy Tells GNU Fortran not to halt compilation when encountering code that does not adhere to the Fortran 95, 2003, or 2008 standards. Gfortran is a much stricter compiler, so turning this option on will tell Gfortran to be more lenient. Default setting
-w Turns off most informational warnings. Default setting
Special compiler settings
-fdefault-real-8 This option tells the compiler to treat variables that are declared as REAL as REAL*8

NOTE: This option is not used globally, but is only applied to certain indidvidual files (mostly from third-party codes like ISORROPIA. Current GEOS-Chem programming practice is to use either REAL*4 or REAL*8 instead of REAL, which avoids confusion.

Used as needed
-freal-4-real-8 This option tells the compiler to treat variables that are declared as REAL as REAL*8

NOTE: This option is not used globally, but is only applied to certain indidvidual files (mostly from third-party codes like ISORROPIA. Current GEOS-Chem programming practice is to use either REAL*4 or REAL*8 instead of REAL, which avoids confusion.

Used as needed
-mcmodel=medium This option is used to tell Gfortran to use more than 2GB of static memory. This avoids a specific type of memory error that can occur if you compile GEOS-Chem for use with an extremely high-resolution grid (e.g. 0.25° x 0.3125° nested grid). Default setting
Settings only used for debugging
-fbacktrace This option tells the compiler to generate extra information in the object file to provide source file traceback information when a severe error occurs at run time. When the severe error occurs, source file, routine name, and line number correlation information is displayed along with call stack hexadecimal addresses (program counter trace). This option increases the size of the executable program, but has no impact on run-time execution speeds. It functions independently of the debug option. TRACEBACK=yes
-fcheck-array-temporaries Checks to see if any array temporaries are created. Depending on how you write your subroutine and function calls, the compiler may need to create a temporary array to hold the values in the array before it passes them to the subroutine. For detailed information, please see our Passing array arguments efficiently in GEOS-Chem wiki page. DEBUG=yes
-fcheck-bounds Check for array-out-of-bounds errors. This is invoked when you compile GEOS-Chem with the BOUNDS=yes Makefile option. NOTE: Only use this option -fcheck-bounds for debugging, as this option will cause GEOS-Chem to execute more slowly! BOUNDS=yes
-ffpe-trap=invalid,zero,overflow This option will cause GEOS-Chem to halt when floating-point errors are encountered. This can happen if an equation results in a denormal value, e.g. NaN, or +/-Infinity. Common causes of floating-point errors are divisions where the denominator becomes zero. FPE=yes
-finit-real-snan This option will set local automatic variables to a signaling NaN. This will make it easier for the compiler to detect undefined variables. FPE=yes
-g Tells the compiler to generate full debugging information in the object file. This will cause a debugger (like Totalview) to display the actual lines of source code, instead of hexadecimal addresses (which is gibberish to anyone except hardware engineers). DEBUG=yes
-O0 Turns off all optimization. Source code instructions (e.g. DO loops, IF blocks) and numerical expressions are evaluated in precisely the order in which they are listed, without being internally rewritten by the optimizer. This is necessary for using a debugger (like Totalview). DEBUG=yes
-Wall Enables some common compiler warnings that you probably would not enable out unless you were debugging. DEBUG=yes
-Warray-temporaries Warn about array temporaries generated by the compiler. The information generated by this warning is sometimes useful in optimization, in order to avoid

such temporaries. Used in conjunction with -fcheck-array-temporaries.

DEBUG=yes
-Wconversion Warn about implicit conversions that are likely to change the value of the expression after conversion. Implied by -Wall. DEBUG=yes
-Wextra -Wextra Enables some warning options for usages of language features which may be problematic. This currently includes -Wcompare-reals and -Wunused-parameter. DEBUG=yes

--Bob Yantosca (talk) 21:55, 21 September 2016 (UTC)

Typical settings for a GEOS-Chem simulation

The normal GEOS-Chem build uses the following Gfortran compiler flags:

-cpp -w -std=legacy -fautomatic -fno-align-commons -fconvert=big-endian -fno-range-check 
-fopenmp -mcmodel=medium -O3 -funroll-loops

whereas a debugging run (meant to execute in a debugger such as TotalView) will typically use these flags:

-cpp -w -std=legacy -fautomatic -fno-align-commons -fconvert=big-endian -fno-range-check 
-fopenmp -mcmodel=medium -g -O0 -Wall -Wextra -Warray-temporaries -Wconversion 
-fcheck-array-temporaries -fbounds-check -fbacktrace -ffpe-trap=invalid,zero,overflow, -finit-real=snan

--Bob Yantosca (talk) 20:15, 22 September 2016 (UTC)

Modifications made to GEOS-Chem for GNU Fortran

Module in GeosCore

Module Code removed (in RED) Code added (in GREEN)
hco_calc_mod.F90
IF ( UseConc /= Dct%Dta%IsConc ) THEN
IF ( UseConc .neqv. Dct%Dta%IsConc ) THEN

Modules in HEMCO/Core

Module Code removed (in RED) Code added (in GREEN)
hco_calc_mod.F90
IF ( UseConc /= Dct%Dta%IsConc ) THEN
IF ( UseConc .neqv. Dct%Dta%IsConc ) THEN

# Use .eqv. and .neqv. instead of == or /=
# when comparing LOGICAL variables directly.
hco_diagn_mod.F90
INTERFACE Diagn_Update
   MODULE PROCEDURE Diagn_UpdateSP
   MODULE PROCEDURE Diagn_UpdateDP
END INTERFACE

# Removed DiagnUpdateSP and DiagnUpdateDP
# which used OPTIONAL arguments
PRIVATE :: Diagn_UpdateSp0d
PRIVATE :: Diagn_UpdateSp0d
PRIVATE :: Diagn_UpdateSp2d
PRIVATE :: Diagn_UpdateSp3d
PRIVATE :: Diagn_UpdateDp0d
PRIVATE :: Diagn_UpdateDp2d
PRIVATE :: Diagn_UpdateDp3d
...
INTERFACE Diagn_Update
   MODULE PROCEDURE Diagn_UpdateSp0d
   MODULE PROCEDURE Diagn_UpdateSp2d
   MODULE PROCEDURE Diagn_UpdateSp3d
   MODULE PROCEDURE Diagn_UpdateDp0d
   MODULE PROCEDURE Diagn_UpdateDp2d
   MODULE PROCEDURE Diagn_UpdateDp3d
END INTERFACE

# Added new routines DiagnUpdateSp* and DiagUpdateDp*
# to avoid using OPTIONAL arguments in a MODULE INTERFACE
hco_interp_mod.F90
          WHERE ( REGFRACS > MAXFRACS ) 
             MAXFRACS = REGR_4D
             INDECES  = IVAL
          END WHERE 
#if defined( LINUX_GFORTRAN )
          DO T  = 1, NTIME
          DO L  = 1 ,NLEV
          DO J  = 1, HcoState%NY
          DO I2 = 1, HcoState%NX
            IF ( REGFRACS(I2,J,L,T) > MAXFRACS(I2,J,L,T) ) THEN
               MAXFRACS(I2,J,L,T) = REGR_4D(I2,J,L,T)
               INDECES (I2,J,L,T) = IVAL
            ENDIF
         ENDDO
         ENDDO
         ENDDO
         ENDDO
#else
         ! This code is preblematic in Gfortran.  Investigate rewriting
         ! it for IFORT with the DO loops (sde, bmy, 9/21/16)
         WHERE ( REGFRACS > MAXFRACS ) 
            MAXFRACS = REGR_4D
            INDECES  = IVAL
         END WHERE 
#endif
 
         # For now, rewrite the offending where statement as
         # individual DO loops.  Need to still test that this 
         # does not introduce any changes with ifort.
  
hco_unit_mod.F90
'1',             &
'count',         &
'unitless',      &
etc.
'1          ',   &
'count      ',   &
'unitless   ',   &
etc.
 
# All strings in array constructors must have the
# same # of spaces or else Gfortran chokes

--Bob Yantosca (talk) 18:21, 26 September 2016 (UTC)

Modules in HEMCO/Extensions

Module Code removed (in RED) Code added (in GREEN)
hcox_gfed_mod.F90
REAL(sp), POINTER   :: TmpPtr(:,:)  => NULL()
REAL(sp), POINTER   :: TmpPtr(:,:)
...
TmpPtr => NULL()

# Setting a pointer to NULL where it is declared
# turns the pointer into a SAVEd variable.
hcox_gfed_mod.F90
! Get pointers to GFED3 data
IF ( IsGFED3 ) THEN
   .... etc ...

! Get pointers to GFED4 data
ELSEIF ( IsGFED4 ) THEN
    ... etc ...
 
ENDIF

 ! Make sure HUMTROP does not exceed one
 WHERE ( HUMTROP > 1.0_sp ) 
    HUMTROP = 1.0_sp
 END WHERE
! Get pointers to GFED3 data
IF ( IsGFED3 ) THEN
   .... etc ...
	 
   ! Make sure HUMTROP does not exceed one
   WHERE ( HUMTROP > 1.0_sp ) 
      HUMTROP = 1.0_sp
   END WHERE

! Get pointers to GFED4 data
ELSEIF ( IsGFED4 ) THEN
   ... etc ...
ENDIF

# HUMTROP is only defined for GFED3, so the
# WHERE statement should go in the IfGFED3 block.
hcox_paranox_mod.F90
VARS(4) = ASIND( SC5(I,J) )
VARS(5) = ASIND( ExtState%SUNCOS%Arr%Val(I,J) )
VARS(4) = ASIN( SC5(I,J)                     ) / HcoState%Phys%PI_180
VARS(5) = ASIN( ExtState%SUNCOS%Arr%Val(I,J) ) / HcoState%Phys%PI_180

# ASIND is not supported in Gfortran.  Use ASIN instead to compute
# the arcsin and convert from degrees to radians manually.
hcox_seasalt_mod.F90
ALLOCATE ( NR  ( NSALT ), STAT=AS )
IF ( AS/=0 ) THEN
  CALL HCO_ERROR( 'Cannot allocate NR', RC )
  RETURN
ENDIF
SS_DEN = 2200.d0

ALLOCATE ( SS_DEN  ( NSALT ), STAT=AS ) 
ALLOCATE ( NR  ( NSALT ), STAT=AS )
IF ( AS/=0 ) THEN
  CALL HCO_ERROR( 'Cannot allocate NR', RC )
  RETURN
ENDIF
NR = 0

ALLOCATE ( SS_DEN  ( NSALT ), STAT=AS ) 

# Don't refer to SS_DEN before it is allocated

--Bob Yantosca (talk) 21:07, 26 September 2016 (UTC)

Modules in NcdfUtil

Module Code removed (in RED) Code added (in GREEN)
ncdf_mod.F90
 PRIVATE :: NC_VAR_WRITE_INT
 PRIVATE :: NC_VAR_WRITE_R4
 PRIVATE :: NC_VAR_WRITE_R8
 PRIVATE :: NC_VAR_WRITE_INT_1D
 PRIVATE :: NC_VAR_WRITE_INT_2D
 PRIVATE :: NC_VAR_WRITE_INT_3D
 PRIVATE :: NC_VAR_WRITE_INT_4D
 PRIVATE :: NC_VAR_WRITE_R4_1D
 PRIVATE :: NC_VAR_WRITE_R4_2D
 PRIVATE :: NC_VAR_WRITE_R4_3D
 PRIVATE :: NC_VAR_WRITE_R4_4D
 PRIVATE :: NC_VAR_WRITE_R8_1D
 PRIVATE :: NC_VAR_WRITE_R8_2D
 PRIVATE :: NC_VAR_WRITE_R8_3D
 PRIVATE :: NC_VAR_WRITE_R8_4D
 
 #Added separate, overloaded module for each combination
 # of array size and INT, REAL*4, REAL*8.  This avoids using
 # OPTIONAL arguments in overloaded routines, which Gfortran hates.
ncdf_mod.F90
 INTERFACE NC_VAR_WRITE
    MODULE PROCEDURE NC_VAR_WRITE_INT
    MODULE PROCEDURE NC_VAR_WRITE_R4
    MODULE PROCEDURE NC_VAR_WRITE_R8
 END INTERFACE NC_VAR_WRITE
 INTERFACE NC_VAR_WRITE
    MODULE PROCEDURE NC_VAR_WRITE_INT_1D
    MODULE PROCEDURE NC_VAR_WRITE_INT_2D
    MODULE PROCEDURE NC_VAR_WRITE_INT_3D
    MODULE PROCEDURE NC_VAR_WRITE_INT_4D
    MODULE PROCEDURE NC_VAR_WRITE_R4_1D
    MODULE PROCEDURE NC_VAR_WRITE_R4_2D
    MODULE PROCEDURE NC_VAR_WRITE_R4_3D
    MODULE PROCEDURE NC_VAR_WRITE_R4_4D
    MODULE PROCEDURE NC_VAR_WRITE_R8_1D
    MODULE PROCEDURE NC_VAR_WRITE_R8_2D
    MODULE PROCEDURE NC_VAR_WRITE_R8_3D
    MODULE PROCEDURE NC_VAR_WRITE_R8_4D
 END INTERFACE NC_VAR_WRITE

ncdf_mod.F90
   READ( tUnit(L1:L2), '(i)', IOSTAT=STAT ) tYr 
   READ( tUnit(L1:L2), '(i)', IOSTAT=STAT ) tMt
   READ( tUnit(L1:L2), '(i)', IOSTAT=STAT ) tDy
   READ( tUnit(L1:L2), '(i)', IOSTAT=STAT ) tHr
   READ( tUnit(L1:L2), '(i)', IOSTAT=STAT ) tMn
   READ( tUnit(L1:L2), '(i)', IOSTAT=STAT ) tSc
   READ( tUnit(L1:L2), '(i4)', IOSTAT=STAT ) tYr 
   READ( tUnit(L1:L2), '(i2)', IOSTAT=STAT ) tMt
   READ( tUnit(L1:L2), '(i2)', IOSTAT=STAT ) tDy
   READ( tUnit(L1:L2), '(i2)', IOSTAT=STAT ) tHr
   READ( tUnit(L1:L2), '(i2)', IOSTAT=STAT ) tMn 
   READ( tUnit(L1:L2), '(i2)', IOSTAT=STAT ) tSc

   # Gfortran cannot have a generic integer with in a FORMAT statement.
ncdf_mod.F90
 READ( TIMEUNIT(L1:L2), '(i)', IOSTAT=STAT ) YYYY
 READ( TIMEUNIT(L1:L2), '(i)', IOSTAT=STAT ) MM
 READ( TIMEUNIT(L1:L2), '(i)', IOSTAT=STAT ) DD
 READ( TIMEUNIT(L1:L2), '(i)', IOSTAT=STAT ) HH
 READ( TIMEUNIT(L1:L2), '(i4)', IOSTAT=STAT ) YYYY
 READ( TIMEUNIT(L1:L2), '(i2)', IOSTAT=STAT ) MM
 READ( TIMEUNIT(L1:L2), '(i2)', IOSTAT=STAT ) DD
 READ( TIMEUNIT(L1:L2), '(i2)', IOSTAT=STAT ) HH

 # Gfortran cannot have a generic integer with in a FORMAT statement.