Passing array arguments efficiently in GEOS-Chem

From Geos-chem
Jump to: navigation, search

On this page we provide strategies to help you write GEOS-Chem code that passes arrays between subroutines in the most efficient manner.

Overview

In many areas of GEOS-Chem, we pass arrays as arguments from one routine to another. But if this is not done properly, it can cause GEOS-Chem to use an excessive amount of memory and take longer to run, especially at very fine resolutions. The following sections explain this issue in more depth:

Technical Description

This very technical description of how Fortran passes arrays to subroutines is taken from the Intel Fortran Compiler Version 11 Manual, p. 1628-1630:

In Fortran, there are two general types of array arguments:

  1. Explicit-shape arrays (introduced with Fortran 77); for example, A(3,4) and B(0:*)
    • These arrays have a fixed rank and extent that is known at compile time.
    • Other dummy argument (receiving) arrays that are not deferred-shape (such as assumed-size arrays) can be grouped with explicit-shape array arguments.
  2. Deferred-shape arrays (introduced with Fortran 95/90); for example, C(:.:)
    • Types of deferred-shape arrays include array pointers and allocatable arrays.
    • Assumed-shape array arguments generally follow the rules about passing deferred-shape array arguments.


When passing arrays as arguments, either the starting (base) address of the array or the address of an array descriptor is passed:

  1. When using explicit-shape (or assumed-size) arrays to receive an array, the starting address of the array is passed.
  2. When using deferred-shape (or assumed-shape) arrays to receive an array, the address of the array descriptor is passed (the compiler creates the array descriptor).


Passing an assumed-shape array or array pointer to an explicit-shape array can slow run-time performance. This is because the compiler needs to create an array temporary for the entire array. The array temporary is created because the passed array may not be contiguous and the receiving (explicit-shape) array requires a contiguous array. When an array temporary is created, the size of the passed array determines whether the impact on slowing run-time performance is slight or severe.


The following table summarizes what happens with the various combinations of array types. The amount of run-time performance inefficiency depends on the size of the array.


Dummy Argument Array Types (i.e. declared in the routine being called)
Actual Argument Array Type
(i.e. declared in the calling routine)
EXPLICIT-SHAPE ARRAYS DEFERRED-SHAPE and ASSUMED-SHAPE ARRAYS
EXPLICIT-SHAPE ARRAYS Result when using this combination: VERY EFFICIENT.
  • Does not use an array temporary.
  • Does not pass an array descriptor.
  • Interface block optional.
Result when using this combination: EFFICIENT.
  • Only allowed for assumed-shape arrays (not deferred-shape arrays).
  • Does not use an array temporary.
  • Passes an array descriptor.
  • Requires an interface block.
DEFERRED-SHAPE and ASSUMED-SHAPE ARRAYS Result when using this combination:
  • When passing an allocatable array, VERY EFFICIENT.
    • Does not use an array temporary.
    • Does not pass an array descriptor.
    • Interface block optional.
  • When not passing an allocatable array: NOT EFFICIENT.
    • Instead, use allocatable arrays whenever possible.
    • Uses an array temporary.
    • Does not pass an array descriptor.
    • Interface block optional.
Result when using this combination: EFFICIENT.
  • Requires an assumed-shape or array pointer as dummy argument.
  • Does not use an array temporary.
  • Passes an array descriptor.
  • Requires an interface block.

NOTE: Code that is contained within a Fortran MODULE construct will have interface blocks computed automatically. Otherwise you have use a Fortran INTERFACE statement to explicitly list the argument name and the sizes and types of each argument.

--Bob Y. 15:37, 6 June 2013 (EDT)

Description in plain English

The discussion in the preceding section is very technical. We attempt to explain it in more understandable terms below.

Allocatable arrays

Many arrays in GEOS-Chem are declared with the ALLOCATABLE attribute, such as:

  REAL*8, ALLOCATABLE :: XMID(:,:,:)

In this example, we tell the compiler to expect a 3-dimensional array named XMID. But we also tell the compiler not to give XMID any memory at compile time. Instead, we do this after GEOS-Chem has started executing by means of an ALLOCATE statement:

  ALLOCATE( XMID( IIPAR, JJPAR, LLPAR ), STAT=RC )
  IF ( RC /= 0 ) CALL ALLOC_ERR( 'XMID' )
  XMID = 0d0

The above statements tell the GEOS-Chem to make the XMID array XMID be of size (IIPAR, JJPAR, LLPAR), where these values have been declared elsewhere. We also check to make sure that there is enough memory before we give memory to XMID. You will see these statements in many modules of GEOS-Chem.

Derived-type objects

In GEOS-Chem v9-02k and higher versions, we have replaced many common allocatable arrays with fields from derived type objects. We did this to better enable GEOS-Chem to run within an external GCM, such as NASA's GEOS-5 GCM.

In particular:

  1. The State_Chm%Tracers field now replaces the STT array of advected tracers.
    • NOTE: State_Chm%Tracers was removed from v11-01 and higher versions.
  2. The State_Chm%Species field now replaces the CSPEC_FULL array of chemical species.
  3. The State_Met object replaces all GEOS-Chem met field arrays formerly contained in GeosCore/dao_mod.F.

