Passing array arguments efficiently in GEOS-Chem

From Geos-chem
Revision as of 19:40, 6 June 2013 by Bmy (Talk | contribs) (Derived-type objects)

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.
  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 like 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 as 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 calling routine
    !---------------------------
    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 calling routine
    !---------------------------
    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 now see:in the preceding section]], we see that we have the following:

  • 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, when calling the subroutine, GEOS-Chem has to copy the values of State_Chm%Tracers into an internal temporary array and then pass that to the subroutine. The larger the size of State_Chm%Tracers, the less efficient GEOS-Chem will be.

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:33, 6 June 2013 (EDT)

Diagnosing inefficient array argument passing in GEOS-Chem

A simple way to check for