Skip to content

Commit

Permalink
Add more netCDF diagnostics and debug the ocean Hg diagnostics
Browse files Browse the repository at this point in the history
Corrected various issues with the remaining ocean Hg diagnostics.

Also added the equivalent of ND03 #21 (Hg2 and HgP deposited to snow
and ice).  This involved passing State_Diag to the convection, drydep,
and wetdep modules.  NOTE: This diagnostic does not match the bpch
output, probably due to how the bpch diagnostic was implemented.
Need to think of a better way to handle that.

Also added netCDF diagnostics for particulate bound mercury (PBM)
and reactive gaseous mercury (RGM) in GeosCore/diagnostics_mod.F90.

Added a new routine called Reset_Hg_Diags in GeosCore/mercury_mod.F90,
which zeroes out several relevant fields of State_Diag for the Hg
simulations.

Removed the module fvdas_convect_mod.F; we no longer use GEOS-4
meteorology, so this was orphaned.

Signed-off-by: Bob Yantosca <yantosca@seas.harvard.edu>
  • Loading branch information
yantosca committed Oct 26, 2018
1 parent ac7a651 commit d09a18a
Show file tree
Hide file tree
Showing 12 changed files with 410 additions and 1,546 deletions.
6 changes: 3 additions & 3 deletions GeosCore/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -509,9 +509,9 @@ co2_mod.o : co2_mod.F \

convection_mod.o : convection_mod.F \
diag_mod.o depo_mercury_mod.o \
fvdas_convect_mod.o wetscav_mod.o \
mercury_mod.o tendencies_mod.o \
hco_interface_mod.o diagnostics_mod.o
wetscav_mod.o mercury_mod.o \
tendencies_mod.o hco_interface_mod.o \
diagnostics_mod.o

dao_mod.o : dao_mod.F