State_Chm is a derived type object that holds information needed for GEOS-Chem's chemistry solver. A derived-type object is a "bucket-o-variables", where you can store scalar and array variables of different types (INTEGER, REAL*4, REAL*8, CHARACTER, etc.) in a single container. Similarly, State_Met gathers various meteorological parameters in a single construct.

One important thing to note is that the Fortran-90 standard requires array fields within a derived-type object to be declared with the POINTER attribute instead of with the ALLOCATABLE attribute, as you might otherwise expect. For this reason, fields in State_Chm and State_Met are declared as POINTER arrays. In other words, the declaration of these fields looks like this:

  TYPE ChmState
      ... etc ... 
     REAL*8, POINTER :: Tracers(:,:,:,:)
     REAL*8, POINTER :: Species(:,:,:,:)
      ... etc ...  
  END TYPE ChmState

  TYPE MetState
     ... etc ...
     REAL*8, POINTER :: UWND(:,:,:)
     REAL*8, POINTER :: VWND(:,:,:)
     ... etc ...
  END TYPE METSTATE

Using POINTER instead of ALLOCATABLE here may seem like a very insignificant distinction. In outward apperance, POINTER fields of derived type objects (such as State_Chm%Tracers) behave much in the same way as ALLOCATABLE arrays. But as you will see in the next couple of subsections, there are important consequences for the overall efficiency of GEOS-Chem.

Passing ALLOCATABLE arrays as arguments to other routines

GEOS-Chem contains a significant fraction of third-party routines, such as TPCORE, FAST-J, etc. These routines were often not originally intended to work with GEOS-Chem. As such, many of these routines accept inputs (such as the array of tracer concentrations) via the argument list. Prior to GEOS-Chem v9-02k, this would have looked like:

    SUBROUTINE MY_GC_SUB

    !-------------------------------------------------------
    ! Example GEOS-Chem routine that calls a 3rd-party code
    ! prior to v9-02k
    !--------------------------------------------------------
    USE CMN_SIZE_MOD,    ONLY : IIPAR, JJPAR, LLPAR  ! Dimensions
    USE TRACER_MOD,      ONLY : STT                  ! Tracer array
    USE TRACER_MOD,      ONLY : N_TRACERS            ! # of tracers
    USE THIRD_PARTY_MOD, ONLY : THIRD_PARTY_SUB      ! 3rd-party routine

    ... etc ...
 
    ! Call another subroutine
    CALL THIRD_PARTY_SUB( IIPAR, JJPAR, LLPAR, N_TRACERS, STT )

    ... etc ...

    END SUBROUTINE MY_GC_SUB

    . . .

    MODULE THIRD_PARTY_MOD

    CONTAINS 

      SUBROUTINE THIRD_PARTY_SUB( IX, JX, LX, NX, Q )

      !------------------------------------------------------------
      ! Example 3rd-party routine that gets called from GEOS-Chem 
      !------------------------------------------------------------

      ! Arguments
      INTEGER, INTENT(IN) :: IX, JX, LX, NX
      REAL*8,  INTENT(IN) :: Q(IX,JX,LX,NX)

      ... etc ...

      END SUBROUTINE THIRD_PARTY_SUB

    END THIRD_PARTY_MOD

From the table in the preceding section, we see that we have the following situation:

  • Array in calling routine: Deferred-shape, allocatable array (STT)
  • Array in called routine: Explicit-shape array (Q)
  • Result: VERY EFFICIENT.

Execution is very efficient because GEOS-Chem does not have to make a duplicate copy of STT when calling the subroutine. This saves both memory and CPU cycles.

Passing POINTER arrays as arguments to other routines

