Skip to content

Commit

Permalink
Resolve compilation issues for TOMAS
Browse files Browse the repository at this point in the history
GeosCore/carbon_mod.F90: Two calls to GetHcoDiagn were lacking the
HcoState and ExtState arguments.  Now fixed.

GeosCore/flexchem_mod.F90: Remove an extraneous character in the
#ifdef block for TOMAS.

GeosCore/vdiff_mod.F90: Remove reference to ND44 bpch diagnostic,
this has since been removed.

Signed-off-by: Bob Yantosca <yantosca@seas.harvard.edu>
  • Loading branch information
yantosca committed Nov 16, 2020
1 parent 14305c2 commit 6cc7c0a
Show file tree
Hide file tree
Showing 3 changed files with 4 additions and 24 deletions.
4 changes: 2 additions & 2 deletions GeosCore/carbon_mod.F90
Expand Up @@ -5017,7 +5017,7 @@ SUBROUTINE EMISSCARBONTOMAS( Input_Opt, State_Chm, State_Grid, State_Met, RC )
Ptr2D => NULL()

DgnName = 'OCPO_BB'
CALL GetHcoDiagn( DgnName, .FALSE., ERR, Ptr2D=Ptr2D )
CALL GetHcoDiagn( HcoState, ExtState, DgnName, .FALSE., ERR, Ptr2D=Ptr2D )
IF ( .NOT. ASSOCIATED(Ptr2D) ) THEN
CALL GC_WARNING('HEMCO diagnostic not found: '//TRIM(DgnName), &
ERR, THISLOC=LOC)
Expand Down Expand Up @@ -5127,7 +5127,7 @@ SUBROUTINE EMISSCARBONTOMAS( Input_Opt, State_Chm, State_Grid, State_Met, RC )
! READ IN directly emitted SOAS (sfarina / jkodros)
Ptr2D => NULL()
DgnName = 'BIOGENIC_SOAS'
CALL GetHcoDiagn( DgnName, .FALSE., RC, Ptr2D=Ptr2D )
CALL GetHcoDiagn( HcoState, ExtState, DgnName, .FALSE., RC, Ptr2D=Ptr2D )
IF ( .NOT. ASSOCIATED(Ptr2D) ) THEN
CALL GC_Error('Not found: '//TRIM(DgnName), RC, THISLOC=LOC)
RETURN
Expand Down
2 changes: 1 addition & 1 deletion GeosCore/flexchem_mod.F90
Expand Up @@ -133,7 +133,7 @@ SUBROUTINE Do_FlexChem( Input_Opt, State_Chm, State_Diag, &
USE UCX_MOD, ONLY : UCX_H2SO4PHOT
#ifdef TOMAS
#ifdef BPCH_DIAG
> USE TOMAS_MOD, ONLY : H2SO4_RATE
USE TOMAS_MOD, ONLY : H2SO4_RATE
#endif
#endif
!
Expand Down
22 changes: 1 addition & 21 deletions GeosCore/vdiff_mod.F90
Expand Up @@ -83,7 +83,6 @@ MODULE Vdiff_Mod
INTEGER :: nspcmix ! # of species for mixing
INTEGER :: plev ! # of levels
INTEGER :: plevp ! # of level edges
LOGICAL :: Do_ND44 = .FALSE. ! Use ND44 bpch (for TOMAS)?
INTEGER :: ntopfl ! top level to which vertical
! diffusion is applied.
INTEGER :: npbl ! max # of levels in pbl
Expand Down Expand Up @@ -1652,14 +1651,6 @@ SUBROUTINE Init_Vdiff( Input_Opt, State_Chm, State_Grid, RC )
IF ( RC /= GC_SUCCESS ) RETURN
qmincg = 0.0_fp

#ifdef TOMAS
#ifdef BPCH_DIAG
! Set a flag to denote we should archive ND44 bpch diagnostic
! NOTE: this will only be valid if BPCH_DIAG=y
Do_ND44 = ( ND44 > 0 )
#endif
#endif

END SUBROUTINE Init_Vdiff
!EOC
!------------------------------------------------------------------------------
Expand Down Expand Up @@ -1847,10 +1838,7 @@ SUBROUTINE VDIFFDR( Input_Opt, State_Chm, State_Diag, &
! INTENT(INOUT). This is because VDIFF will modify the specific
! humidity field. (bmy, 11/21/12)
! .
! (2) VDIFF also archives drydep fluxes to the soil NOx emissions module
! (by calling routine SOIL_DRYDEP) and to the ND44 diagnostic.
! .
! (3) As of July 2016, we assume that all of the advected species are listed
! (2) As of July 2016, we assume that all of the advected species are listed
! first in the species database. This is the easiest way to pass a slab
! to the TPCORE routine. This may change in the future. (bmy, 7/13/16)

Expand Down Expand Up @@ -2097,14 +2085,6 @@ SUBROUTINE Do_Vdiff( Input_Opt, State_Chm, State_Diag, &
USE TIME_MOD, ONLY : ITS_TIME_FOR_EMIS
USE Time_Mod, ONLY : Get_Ts_Dyn
USE UnitConv_Mod, ONLY : Convert_Spc_Units
#ifdef TOMAS
#ifdef BPCH_DIAG
!=======================================================================
! These are only needed if GEOS-Chem is compiled for TOMAS
!=======================================================================
USE CMN_DIAG_MOD, ONLY : ND44
#endif
#endif

IMPLICIT NONE
!
Expand Down

0 comments on commit 6cc7c0a

Please sign in to comment.