Expand Down
16 changes: 10 additions & 6 deletions GeosCore/convection_mod.F
Original file line number Diff line number Diff line change
Expand Up @@ -405,6 +405,7 @@ SUBROUTINE DO_CONVECTION( am_I_Root, Input_Opt, State_Met,
& Input_Opt = Input_Opt,
& State_Met = State_Met,
& State_Chm = State_Chm,
& State_Diag = State_Diag,
& I = I,
& J = J,
& AREA_M2 = AREA_M2,
Expand Down Expand Up @@ -567,6 +568,7 @@ SUBROUTINE DO_CLOUD_CONVECTION( am_I_Root,
& Input_Opt,
& State_Met,
& State_Chm,
& State_Diag,
& I,
& J,
& AREA_M2,
Expand All @@ -590,6 +592,7 @@ SUBROUTINE DO_CLOUD_CONVECTION( am_I_Root,
USE Input_Opt_Mod, ONLY : OptInput
USE PhysConstants
USE State_Chm_Mod, ONLY : ChmState
USE State_Diag_Mod, ONLY : DgnState
USE State_Met_Mod, ONLY : MetState
USE Species_Mod, ONLY : Species
USE WETSCAV_MOD, ONLY : H2O2s_3D => H2O2s ! [v/v]
Expand All @@ -616,6 +619,7 @@ SUBROUTINE DO_CLOUD_CONVECTION( am_I_Root,
! !INPUT/OUTPUT PARAMETERS:
!
TYPE(ChmState), INTENT(INOUT) :: State_Chm ! Chemistry State object
TYPE(DgnState), INTENT(INOUT) :: State_Diag ! Diagnostics State object
!
! !OUTPUT PARAMETERS:
!
Expand Down Expand Up @@ -1537,9 +1541,9 @@ SUBROUTINE DO_CLOUD_CONVECTION( am_I_Root,
Hg_Cat = SpcInfo%Hg_Cat
! Pass to "ocean_mercury_mod.f"
CALL ADD_Hg2_WD ( I, J, Hg_Cat, WET_Hg2 )
CALL ADD_Hg2_SNOWPACK( I, J, Hg_Cat, WET_Hg2,
& State_Met )
CALL ADD_Hg2_WD ( I, J, Hg_Cat, WET_Hg2 )
CALL ADD_Hg2_SNOWPACK( I, J, Hg_Cat, WET_Hg2,
& State_Met, State_Diag )
ENDIF
!--------------------------------------
Expand All @@ -1554,9 +1558,9 @@ SUBROUTINE DO_CLOUD_CONVECTION( am_I_Root,
Hg_Cat = SpcInfo%Hg_Cat
! Pass to "ocean_mercury_mod.f"
CALL ADD_HgP_WD ( I, J, Hg_Cat, WET_HgP )
CALL ADD_Hg2_SNOWPACK( I, J, Hg_Cat, WET_HgP,
& State_Met )
CALL ADD_HgP_WD ( I, J, Hg_Cat, WET_HgP )
CALL ADD_Hg2_SNOWPACK( I, J, Hg_Cat, WET_HgP,
& State_Met, State_Diag )
ENDIF
ENDIF
ENDDO ! End internal timestep loop
Expand Down
37 changes: 32 additions & 5 deletions GeosCore/depo_mercury_mod.F
Original file line number Diff line number Diff line change
Expand Up @@ -279,23 +279,30 @@ END SUBROUTINE ADD_HgP_WD
!\\
! !INTERFACE:
!
SUBROUTINE ADD_HG2_SNOWPACK( I, J, Hg_Cat, DEP_Hg2, State_Met )
SUBROUTINE ADD_HG2_SNOWPACK( I, J, Hg_Cat, DEP_Hg2,
& State_Met, State_Diag )
!
! !USES:
!
USE DAO_MOD, ONLY : IS_ICE, IS_LAND
USE State_Diag_Mod, ONLY : DgnState
USE State_Met_Mod, ONLY : MetState
#if defined( BPCH_DIAG )
USE DIAG03_MOD, ONLY : AD03, ND03
#endif
USE Time_Mod, ONLY : Get_Ts_Chem
!
! !INPUT PARAMETERS:
!
! Arguments as input
INTEGER, INTENT(IN) :: I, J ! Grid box lon & lat indices
INTEGER, INTENT(IN) :: Hg_Cat ! Hg category number
REAL(fp), INTENT(IN) :: Dep_Hg2 ! Hg2 (or HgP) deposited
TYPE(MetState), INTENT(IN) :: State_Met ! Meteorology State object
INTEGER, INTENT(IN) :: I, J ! Grid box lon & lat indices
INTEGER, INTENT(IN) :: Hg_Cat ! Hg category number
REAL(fp), INTENT(IN) :: Dep_Hg2 ! Hg2 (or HgP) deposited
TYPE(MetState), INTENT(IN) :: State_Met ! Meteorology State object
!
! !INPUT/OUTPUT PARAMETERS:
!
TYPE(DgnState), INTENT(INOUT) :: State_Diag ! Diagnostics State object
!
! !REVISION HISTORY:
! 02 Sep 2008 - C. Holmes - Initial version
Expand Down Expand Up @@ -327,6 +334,7 @@ SUBROUTINE ADD_HG2_SNOWPACK( I, J, Hg_Cat, DEP_Hg2, State_Met )
LOGICAL :: IS_SNOW_OR_ICE
REAL(fp) :: FRAC_SNOW_OR_ICE
REAL(fp) :: FRAC_O
REAL(fp) :: DT

!=================================================================
! ADD_HG2_SNOWPACK begins here!
Expand All @@ -338,6 +346,9 @@ SUBROUTINE ADD_HG2_SNOWPACK( I, J, Hg_Cat, DEP_Hg2, State_Met )
! Return if snowpack model is disabled
IF ( .NOT. LHGSNOW ) RETURN

! Chemistry timestep [s]
DT = GET_TS_CHEM()

! Don't let fraction be greater than 1
FRAC_SNOW_OR_ICE = MIN( State_Met%FRSNO(I,J) +
& State_Met%FRSEAICE(I,J) +
Expand Down Expand Up @@ -380,6 +391,8 @@ SUBROUTINE ADD_HG2_SNOWPACK( I, J, Hg_Cat, DEP_Hg2, State_Met )
#if defined( BPCH_DIAG )
!----------------------------------------------------------------------------
! %%%%% ND03 (bpch) DIAGNOSTIC %%%%%
!
! NOTE: Archiving to AD03(I,J,21,1) causes the slot #4 of the PL-HG2-$
! diagnostic to yield different results when comparing a GEOS-5 Hg simulation
! done on a single processor to one done with multi-processors. (In other
Expand Down Expand Up @@ -409,6 +422,20 @@ SUBROUTINE ADD_HG2_SNOWPACK( I, J, Hg_Cat, DEP_Hg2, State_Met )
!----------------------------------------------------------------------------
#endif
#if defined( NC_DIAG )
!--------------------------------------------------------------
! %%%%% HISTORY (aka netCDF diagnostics) %%%%%
!
! Store diagnostic of TOTAL HgII/HgP deposition to snow/ice
! NOTE: Units are now kg/s
!--------------------------------------------------------------
IF ( State_Diag%Archive_FluxHg2HgPfromAirToSnow ) THEN
State_Diag%FluxHg2HgPfromAirToSnow(I,J) =
& State_Diag%FluxHg2HgPfromAirToSnow(I,J) +
& ( FRAC_SNOW_OR_ICE * MAX( DEP_HG2, 0e+0_fp ) ) !/ DT
ENDIF
#endif
ENDIF
END SUBROUTINE ADD_HG2_SNOWPACK
Expand Down
11 changes: 6 additions & 5 deletions GeosCore/diag1.F
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,6 @@ SUBROUTINE DIAG1( am_I_Root, Input_Opt,
INTEGER :: I, J, K
INTEGER :: L, N, NA
REAL(fp) :: EmMW_g, P0, Spc_VV
REAL(fp) :: EmMW_g_Hg2, EmMW_g_HgP

! SAVEd scalars
LOGICAL, SAVE :: FIRST = .TRUE.
Expand All @@ -184,6 +183,8 @@ SUBROUTINE DIAG1( am_I_Root, Input_Opt,
LOGICAL, SAVE :: Do_ND71 = .FALSE.
INTEGER, SAVE :: id_Hg2 = -1
INTEGER, SAVE :: id_HgP = -1
REAL(fp),SAVE :: EmMW_g_Hg2 = -1.0_fp
REAL(fp),SAVE :: EmMW_g_HgP = -1.0_fp

!=================================================================
! DIAG1 begins here!
Expand Down Expand Up @@ -274,18 +275,18 @@ SUBROUTINE DIAG1( am_I_Root, Input_Opt,
IF ( Do_ND03 .and. NA == 1 ) THEN
!--------------------------------------------------------
! Reactive gaseous mercury (RGM), [pptv]
! Reactive gaseous mercury [pptv]
!--------------------------------------------------------
IF ( N == id_Hg2 ) THEN
IF ( id_Hg2 > 0 ) THEN
AD03_RGM(I,J,L) = AD03_RGM(I,J,L)
& + State_Chm%Species(I,J,L,id_Hg2)
& * ( AIRMW / EmMw_g_Hg2 * 1e+12_fp )
ENDIF
!--------------------------------------------------------
! Reactive particulate mercury (RGM), [pptv]
! Particulate bound mercury [pptv]
!--------------------------------------------------------
IF ( N == id_HgP ) THEN
IF ( id_HgP > 0 ) THEN
AD03_PBM(I,J,L) = AD03_PBM(I,J,L)
& + State_Chm%Species(I,J,L,id_HgP)
& * ( AIRMW / EmMW_g_HgP * 1e+12_fp )
Expand Down
56 changes: 54 additions & 2 deletions GeosCore/diagnostics_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -68,8 +68,9 @@ SUBROUTINE Set_Diagnostics_EndofTimestep ( am_I_Root, Input_Opt, &
!
USE Input_Opt_Mod, ONLY : OptInput
USE State_Met_Mod, ONLY : MetState
USE State_Chm_Mod, ONLY : ChmState
USE State_Chm_Mod, ONLY : ChmState, Ind_
USE State_Diag_Mod, ONLY : DgnState
USE PhysConstants, ONLY : AIRMW
!
! !INPUT PARAMETERS:
!
Expand All @@ -95,8 +96,17 @@ SUBROUTINE Set_Diagnostics_EndofTimestep ( am_I_Root, Input_Opt, &
! !LOCAL VARIABLES:
!
#if defined( NC_DIAG )
! Scalars
INTEGER :: I, J, L, N
CHARACTER(LEN=255) :: ErrMsg, thisLoc
REAL(fp) :: ToPptv

! SAVEd scalars
INTEGER, SAVE :: id_Hg2 = -1
INTEGER, SAVE :: id_HgP = -1
LOGICAL, SAVE :: FIRST = .TRUE.

! Strings
CHARACTER(LEN=255) :: ErrMsg, ThisLoc

!=======================================================================
! Set_Diagnostics_EndofTimestep begins here
Expand Down Expand Up @@ -141,6 +151,48 @@ SUBROUTINE Set_Diagnostics_EndofTimestep ( am_I_Root, Input_Opt, &
!$OMP END PARALLEL DO
ENDIF

!-----------------------------------------------------------------------
! Diagnostics for the mercury and tagged mercury simulations
!-----------------------------------------------------------------------
IF ( Input_Opt%ITS_A_MERCURY_SIM ) THEN

! Get species indices for Hg2 and HgP
IF ( FIRST ) THEN
id_Hg2 = Ind_('Hg2')
id_HgP = Ind_('HgP')
FIRST = .FALSE.
ENDIF

!--------------------------------------------
! Ractive gaseous mercury (RGM) [pptv]
!--------------------------------------------
IF ( id_Hg2 > 0 .and. State_Diag%Archive_ReactiveGaseousHg ) THEN

! Conversion factor to pptv
ToPptv = ( AIRMW / &
State_Chm%SpcData(id_Hg2)%Info%EmMW_g * &
1.0e+12_fp )

! Save into State_diag
State_Diag%ReactiveGaseousHg = State_Chm%Species(:,:,:,id_Hg2) &
* ToPptv
ENDIF

!--------------------------------------------
! Ractive particulate mercury (RGM) [pptv]
!--------------------------------------------
IF ( id_HgP > 0 .and. State_Diag%Archive_ParticulateBoundHg ) THEN

! Conversion factor to pptv
ToPptv = ( AIRMW / &
State_Chm%SpcData(id_HgP)%Info%EmMW_g * &
1.0e+12_fp )

! Save into State_Diag
State_Diag%ParticulateBoundHg = State_Chm%Species(:,:,:,id_HgP) &
* ToPptv
ENDIF
ENDIF
#endif

END SUBROUTINE Set_Diagnostics_EndofTimestep
Expand Down

0 comments on commit d09a18a

Please sign in to comment.