Now look what happens in GEOS-Chem v9-02k and later versions, where STT is now replaced with the pointer field State_Chm%Tracers:

    SUBROUTINE MY_GC_SUB( Input_Opt, State_Chm )

    !--------------------------------------------------------
    ! Example GEOS-Chem routine that calls a 3rd-party code
    ! v9-02k and later versions
    !--------------------------------------------------------
    USE CMN_SIZE_MOD,       ONLY : IIPAR, JJPAR, LLPAR  ! Dimensions
    USE GIGC_Input_Opt_Mod, ONLY : OptInput             ! Derived type for Input_Opt           
    USE GIGC_State_Chm_Mod, ONLY : ChmState             ! Derived type for State_Chm
    USE THIRD_PARTY_MOD,    ONLY : THIRD_PARTY_SUB      ! 3rd-party routine

    ! Arguments
    TYPE(OptInput), INTENT(IN)    :: Input_Opt   ! Input Options object
    TYPE(ChmState,  INTENT(INOUT) :: State_Chm   ! Chemistry State object

    ! Local variables
    INTEGER :: N_TRACERS

    ... etc ...
 
    N_TRACERS = Input_Opt%N_TRACERS

    ! Call another subroutine
    CALL THIRD_PARTY_SUB( IIPAR, JJPAR, LLPAR, N_TRACERS, State_Chm%Tracers )

    ... etc ...

    END SUBROUTINE MY_GC_SUB

    . . .

    MODULE THIRD_PARTY_MOD

    CONTAINS 

      SUBROUTINE THIRD_PARTY_SUB( IX, JX, LX, NX, Q )

      !------------------------------------------------------------
      ! Example 3rd-party routine that gets called from GEOS-Chem 
      !------------------------------------------------------------

      ! Arguments
      INTEGER, INTENT(IN) :: IX, JX, LX, NX
      REAL*8,  INTENT(IN) :: Q(IX,JX,LX,NX)

      ... etc ...

      END SUBROUTINE THIRD_PARTY_SUB

    END THIRD_PARTY_MOD

Referring to the above table, we see that we have this situation:

  • Array in calling routine: Deferred-shape array, but NOT ALLOCATABLE (State_Chm%Tracers is a POINTER)
  • Array in called routine: Explicit-shape array (Q)
  • Result: NOT EFFICIENT.

In this case, GEOS-Chem must copy the values of State_Chm%Tracers into an internal temporary array (also known as an array temporary) and then pass that to the subroutine. The larger the size of State_Chm%Tracers, the larger the array temporary will have to be, and the more memory and CPU cycles will be wasted. If array temporaries are being created for multiple arguments within the same subroutine call, this can cause GEOS-Chem to either run out of available memory or to take exceedingly long to execute.

Caveat: Now that GEOS-Chem is making more use of derived-type objects, we will need to be extra careful to prevent problems like these from occurring.

--Bob Y. 15:46, 6 June 2013 (EDT)

Correcting inefficient array argument passing in GEOS-Chem

In this section we provide information about diagnosing when array temporaries are created, and also how to restructure your code that you can avoid them.

Diagnosing with Intel Fortran Compiler

If you are using the Intel Fortran Compiler, you can check if array temporaries are being created with the compiler switch -check arg_temp_created. For your debugging runs, you can add this onto the FFLAGS section in the Makefile_header.mk file. Change this section of code:

# Pick compiler options for debug run or regular run 
ifdef DEBUG
FFLAGS    := -cpp -w -O0 -auto -noalign -convert big_endian -g -DDEBUG
else
FFLAGS    := -cpp -w $(OPT) -auto -noalign -convert big_endian -vec-report0 
endif

to this:

# Pick compiler options for debug run or regular run 
ifdef DEBUG
FFLAGS    := -cpp -w -O0 -auto -noalign -convert big_endian -g -DDEBUG -check arg_temp_created
else
FFLAGS    := -cpp -w $(OPT) -auto -noalign -convert big_endian -vec-report0 
endif

Then recompile your code as follows:

make realclean
make -j4 DEBUG=yes

This will build run-time checking for array temporaries into the GEOS-Chem executable. If there are any array temporaries, you will see output such as:

forrtl: warning (402): fort: (1): In call to THIRD_PARTY_MOD^THIRD_PARTY_SUB, an array temporary was created for argument #5

--Bob Y. 15:57, 6 June 2013 (EDT)

Preventing array temporaries

In many cases, you can prevent an array temporary from being created by converting a dummy argument from an explicit-shape array to a deferred-shape array. From our above example, we can do this by changing the argument type from explicit-shape to deferred shape, as shown below:

    ! Subroutine call from previous example (GEOS-Chem v9-02k and later)
    CALL THIRD_PARTY_SUB( IIPAR, JJPAR, LLPAR, N_TRACERS, State_Chm%TRACERS )

    . . .

    MODULE THIRD_PARTY_MOD
      
      CONTAINS

      SUBROUTINE THIRD_PARTY_SUB( IX, JX, LX, NX, Q )

      !-----------------------------------
      ! Example 3rd-party routine 
      ! that gets called from GEOS-Chem 
      !-----------------------------------

      ! Arguments     
      !------------------------------------------------------
      !%%%% NOTE: CHANGING THIS AVOIDS AN ARRAY TEMPORARY!!!
      !REAL*8,  INTENT(IN) :: Q(IX,JX,LX,NX)
      !------------------------------------------------------
      REAL*8,  INTENT(IN) :: Q(:,:,:,:)

      ! Local variables
      !%%% NOTE: Define local values for array dimensions      
      INTEGER             :: IX, JX, LX, NX

      !%%% NOTE: If we need to refer to the dimensions of Q w/in this routine,
      !%%% we can use the Fortran SIZE function to return these values.
      IX = SIZE( Q, 1 )
      JX = SIZE( Q, 2 )
      LX = SIZE( Q, 3 )
      NX = SIZE( Q, 4 )

      ... etc ...

      END SUBROUTINE THIRD_PARTY_SUB

    END MODULE THIRD_PARTY_MOD

Then we will have the following situation:

  • Array in calling routine: Deferred-shape array, but NOT ALLOCATABLE (State_Chm%Tracers is a POINTER)
  • Array in called routine: Deferred-shape array (Q)
  • Result: EFFICIENT.

If you do not have permission to modify the subroutine THIRD_PARTY_SUB (i.e. if it comes from an external source that is not maintained by you), then this is the best you can expect. But if you are not afraid of hacking into someone else's code, you may get more bang for your buck if you rewrite the subroutine to accept the entire derived type object. For example:

    ! Now pass entire derived-type object from GEOS-Chem to 3rd-party routine
    CALL THIRD_PARTY_SUB( State_Chm )

    . . . 

    MODULE THIRD_PARTY_MOD

    CONTAINS

      SUBROUTINE THIRD_PARTY_SUB( State_Chm )
 
      !-----------------------------------
      ! Example 3rd-party routine 
      ! that gets called from GEOS-Chem 
      !-----------------------------------
      USE GIGC_State_Chm_Mod, ONLY : ChmState

      ! Arguments
      TYPE(ChmState), INTENT(INOUT) :: State_Chm
      
      ! Local variables
      !%%% NOTE: Define local values for array dimensions       
      INTEGER         :: IX, JX, LX, NX

      !%%% NOTE: Define Q as a local pointer array instead
      !%%% of having it be an input argument
      REAL*8, POINTER :: Q(:,:,:,:)

      ... etc ...

      !%%% NOTE: Point Q to State_Chm%Tracers
      !%%% This allows us to keep all other references 
      !%%% to Q in the code below untouched
      Q => State_Chm%Tracers
     
      !%%% NOTE: If we need to refer to the dimensions of Q w/in this routine,
      !%%% we can use the Fortran SIZE function to return these values
      IX = SIZE( Q, 1 )
      JX = SIZE( Q, 2 )
      LX = SIZE( Q, 3 )
      NX = SIZE( Q, 4 )

      ... etc ...

      !%%% NOTE: Free pointer memory before exiting subroutine
      NULLIFY( Q )

      END SUBROUTINE THIRD_PARTY_SUB

In the above example, we have totally eliminated passing a pointer array as an argument to a subroutine. We now pass the entire derived-type object State_Chm, so that within the subroutine we can access any of its fields. Actually, GEOS-Chem will pass a reference to State_Chm to the subroutine, so that it does not have to make a duplicate copy of it. This is very efficient.

Furthermore, note that within THIRD_PARTY_SUB, we can point to State_Chm%Tracers with locally-defined POINTER arrays. This is much more efficient than trying to pass State_Chm%Tracers via the argument list.

--Bob Y. 16:41, 6 June 2013 (EDT)

Array temporaries corrected in GEOS-Chem v9-02

In GEOS-Chem v9-02k, we have eliminated several inefficient subroutine calls that were creating array temporaries. The following table shows the performance of several recent GEOS-Chem 1-month benchmark simulations (4° x 5° with GEOS-5.2.0 meteorology). Each simulation used version 11.1.069 of the Intel Fortran Compiler and ran on 8 CPUs of bench@titan-11.as.harvard.edu (2.659 GHz x 8 CPU), so this is an "apples-to-apples" comparison.

1-month benchmark Date approved Wall clock time (hh:mm) Scalability (8.0 is ideal)
GEOS-Chem v9-02l 26 Jun 2013 02:35 7.3577
GEOS-Chem v9-02k 07 Jun 2013 02:30 7.4285
GEOS-Chem v9-02j 28 May 2013 03:05 6.2866
GEOS-Chem v9-02i 17 May 2013 03:06 6.2832

As you can see, with v9-02k we achieved a savings of 1/2 hour per model month as compared to the two prior benchmark simulations. This translates to a savings of 6 hours per model year at 4° x 5° resolution. Also, the scalability—a measure of how efficiently the code parallelizes across multiple CPUs—increased from 6.2 to 7.4. The next benchmark after that, v9-02l, has a similar run time and scalability as v9-02k.

We list below the source code modifications that we made in v9-02k and v9-02l. Feel free to add these changes to your research codes.

--Bob Y. 13:12, 13 June 2013 (EDT)

bromocarb_mod.F

Modifications added in GEOS-Chem v9-02k

The following code was removed from GEOS-Chem v10-01 and higher versions. The HEMCO emissions component now handles all emissions of bromine species.

In routine INIT_BROMOCARB, modify these subroutine calls:

      call NcRd( ARRAY2x25, fileID, 'CHBr3_emission', 
     &           (/ 1, 1 /),  (/ 144, 91 /) )
      . . .
      call NcRd( ARRAY2x25, fileID, 'CH2Br2_emission',
     &           (/ 1, 1 /),  (/ 144, 91 /) )

so that they accept the st2d, ct2d arguments.

      INTEGER            :: st2d(2)
      INTEGER            :: ct2d(2)
      . . .
      ! Start and count arrays for netCDF reads
      st2d = (/ 1,   1  /)
      ct2d = (/ 144, 91 /)
      . . .        
      call NcRd( ARRAY2x25, fileID, 'CHBr3_emission', st2d, ct2d )
      . . .
      call NcRd( ARRAY2x25, fileID, 'CH2Br2_emission', st2d, ct2d )

--Bob Y. 15:04, 10 June 2013 (EDT)

tpcore_fvdas_mod.F90

Modifications added in GEOS-Chem v9-02k. This update is included in Adjoint v35a.

In routine TPCORE_FVDAS, rewrite the following argument definitions:

!----------------------------------------------------------------------------
! Prior to 6/4/13:
! Now use assumed-shape declaration for U (bmy, 6/4/13)
!   REAL*8,  INTENT(IN)    :: u(IM,JFIRST:JLAST,KM)
!----------------------------------------------------------------------------
    REAL*8,  INTENT(IN)    :: u(:,:,:)
    . . . . . .
!----------------------------------------------------------------------------
! Prior to 6/4/13:
! Now use assumed-shape declaration for XMASS, YMASS (bmy, 6/4/13)
!   REAL*8,  INTENT(IN)    :: XMASS(IM,JM,KM)
!   REAL*8,  INTENT(IN)    :: YMASS(IM,JM,KM)
!----------------------------------------------------------------------------
    REAL*8,  INTENT(IN)    :: XMASS(:,:,:)
    REAL*8,  INTENT(IN)    :: YMASS(:,:,:)
    . . . . . .
!----------------------------------------------------------------------------
! Prior to 6/4/13:
! Now use assumed-shape declaration for V (bmy, 6/4/13)
!    REAL*8,  INTENT(INOUT) :: v(IM, JFIRST-MG:JLAST+MG, KM)
!----------------------------------------------------------------------------
    REAL*8,  INTENT(INOUT) :: v(:,:,:)
    . . . . . .
!----------------------------------------------------------------------------
! Prior to 6/4/13:
! Now use assumed-shape declaration for Q (bmy, 6/4/13)
!    REAL*8,  INTENT(INOUT) :: q(IM, JFIRST-NG:JLAST+NG, KM, NQ)
!----------------------------------------------------------------------------
    REAL*8,  INTENT(INOUT), TARGET :: q(:,:,:,:)

Then add local pointer array:

   ! Add pointer to avoid array temporary in call to FZPPM (bmy, 6/5/13)
   REAL*8,  POINTER   :: ptr_Q(:,:,:)

Then make ptr_Q PRIVATE to the OMP loop:

!--------------------------------------------------------
! For time optimization : we parallelize over tracers and
! we loop over the levels outside horizontal transport 
! subroutines. (ccc, 4/1/09)
!--------------------------------------------------------
!$OMP PARALLEL DO        &
!$OMP DEFAULT( SHARED   )&
!$OMP PRIVATE( IQ, IK, adx, ady, qqu, qqv, dq1, ptr_Q )
    do iq = 1, nq

Then modify the call to FZPPM as follows:

      ! Set up temporary pointer to Q to avoid array temporary in FZPPM
      ! (bmy, 6/5/13)
      ptr_Q => q(:,:,:,iq)

     ! ==========
       call Fzppm  &
     ! ==========
!-----------------------------------------------------------------------------
! Prior to 6/5/13:
! Now pass ptr_Q to avoid creating an array temporary in FZPPM.
! This array temporary was found with -check arg_temp_created (bmy, 6/5/13)
!            (klmt, delp1, wz, dq1, q(:,:,:,iq), fz(:,:,:,iq), &
!-----------------------------------------------------------------------------
            (klmt, delp1, wz, dq1, ptr_Q, fz(:,:,:,iq), &
            j1p, 1, jm, 1, im, 1, jm, &
            im, km, 1, im, 1, jm, 1, km)
         
       ! Free pointer memory (bmy, 6/5/13)
       NULLIFY( ptr_Q )

--Bob Y. 09:40, 11 June 2013 (EDT)

tpcore_geos5_window_mod.F90 and tpcore_geos57_window_mod.F90

Modifications added in GEOS-Chem v9-02k. This update is included in Adjoint v35a.

Identical modfications are made in both:

  • Routine TPCORE_GEOS5_WINDOW (in tpcore_geos5_window_mod.F90)
  • Routine TPCORE_GEOS57_WINDOW (in tpcore_geos57_window_mod.F90)

Modify arguments:

!------------------------------------------------------------------------------
! Prior to 6/4/13:
! Now use assumed shape declarations for U, V (bmy, 6/4/13)
! real, intent(in):: u(im,jfirst:jlast,km) ! u-wind (m/s) at mid-time-level (t=t+dt/2)
! real, intent(inout):: v(im,jfirst-mg:jlast+mg,km) ! v-wind (m/s) at mid-time-level (t=t+dt/2)
!------------------------------------------------------------------------------
 real, intent(in):: u(:,:,:)    ! u-wind (m/s) at mid-time-level (t=t+dt/2)
 real, intent(inout):: v(:,:,:) ! v-wind (m/s) at mid-time-level (t=t+dt/2)
 . . . . . .
!------------------------------------------------------------------------------
! Prior to 6/4/13:
! Now use assumed-shape declaration for Q (bmy, 6/4/13)
! real, intent(inout):: q(im,jfirst-ng:jlast+ng,km,nq)  ! Tracer "mixing ratios"
!------------------------------------------------------------------------------
 real, intent(inout):: q(:,:,:,:)
 . . . . . .
!------------------------------------------------------------------------------
! Prior to 6/4/13:
! Now use assumed-shape declaration for XMASS, YMASS (bmy, 6/4/13)
! REAL,    INTENT(IN)    :: XMASS(IM,JM,KM), YMASS(IM,JM,KM)
!------------------------------------------------------------------------------
 REAL,    INTENT(IN)    :: XMASS(:,:,:), YMASS(:,:,:)

Then modify calls to routine XPAVG as follows:

  if ( jfirst == 1 ) then
!-----------------------------------------------------------------------------
! Prior to 6/4/13:
! Use psg(:,jm,1) and psg(:,jm,2) to pass a longitude slice (bmy, 6/4/13)
!       call xpavg(psg(1,1,1), im)
!       call xpavg(psg(1,1,2), im)
!-----------------------------------------------------------------------------
       call xpavg(psg(:,1,1), im)
       call xpavg(psg(:,1,2), im)
  endif

  if ( jlast == jm ) then
!-----------------------------------------------------------------------------
! Prior to 6/4/13:
! Use psg(:,jm,1) and psg(:,jm,2) to pass a longitude slice (bmy, 6/4/13)
!       call xpavg(psg(1,jm,1), im)
!       call xpavg(psg(1,jm,2), im)
!-----------------------------------------------------------------------------
       call xpavg(psg(:,jm,1), im)
       call xpavg(psg(:,jm,2), im)
  endif

and again:

  ! Average q at both poles
  do iq=1,nq
!$omp parallel do   &
!$omp shared(im)    &
!$omp private(k)
     do k=1,km
        if ( jfirst == 1 ) then
!-----------------------------------------------------------------------------
! Prior to 6/4/13:
! Use q(:,1,k,iq) to pass a longitude slice (bmy, 6/4/13)
!             call xpavg(q(1,1,k,iq), im)
!-----------------------------------------------------------------------------
             call xpavg(q(:,1,k,iq), im)
        endif
        if ( jlast == jm ) then
!-----------------------------------------------------------------------------
! Prior to 6/4/13:
! Use q(:,jm,k,iq) to pass a longitude slice (bmy, 6/4/13)
!             call xpavg(q(1,jm,k,iq), im)
!-----------------------------------------------------------------------------
             call xpavg(q(:,jm,k,iq), im)
        endif
     enddo
  enddo

--Bob Y. 15:06, 10 June 2013 (EDT)

CHECK_VALUE

Modifications added in GEOS-Chem v9-02l. This update is included in Adjoint v35a.

In GeosUtil/error_mod.F, we have made the following changes:

1) In CHECK_REAL_VALUE and CHECK_DBLE_VALUE, modify the character arguments accordingly:

!------------------------------------------------------------------------------
! Prior to 6/10/13:
! Avoid array temporaries (bmy, 6/10/13)
!      CHARACTER(LEN=*), INTENT(IN) :: VARNAME      ! Name of variable
!      CHARACTER(LEN=*), INTENT(IN) :: MESSAGE      ! Short descriptive msg
!------------------------------------------------------------------------------
      CHARACTER(LEN=255), INTENT(IN) :: VARNAME      ! Name of variable
      CHARACTER(LEN=255), INTENT(IN) :: MESSAGE      ! Short descriptive msg

This will avoid an array temporary from being created when a character string is passed to a dummy argument of type CHARACTER(LEN=*).

(Sidebar note: CHECK_REAL_VALUE and CHECK_DBLE_VALUE are overloaded by module interface CHECK_VALUE. This means that if you call CHECK_VALUE with a REAL*4 value for VARNAME, it will pass execution to CHECK_REAL_VALUE. Similarly, if you pass a REAL*8 value to VARNAME, then execution will pass to CHECK_DBLE_VALUE.)

2) Modify all places in the code that call CHECK_VALUE, in these files:

  1. GeosCore/calcrate.F
  2. GeosCore/h2_hd_mod.F
  3. GeosCore/tagged_co_mod.F
  4. GeosUtil/pressure_mod.F

