GNU Fortran compiler: Difference between revisions
Line 60: | Line 60: | ||
You can ask your IT staff what the corresponding commands would be on your particular cluster. | You can ask your IT staff what the corresponding commands would be on your particular cluster. | ||
The <code>module</code> command should automatically define several environment variables: | |||
In order to tell GNU Fortran to use enough stacksize memory (which is needed to create local variables as well as temporary PRIVATE variables for OpenMP parallel loops), add the following line to your system startup file: | In order to tell GNU Fortran to use enough stacksize memory (which is needed to create local variables as well as temporary PRIVATE variables for OpenMP parallel loops), add the following line to your system startup file: |
Revision as of 16:58, 4 October 2016
On this page, we discuss compiling GEOS-Chem with the GNU Fortran compiler (aka gfortran
).
Overview
We have added several modifications to facilitate compiling GEOS-Chem with the GNU Fortran (aka gfortran
compiler). In the process, we have also corrected some coding issues that were flagged by GNU Fortran. These changes will be added to the v11-01 public release code.
GNU Fortran versions tested with GEOS-Chem
The GEOS-Chem Support Team has experimented using different versions of GNU Fortran to build GEOS-Chem. Here are our results.
Version | Machine | Status |
---|---|---|
gfortran 4.4.7 | odyssey.rc.fas.harvard.edu |
|
gfortran 4.8.2 | odyssey.rc.fas.harvard.edu |
|
gfortran 5.2.0 | odyssey.rc.fas.harvard.edu |
|
gfortran 6.1.0 | odyssey.rc.fas.harvard.edu |
|
--Bob Yantosca (talk) 15:48, 4 October 2016 (UTC)
Environment settings for GNU Fortran
On most Unix clusters, the module
command is used to load the GNU Fortran compiler library into your Unix enviroment, along with any related libraries (e.g. netCDF, OpenMPI). On the Harvard machine odyssey.rc.fas.harvard.edu
, these commands are used:
# These commands load GNU Fortran 4.8.2 module load gcc/4.8.2-fasrc01 openmpi/1.10.1-fasrc01 module load netcdf/4.3.3.1-fasrc02 netcdf-fortran/4.4.2-fasrc01
You can ask your IT staff what the corresponding commands would be on your particular cluster.
The module
command should automatically define several environment variables:
In order to tell GNU Fortran to use enough stacksize memory (which is needed to create local variables as well as temporary PRIVATE variables for OpenMP parallel loops), add the following line to your system startup file:
If you use bash. add this to your .bashrc file |
If you use csh or tcsh, add this to your .cshrc file |
---|---|
export OMP_STACKSIZE=500m
|
setenv OMP_STACKSIZE 500m
|
Although we are nominally telling OMP_STACKSIZE
to request 500 MB of memory, in practice, this means just to use the maximum amount of stack memory available on your system. The 500m
is just sufficiently large number that should be larger than the largest amount of stack memory on most systems. You can also experiment with different values if you wish.
--Bob Yantosca (talk) 16:43, 4 October 2016 (UTC)
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
|
-gdwarf-2
|
Tells the compiler to generate full debugging information using the DWARF-2 library standard. | DEBUG=yes
|
-gdwarf-2
|
Tells the compiler to strictly adhere to the DWARF-2 debugging library standard. | 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 |
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 gdwarf-2 -gstrict-dwarf -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) |
---|---|---|
carbon_mod.F |
GLOB_DARO2(I,J,L,:,JHC-5) = DELHC(:) . . . GLOB_DARO2(I,J,L,:,4) = DELHC(:) |
GLOB_DARO2(I,J,L,1:2,JHC-5) = DELHC(1:2) . . . GLOB_DARO2(I,J,L,1:2,4) = DELHC(1:2) # Now only copy the 1st 2 elements of DELHC # into GLOB_DARO2, which avoids an array-size mismatch |
convection_mod.F |
IF ( AER == .TRUE. ) THEN
|
IF ( AER ) THEN |
diag3.F |
(Input_Opt%LSKYRAD(2).EQ.TRUE.)) . . . (Input_Opt%LSKYRAD(1).EQ.TRUE.)) |
(Input_Opt%LSKYRAD(2).EQV.TRUE.)) . . . (Input_Opt%LSKYRAD(1).EQV.TRUE.)) |
diag_mod.F |
INTEGER, ALLOCATABLE :: AD71_COUNT
INTEGER, ALLOCATABLE :: AD71_HRCT
INTEGER, ALLOCATABLE :: AD71_LHR
INTEGER, ALLOCATABLE :: AD71_LDAY
|
INTEGER :: AD71_COUNT
INTEGER :: AD71_HRCT
INTEGER :: AD71_LHR
INTEGER :: AD71_LDAY
# Scalar variables cannot be declared ALLOCATABLE.
|
diag48_mod.F |
(Input_Opt%LSKYRAD(2).EQ.TRUE.)) . . . (Input_Opt%LSKYRAD(1).EQ.TRUE.)) |
(Input_Opt%LSKYRAD(2).EQV.TRUE.)) . . . (Input_Opt%LSKYRAD(1).EQV.TRUE.)) |
emissions_mod.F90 |
CALL EMISSCARBON( ... etc ... ) IF ( RC /= GC_SUCCESS ) RETURN |
IF ( Input_Opt%ITS_A_FULLCHEM_SIM .or. & Input_Opt%ITS_AN_AEROSOL_SIM ) THEN CALL EMISSCARBON( ... etc ... ) IF ( RC /= GC_SUCCESS ) RETURN ENDIF # Need to prevent EMISSCARBON from being called # for simulations without carbon aerosols |
flexchem_mod.F90 |
write(*,'(i,a3,a85)') D,' | ',EQN_NAMES(D) |
WRITE( 6, '(i8,a3,a85)' ) D,' | ',EQN_NAMES(D)
|
geosfp_read_mod.F90 |
INTEGER, SAVE :: first = .TRUE.
|
LOGICAL, SAVE :: first = .TRUE.
|
hcoi_gc_diagn_mod.F90 |
IF ( YesOrNo == .FALSE. ) THEN
|
IF ( YesOrNo .eqv. FALSE ) THEN
|
hcoi_gc_main_mod.F90 |
IF ( Input_Opt%LUCX /= LTMP ) THEN . . . IF ( Input_Opt%LSCHEM /= LTMP ) THEN . . . IF ( Input_Opt%LCHEM /=. LTMP .and. |
IF ( Input_Opt%LUCX .neqv. LTMP ) THEN . . . IF ( Input_Opt%LSCHEM .neqv. LTMP ) THEN . . . IF ( Input_Opt%LCHEM .neqv./ LTMP .and. |
input_mod.F |
READ( SUBSTRS(1:N), '(i)') CFCYEAR
. . .
write(MSG,'(I,a,L)') '<>', Input_Opt%TS_DYN, ...
. . .
Input_Opt%ND63_TRACERS(1:ND63) = TRACERS(1:N_ND63)
. . .
IF ( LCH4BUD .EQ. .TRUE. ) THEN
|
READ( SUBSTRS(1:N), '(i4)') CFCYEAR . . . write(MSG,'(I8,a,L)') '<>', Input_Opt%TS_DYN, ... . . . Input_Opt%ND63_TRACERS(1:N_ND63) = TRACERS(1:N_ND63) . . . IF ( LCH4BUD ) THEN |
isoropiaII_mod.F |
#IF !defined ( USE_REAL_8 ) HNO3_sav(I,J,L) = SNGL(HNO3_UGM3) #ELIF HNO3_sav(I,J,L) = HNO3_UGM3 #ENDIF |
#if !defined( USE_REAL_8 ) HNO3_sav(I,J,L) = SNGL(HNO3_UGM3) #else HNO3_sav(I,J,L) = HNO3_UGM3 #endif |
ocean_mercury_mod.F |
IF ( ND03 .and. NN == ID_Hg_tot )
|
IF ( ( ND03 > 0 ) .and. ( NN == ID_Hg_tot ) ) # Use parentheses to cast to LOGICAL type |
merra2_read_mod.F90 |
INTEGER, SAVE :: first = .TRUE.
|
LOGICAL, SAVE :: first = .TRUE.
|
ndxx_setup.F |
INTEGER :: IT_IS_A_CH3I_SIM INTEGER :: IT_IS_A_FULLCHEM_SIM INTEGER :: IT_IS_A_MERCURY_SIM INTEGER :: IT_IS_A_TAGO3_SIM INTEGER :: IT_IS_A_H2HD_SIM |
LOGICAL :: IT_IS_A_CH3I_SIM LOGICAL :: IT_IS_A_FULLCHEM_SIM LOGICAL :: IT_IS_A_MERCURY_SIM LOGICAL :: IT_IS_A_TAGO3_SIM LOGICAL :: IT_IS_A_H2HD_SIM |
ndxx_setup.F |
IF ( ALLOCATED( AD71_COUNT ) ) DEALLOCATE( AD71_COUNT )
IF ( ALLOCATED( AD71_HRCT ) ) DEALLOCATE( AD71_HRCT )
IF ( ALLOCATED( AD71_LDAY ) ) DEALLOCATE( AD71_LDAY )
IF ( ALLOCATED( AD71_LHR ) ) DEALLOCATE( AD71_LHR )
|
|
seasalt_mod.F |
IF (DMID(ID) .ge. R0*2e+0_fp .and. ...
& THEN
|
IF ( DMID(ID) .ge. R0*2e+0_fp .and.
& DMID(ID) .le. R1*2e+0_fp ) THEN
# Break IF statement into 2 lines
|
seasalt_mod.F |
IF ( LMPOA > 0 ) THEN
|
IF ( LMPOA ) THEN |
strat_chem_mod.F90 |
'A3O2', 'ACET', etc.
|
'A3O2 ', 'ACET ', etc.
# All strings in array constructors must
# have the same number of spaces
|
strat_chem_mod.F90 |
TYPE(BrPointers) :: BrPtrDay(6)
TYPE(BrPointers) :: BrPtrNight(6)
|
TYPE(BrPointers), POINTER :: BrPtrDay(:) TYPE(BrPointers), POINTER :: BrPtrNight(:) . . . ! BrPtrDay and BrPtrNight have to be allocated dynamically ! because they are pointers (bmy, 10/3/16) ALLOCATE( BrPtrDay ( 6 ), STAT=errCode ) ALLOCATE( BrPtrNight( 6 ), STAT=errCode ) . . . IF ( ASSOCIATED( BrPtrDay ) ) DEALLOCATE( BrPtrDay ) IF ( ASSOCIATED( BrPtrNight ) ) DEALLOCATE( BrPtrNight ) # Dynamically allocate the BrPtrDay and BrPtrNight arrays # so as to not have to declare them SAVEd. |
ucx_mod.F90 |
JDIF_OUT = SIND(JMAX_OUT)-SIND(JMIN_OUT) . . . JDIF_TMP = SIND(JMAX_TMP)-SIND(JMIN_TMP) |
USE PhysConstants, ONLY : PI_180 . . . JDIF_OUT = SIN( JMAX_OUT * PI_180 ) & - SIN( JMIN_OUT * PI_180 ) . . . JDIF_TMP = SIN( JMAX_TMP * PI_180 ) & - SIN( JMIN_TMP * PI_180 ) # Remove unsupported SIND function |
--Bob Yantosca (talk) 19:45, 28 September 2016 (UTC)
Modules in GeosUtil
Module | Code removed (in RED) | Code added (in GREEN) |
---|---|---|
error_mod.F |
#if defined( LINUX_IFORT ) |
#if defined( LINUX_IFORT ) || defined( LINUX_GFORTRAN )
|
geos_timers_mod.F |
IF ( (SavedTimers(TimerLoc)%ENABLED) .eq. .true.)
|
IF ( SavedTimers(TimerLoc)%ENABLED ) |
henry_coeffs_mod.F |
'H2O2', ! Jacob et al. 2000
'CH3I', ! Moore et al. 1995
'DMS', ! De Bruyn et al. 1995
'ACET' )/ ! Benkelberg et al 1995
|
'H2O2', ! Jacob et al. 2000 'CH3I', ! Moore et al. 1995 'DMS ', ! De Bruyn et al. 1995 'ACET' )/ ! Benkelberg et al 1995 # All strings in an array constructor # must have the same number of spaces |
--Bob Yantosca (talk) 19:13, 28 September 2016 (UTC)
Modules in Headers
Module | Code removed (in RED) | Code added (in GREEN) |
---|---|---|
input_opt_mod.F90 |
INTEGER :: LND51_HDF . . . INTEGER :: LND51b_HDF . . . INTEGER :: LWINDO_SE . . . INTEGER :: LWINDO_CU |
LOGICAL :: LND51_HDF . . . LOGICAL :: LND51b_HDF . . . LOGICAL :: LWINDO_SE . . . LOGICAL :: LWINDO_CU |
--Bob Yantosca (talk) 19:49, 28 September 2016 (UTC)
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
|
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
|
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 routine
# 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 #width 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 #width in a FORMAT statement. |
--Bob Yantosca (talk) 15:14, 29 September 2016 (UTC)
Known issues
Now us ASIN instead of obsolete function ASIND
In HEMCO module HEMCO/Extensions/hcox_paranox_mod.F90
, we had to replace the non-standard function ASIND (which returns the arcsine of an argument in degrees) with the ASIN function (which returns the arcsin in radians). The proper unit conversion was then applied.
The code in RED was deleted:
VARS(4) = ASIND( SC5(I,J) ) VARS(5) = ASIND( ExtState%SUNCOS%Arr%Val(I,J) )
And the code in GREEN was added:
VARS(4) = ASIN( SC5(I,J) ) / HcoState%Phys%PI_180 VARS(5) = ASIN( ExtState%SUNCOS%Arr%Val(I,J) ) / HcoState%Phys%PI_180
This modification does not cause any numerical differences in the output. All difference tests returned identical results.
--Bob Yantosca (talk) 21:00, 30 September 2016 (UTC)
Now use SIN instead of obsolete function SIND
In the UCX chemistry module GeosCore/ucx_mod.F
, we had to replace the non-standard function SIND (which returns the sine of an argument in degrees) with the SIN function (which returns the sine in radians). The argument was converted from degrees to radians before being passed to SIN.
The code in RED was deleted:
JDIF_OUT = SIND(JMAX_OUT)-SIND(JMIN_OUT) . . . JDIF_TMP = SIND(JMAX_TMP)-SIND(JMIN_TMP)
And the code in GREEN was added:
USE PhysConstants, ONLY : PI_180 . . . JDIF_OUT = SIN( JMAX_OUT * PI_180 ) & - SIN( JMIN_OUT * PI_180 ) . . . JDIF_TMP = SIN( JMAX_TMP * PI_180 ) & - SIN( JMIN_TMP * PI_180 )
This change causes very small numerical differences, at the level of numerical noise, only in the "Standard" and "UCX" chemical mechanisms. We attribute these differences to conversion between degrees and radians, probably with a different value of PI in each case.
--Bob Yantosca (talk) 21:14, 30 September 2016 (UTC)
THREADPRIVATE error in GNU Fortran 5 and higher
GNU Fortran v5 and higher seems to not like how the !$OMP THREADPRIVATE
statements in the ISORROPIA code are written. It does not let you place a COMMON
block name in an !$OMP THREADPRIVATE
statement. We are still looking into a workaround for this.
Bob Yantosca wrote:
I tried loading these modules on the holy2a81302 node of Odyssey:
Currently Loaded Modules: 1) git/2.1.0-fasrc01 5) gmp/6.1.1-fasrc02 9) openmpi/1.10.3-fasrc01 2) perl/5.10.1-fasrc04 6) mpfr/3.1.4-fasrc02 10) zlib/1.2.8-fasrc07 3) IDL/8.5.1-fasrc01 7) mpc/1.0.3-fasrc04 11) hdf5/1.8.12-fasrc12 4) ncl/6.1.2 8) gcc/6.1.0-fasrc01 12) netcdf/4.1.3-fasrc09
And then I tried to compile GEOS-Chem with Gfortran 6.1.0, but I got a bunch of these errors:
!$OMP THREADPRIVATE( /CASE/ ) Error: !$OMP THREADPRIVATE statement is not allowed inside of BLOCK DATA at (1) isrpia.inc:232:72:
This is occurring in a section of 3rd-party, legacy code that is not easily rewritten. I looked on the internet and found this forum on Openmp.org. So it appears that it is not an OpenMP problem, but Gfortran is being petty and pedantic here. Gfortran seems to be very unfriendly to legacy codes.
--Bob Yantosca (talk) 20:37, 28 September 2016 (UTC)
GNU Fortran 4.8 and higher is not compatible with Totalview
GNU Fortran 4.8 and higher versions save debugging information to disk using the DWARF library, version 4, by default. This makes code compiled with GNU Fortran incompatible with the Totalview debugger, version 8.8.0.1, which can only accept DWARF v2 or DWARF v3 input. The GEOS-Chem Support Team noticed this on our local computer cluster. We are still looking into a workaround for this.
--Bob Yantosca (talk) 21:39, 30 September 2016 (UTC)