GEOS-Chem v9-01-02

From Geos-chem
Revision as of 19:03, 2 March 2011 by Bmy (Talk | contribs) (Bug fixes for compatibility with the PGI compiler)

Jump to: navigation, search

Overview

BETA RELEASE -- Spring 2011

What's new in this version

GEOS-Chem v9-01-02 contains the following major updates and improvements:

  1. APM aerosol microphysics (F. Yu & G. Luo, SUNY Albany)
  2. Various emissions updates

Previous issues now resolved in v9-01-02

Patches from v9-01-01

The following patches that were issued after the release of GEOS-Chem v9-01-01 are now standardized in v9-01-02:

  1. Double counting of biofuel emissions over Asia
  2. Updated annual and monthly CO2 emissions from CDIAC

--Bob Y. 11:21, 1 March 2011 (EST)

Minor bug fixes in ISORROPIA II

Please see this wiki post for a description of two minor bug fixes that were implemented in source code file ISOROPIA/isorropiaIIcode.f. This bug does not affect the current GEOS-Chem ISORROPIA configuration, but may affect future development.

--Bob Y. 13:13, 1 March 2011 (EST)

Diagnostic updates

The following diagnostic updates have been implemented in v9-01-02:

  1. Fixes for inconsistencies in aerosol diagnostics
  2. The MERRA SEAICExx fields are now saved to the plane flight diagnostic.

--Bob Y. 13:13, 1 March 2011 (EST)

Bug fixes for compatibility with the PGI compiler

Gan Luo from SUNY/Albany pointed out several minor typos that cause the PGI compiler to choke when building the GEOS-Chem executable. These will all be fixed in v9-01-02.

(1) Line 303 of GeosCore/depo_mercury_mod.f:

Change this:
 #include 'define.h'

to this:
 #include "define.h"

(2) Line 169 of GeosCore/ocean_mercury_mod.f:

Change this:
 REAL*8, PARAMETER     :: Kd_part   = 10**(5.5)

to this:
 REAL*8, PARAMETER     :: Kd_part   = 10d0**(5.5d0)

(3) Line 1281 of GeosCore/ocean_mercury_mod.f:

Change this:
 HgPaq(I,J)   = MAX ( HgPaq(I,J) , 0.0 )

to this:
 HgPaq(I,J)   = MAX ( HgPaq(I,J) , 0d0 )

(4) In subroutine DO_MERRA_CONVECTION of convection_mod.f

Change this:
 REAL*8            :: ALPHA,       ALPHA2,   CLDBASE, CMFMC_BELOW

to this:
 INTEGER           :: CLDBASE
 REAL*8            :: CMFMC_BELOW, ALPHA,    ALPHA2

(5) In module vdiff_mod.f90: Several numerical constants had to be rewritten so that explicitly use "D" exponents. In other words:

Change numbers like these:
 1.
 1.e-12

to these:
 1.d0
 1.d-12

In short, the PGI compiler expects constants to agree strictly with the type of the variable that they are being assigned to (i.e. if A is a REAL*8, then you must use A = 1.0d0 instead of A = 1.0). IFORT will correct for this situation during compilation, but PGI will throw an error.

--Bob Y. 13:27, 2 March 2011 (EST)

Out-of-bounds error in readchem.f

It was discovered that the following code near the end of subroutine readchem.f:


                 ELSEIF ( J == MAPPL(ILBRO2H,NCS) .or.
    &                     J == MAPPL(ILBRO2N,NCS) .or.
    &                     J == MAPPL(ILTRO2H,NCS) .or.
    &                     J == MAPPL(ILTRO2N,NCS) .or.
    &                     J == MAPPL(ILXRO2H,NCS) .or.
    &                     J == MAPPL(ILXRO2N,NCS) ) THEN
                    ITS_NOT_A_ND65_FAMILY(J) = .FALSE.
                    EXIT

Will cause an out-of-bounds error if any of the IL*,indices are zero. This error manifested itself in a standard 43-tracer simulation.

We have corrected this error by first making sure that each IL* index is nonzero before doing the corresponding IF ( J = ... ) test:

                 ! Avoid out-of-bounds-errors by making sure that each
                 ! IL* index is nonzero before doing the IF test for J. 
                 ! (bmy, 3/1/11)
                 IF ( ILBRO2H > 0 ) THEN 
                    IF ( J == MAPPL(ILBRO2H,NCS) ) THEN
                       ITS_NOT_A_ND65_FAMILY(J) = .FALSE.
                       EXIT
                    ENDIF
                 ENDIF

                 ... etc ...

--Bob Y. 14:03, 2 March 2011 (EST)

Outstanding issues not yet resolved in v9-01-02

TBA