using the following pattern:

       ! Avoid array temporaries in CHECK_VALUE
       INTEGER            :: ERR_LOC(4)
       CHARACTER(LEN=255) :: ERR_VAR
       CHARACTER(LEN=255) :: ERR_MSG

       . . .

       ! Error check
       ERR_LOC = (/ I, J, L, N /)
       ERR_VAR = 'STT'
       ERR_MSG = 'STOP at tagged_co_mod:7'
       CALL CHECK_VALUE( STT(I,J,L,N), ERR_LOC
      &                  ERR_VAR,      ERR_MSG  )

You can change the values of ERR_LOC, ERR_VAR, and ERR_MSG accordingly.

--Bob Y. 13:19, 13 June 2013 (EDT)

strat_chem_mod.F90

Modifications added in GEOS-Chem v9-02l. This update is included in Adjoint v35a.

The following code was removed. HEMCO now handles file I/O for the GMI stratospheric chemistry module in GEOS-Chem v10-01 and higher versions.

We replaced 3 calls to the NcRd routine, which have the pattern:

    ! Arrays 
    INTEGER :: st4d(4)
    INTEGER :: ct4d(4)

    . . .

    !------------------------------------------------------------------------
    ! NOTE: Replace this call to NcRd, and others like it:
    ! call NcRd( array, fileID, 'species',                      &
    !                            (/     1,     1,     1,  m /), & ! Start
    !                            (/ iipar, jjpar, lglob,  1 /)  ) ! Count
    !------------------------------------------------------------------------
    st4d = (/     1,     1,     1,  M /)                  ! Start
    ct4d = (/ IIPAR, JJPAR, LGLOB,  1 /)                  ! Count
    call NcRd( array, fileID, 'species', st4d, ct4d )

etc.

--Bob Y. 16:56, 12 June 2013 (EDT)

biofuel_mod.F

Modifications added in GEOS-Chem v9-02l. This update is included in Adjoint v35a.

This routine was removed from GEOS-Chem v10-01. All emissions are now handled via HEMCO.

In routine BIOFUEL_BURN, we removed 10 calls to the TRANSFER_2D routine in which we pass the BIOFUEL_KGarray . We used the following pattern:

                  ! Cast from REAL*4 to REAL*8, resize to (IIPAR,JJPAR)
!-------------------------------------------------------------------------
! NOTE: Remove this subroutine call (there are 10 of these)
!                  CALL TRANSFER_2D( ARRAY(:,:,1), BIOFUEL_KG(N,:,:) )
!-------------------------------------------------------------------------
                  BIOFUEL_KG(N,:,:) = ARRAY(:,:,1)

Also in BIOFUEL_BURN, in we replaced a call to TRANSFER_2D in which we passed the BF_CO array, using this pattern:

               ! Save BF_CO before scaling (tmf, 6/15/07) 
!-------------------------------------------------------------------------
! NOTE: Remove this subroutine call (this is the only one)
!               CALL TRANSFER_2D( ARRAY(:,:,1), BF_CO(:,:) )  
!-------------------------------------------------------------------------       
               BF_CO             = ARRAY(:,:,1)

--Bob Y. 09:57, 13 June 2013 (EDT)

fvdas_convect_mod.F

Modifications added in GEOS-Chem v9-02r. This update is included in Adjoint v35j.

We have rewritten the arguments in routines FVDAS_CONVECT, HACK_CONV, and ARCONVTRAN (in GeosCore/fvdas_convect_mod.F) so as to avoid creating array temporaries. As of this commit, we have eliminated array temporaries for the HKETA, HKBETA, ZMMU, ZMMD, ZMEU met fields. Array temporaries still exist for the STT and F (aka FRACIS) arguments, so we will remove them in a future commit.

We made these modifications in FVDAS_CONVECT:

!-----------------------------------------------------------------------------
! Prior to 10/28/13:
! Eliminate array temporary by accepting pointer variables into this routine
! via assumed-shape arguments.  This is more efficient. (bmy, 10/28/13)
!      REAL*8,         INTENT(IN)    :: ETA(IIPAR,JJPAR,LLPAR)
!      REAL*8,         INTENT(IN)    :: BETA(IIPAR,JJPAR,LLPAR)
!      REAL*8,         INTENT(IN)    :: MU(IIPAR,JJPAR,LLPAR)
!      REAL*8,         INTENT(IN)    :: MD(IIPAR,JJPAR,LLPAR)
!      REAL*8,         INTENT(IN)    :: EU(IIPAR,JJPAR,LLPAR) 
!-----------------------------------------------------------------------------
      REAL*8,         INTENT(IN)    :: ETA (:,:,:)
      REAL*8,         INTENT(IN)    :: BETA(:,:,:)
      REAL*8,         INTENT(IN)    :: MU  (:,:,:)
      REAL*8,         INTENT(IN)    :: MD  (:,:,:)
      REAL*8,         INTENT(IN)    :: EU  (:,:,:)

and these in HACK_CONV:

!-----------------------------------------------------------------------------
! Prior to 10/28/13:
! Eliminate array temporary by accepting pointer variables into this routine
! via assumed-shape arguments.  This is more efficient. (bmy, 10/28/13)
!      REAL*8,  INTENT(IN)    :: ETA(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)    :: BETA(IIPAR,JJPAR,LLPAR)
!-----------------------------------------------------------------------------
      REAL*8,  INTENT(IN)    :: ETA (:,:,:)
      REAL*8,  INTENT(IN)    :: BETA(:,:,:)	  

and lastly, these in ARCONVTRAN:

!------------------------------------------------------------------------------
! Prior to 10/28/13:
! Eliminate array temporary by accepting pointer variables into this routine
! via assumed-shape arguments.  This is more efficient. (bmy, 10/28/13)
!      REAL*8,  INTENT(IN)  :: MU(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)  :: MD(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)  :: EU(IIPAR,JJPAR,LLPAR)
!------------------------------------------------------------------------------
      REAL*8,  INTENT(IN)  :: MU (:,:,:)
      REAL*8,  INTENT(IN)  :: MD (:,:,:)
      REAL*8,  INTENT(IN)  :: EU (:,:,:)

--Bob Y. 16:46, 31 October 2013 (EDT)

gcap_convect_mod.F

Modifications added in GEOS-Chem v9-02r. This update is included in Adjoint v35j.

We have rewritten the arguments in routines GCAP_CONVECT and ARCONVTRAN (in GeosCore/gcap_convect_mod.F) so as to avoid creating array temporaries. We have eliminated array temporaries for the UPDE, DNDE, UPDN, DNDN, ENTRAIN, DETRAINE, and DETRAINN met fields. Array temporaries still exist for the STT (aka Q) and F (aka FRACIS) arguments, so we will remove them in a future commit.

We made these modifications in GCAP_CONVECT:

!------------------------------------------------------------------------------
! Prior to 11/4/13:
! Eliminate array temporary by accepting pointer variables into this routine
! via assumed-shape arguments. (mpayer, 11/4/13)
!      REAL*8,  INTENT(IN)    :: UPDE(IIPAR,JJPAR,LLPAR)     
!      REAL*8,  INTENT(IN)    :: DNDE(IIPAR,JJPAR,LLPAR)     
!      REAL*8,  INTENT(IN)    :: ENTRAIN(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)    :: DETRAINE(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)    :: UPDN(IIPAR,JJPAR,LLPAR)     
!      REAL*8,  INTENT(IN)    :: DNDN(IIPAR,JJPAR,LLPAR)     
!      REAL*8,  INTENT(IN)    :: DETRAINN(IIPAR,JJPAR,LLPAR)
!------------------------------------------------------------------------------
      REAL*8,  INTENT(IN)    :: UPDE(:,:,:)
      REAL*8,  INTENT(IN)    :: DNDE(:,:,:)
      REAL*8,  INTENT(IN)    :: ENTRAIN(:,:,:)
      REAL*8,  INTENT(IN)    :: DETRAINE(:,:,:)
      REAL*8,  INTENT(IN)    :: UPDN(:,:,:)
      REAL*8,  INTENT(IN)    :: DNDN(:,:,:)
      REAL*8,  INTENT(IN)    :: DETRAINN(:,:,:)

and these in ARCONVTRAN:

!------------------------------------------------------------------------------
! Prior to 11/4/13:
! Eliminate array temporary by accepting pointer variables into this routine
! via assumed-shape arguments. (mpayer, 11/4/13)
!      REAL*8,  INTENT(IN)  :: MU(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)  :: MD(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)  :: DU(IIPAR,JJPAR,LLPAR)
!      REAL*8,  INTENT(IN)  :: EU(IIPAR,JJPAR,LLPAR) 
!------------------------------------------------------------------------------
      REAL*8,  INTENT(IN)  :: MU(:,:,:)
      REAL*8,  INTENT(IN)  :: MD(:,:,:)
      REAL*8,  INTENT(IN)  :: DU(:,:,:)
      REAL*8,  INTENT(IN)  :: EU(:,:,:)

--Melissa Sulprizio 16:20, 4 November 2013 (EST)

pjc_pfix_mod.F

Modifications added in GEOS-Chem v9-02r. This update is included in Adjoint v35j.

In routine DO_PJC_PFIX (in GeosCore/pjc_pfix_mod.F), rewrite the following argument definitions:

!------------------------------------------------------------------------------
! Prior to 11/4/13:
! Eliminate array temporaries by accepting assumed-shape arguments into this
! routine. (mpayer, 11/4/13)
!      ! True PSurface at middle of dynamic timestep [hPa]
!      REAL*8,  INTENT(IN)  :: P1(IIPAR,JJPAR)
!
!      ! True PSurface at end    of dynamic timestep [hPa]
!      REAL*8,  INTENT(IN)  :: P2(IIPAR,JJPAR)
!------------------------------------------------------------------------------
      ! True PSurface at middle of dynamic timestep [hPa]
      REAL*8,  INTENT(IN)  :: P1(:,:)

      ! True PSurface at end    of dynamic timestep [hPa]
      REAL*8,  INTENT(IN)  :: P2(:,:)

--Melissa Sulprizio 16:35, 4 November 2013 (EST)

pressure_mod.F

Modifications added in GEOS-Chem v9-02r. This update is included in Adjoint v35j.

In routine SET_FLOATING_PRESSURE (in GeosUtil/pressure_mod.F), rewrite the following argument definitions:

!------------------------------------------------------------------------------
! Prior to 11/4/13:
! Eliminate array temporary by accepting assumed-shape argument into this
! routine. (mpayer, 11/4/13)
!      ! Array containing pressure with which to initialize PFLT [hPa]
!      REAL*8, INTENT(IN) :: PS(IIPAR,JJPAR)  
!------------------------------------------------------------------------------
      ! Array containing pressure with which to initialize PFLT [hPa]
      REAL*8, INTENT(IN) :: PS(:,:)

--Melissa Sulprizio 16:35, 4 November 2013 (EST)