Skip to content

Commit

Permalink
Restored archival of drydepvel diagnostics in drydep_mod.F90
Browse files Browse the repository at this point in the history
GeosCore/drydep_mod.F90
- Restored the archival of the DryDepVel and SatDiagnDryDepVel
  diagnostic quantities in routine Update_DryDepFreq, in an IF
  block that only executes when the full PBL mixing option
  is selected.  This is to prevent these diagnostics from being
  zero when the non-local PBL mixing is not selected.
- Updated comments

GeosCore/hco_interface_gc_mod.F90
- Added a comment block that the DryDepVel and SatDiagnDryDepVel
  diagnostics are archived here when non-local PBL mixing is used,
  and in drydep_mod.F90 when full PBL mixing is used.

CHANGELOG.md
- Added note about the SatDiagnColEmis and SatDiagnSurfFlux arrays
  being updated with (I,J,S) instead of (:,:,S)
  • Loading branch information
yantosca committed Dec 3, 2024
1 parent ec3a08d commit d9ee2e2
Show file tree
Hide file tree
Showing 3 changed files with 63 additions and 14 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),

### Fixed
- Fixed CEDS HEMCO_Config.rc entries to emit TMB into the TMB species (and not HCOOH)
- In `hco_interface_gc_mod.F90`, update `SatDiagnColEmis` and `SatDiagnSurfFlux` arrays with `(I,J,S)` instead of `(:,:,S)`

## [14.5.0] - 2024-11-07
### Added
Expand Down
59 changes: 46 additions & 13 deletions GeosCore/drydep_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,6 @@ MODULE DRYDEP_MOD
#if defined( MODEL_CESM )
PUBLIC :: UPDATE_DRYDEPFREQ
#else

!
! !PRIVATE MEMBER FUNCTIONS:
!
Expand Down Expand Up @@ -611,7 +610,7 @@ SUBROUTINE UPDATE_DRYDEPFREQ( Input_Opt, State_Chm, State_Diag, State_Grid, &
!$OMP END PARALLEL DO

! Set diagnostics - consider moving?
IF ( State_Diag%Archive_DryDepVelForALT1 ) THEN
IF ( State_Diag%Archive_DryDepVelForALT1 ) THEN

!$OMP PARALLEL DO &
!$OMP DEFAULT( SHARED )&
Expand All @@ -621,6 +620,40 @@ SUBROUTINE UPDATE_DRYDEPFREQ( Input_Opt, State_Chm, State_Diag, State_Grid, &
! Point to State_Chm%DryDepVel [m/s]
NDVZ = NDVZIND(D)

! When using the full PBL mixing option (aka TURBDAY),
! update DryDepVel and SatDiagnDryDepVel diagnostics here.
!
! When using the non-local PBL mixing option (VDIFF), then
! update these diagnostics in Compute_Sflx_for_Vdiff (in
! GeosCore/hco_interface_gc_mod.F90). This is necessary in
! order to capture the air-sea deposition velocities computed
! by the HEMCO "SeaFlux" extension. For more information,
! see https://github.com/geoschem/geos-chem/pull/2606 and
! https://github.com/geoschem/geos-chem/issues/2564.
!
! -- Bob Yantosca (03 Dec 2024)
IF ( .not. Input_Opt%LNLPBL ) THEN

! Dry dep velocity [cm/s]
IF ( State_Diag%Archive_DryDepVel ) THEN
S = State_Diag%Map_DryDepVel%id2slot(D)
IF ( S > 0 ) THEN
State_Diag%DryDepVel(:,:,S) = &
State_Chm%DryDepVel(:,:,NDVZ) * 100.0_f4
ENDIF
ENDIF

! Satellite diagnostic: Dry dep velocity [cm/s]
IF ( State_Diag%Archive_SatDiagnDryDepVel ) THEN
S = State_Diag%Map_SatDiagnDryDepVel%id2slot(D)
IF ( S > 0 ) THEN
State_Diag%SatDiagnDryDepVel(:,:,S) = &
State_Chm%DryDepVel(:,:,NDVZ) * 100.0_f4
ENDIF
ENDIF

ENDIF

! Dry dep velocity [cm/s] for species at altitude (e.g. 10m)
IF ( State_Diag%Archive_DryDepVelForALT1 ) THEN
! Get the "DryAltID" index, that is used to archive species
Expand Down Expand Up @@ -1620,9 +1653,9 @@ SUBROUTINE DEPVEL( Input_Opt, State_Chm, State_Diag, State_Grid, &
! - Bob Yantosca (17 May 2023)
IF ( N_SPC == ID_Hg0 ) THEN

! Assume lower reactivity
F0_K = 3.0e-05_f8
! Assume lower reactivity
F0_K = 3.0e-05_f8

! But if this is the rainforest land type and we fall
! within the bounding box of the Amazon rainforest,
! then increase reactivity as inferred from observations.
Expand Down Expand Up @@ -1718,10 +1751,10 @@ SUBROUTINE DEPVEL( Input_Opt, State_Chm, State_Diag, State_Grid, &
RHB(I,J), &
W10(I,J), &
VTSoutput, &
Input_Opt, &
Input_Opt, &
State_Chm )

VTSoutput_(K,LDT) = VTSoutput
VTSoutput_(K,LDT) = VTSoutput

ELSE IF ( SpcInfo%DD_DustDryDep ) THEN

Expand Down Expand Up @@ -2234,7 +2267,7 @@ SUBROUTINE DEPVEL( Input_Opt, State_Chm, State_Diag, State_Grid, &
!** Load array State_Chm%DryDepVel
DO 550 K=1,NUMDEP
IF (.NOT.LDEP(K)) GOTO 550

State_Chm%DryDepVel(I,J,K) = VD(K)

! Now check for negative deposition velocity before returning to
Expand Down Expand Up @@ -3198,7 +3231,7 @@ FUNCTION AERO_SFCRSII( K, II, PRESS, TEMP, USTAR, RHB, W10, VTSout, Input_Opt, S
TYPE(ChmState), INTENT(IN) :: State_Chm ! Chemistry State object

!
! !OUTPUT PARAMETERS:
! !OUTPUT PARAMETERS:
!
REAL(f8), INTENT(OUT) :: VTSout ! Settling velocity [m/s]

Expand Down Expand Up @@ -3965,7 +3998,7 @@ END FUNCTION DUST_SFCRSI
FUNCTION ADUST_SFCRSII( K, II, PRESS, TEMP, USTAR, &
VTSout, RHB, State_Chm ) RESULT( RS )
!
! !USES:
! !USES:
!
USE Species_Mod, ONLY : Species
USE State_Chm_Mod, ONLY : ChmState
Expand All @@ -3982,7 +4015,7 @@ FUNCTION ADUST_SFCRSII( K, II, PRESS, TEMP, USTAR, &
TYPE(ChmState), INTENT(IN) :: State_Chm ! Chemistry State object

!
! !OUTPUT PARAMETERS:
! !OUTPUT PARAMETERS:
!
REAL(f8), INTENT(OUT) :: VTSout ! Settling velocity [m/s]

Expand Down Expand Up @@ -4198,7 +4231,7 @@ FUNCTION ADUST_SFCRSII( K, II, PRESS, TEMP, USTAR, &
!BC
ELSE IF ( K == idd_BCPI .OR. K == idd_BCPO ) THEN
! DIAM is not changed

!OA
ELSE
DIAM = DIAM * ((1.0_fp + 0.1_fp * RHBL / (1.0_fp - RHBL)) &
Expand Down Expand Up @@ -4320,7 +4353,7 @@ FUNCTION DUST_SFCRSII( K, II, PRESS, TEMP, USTAR, DIAM, &
REAL(f8), INTENT(IN) :: DEN ! Particle density [kg/m3]

!
! !OUTPUT PARAMETERS:
! !OUTPUT PARAMETERS:
!
REAL(f8), INTENT(OUT) :: VTSout ! Settling velocity [m/s]

Expand Down
17 changes: 16 additions & 1 deletion GeosCore/hco_interface_gc_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5029,7 +5029,21 @@ SUBROUTINE Compute_Sflx_for_Vdiff( Input_Opt, State_Chm, State_Diag, &
ENDIF
ENDIF

! Dry deposition velocity (cm/s):
!-----------------------------------------------------------------
! HISTORY: Update dry deposition velocity [cm/s]
!
! Here we save the dry deposition velocities (stored in the
! DVEL array) into the DryDepVel and SatDiagnDryDepVel History
! diagnostics. This is necessary in order to capture the
! air-sea deposition velocity computed by the HEMCO "SeaFlux"
! extension for certain species.
!
! When using the full PBL mixing option (aka TURBDAY), the
! DryDepVel and SatDiagnDryDepVel diagnostics will be archived
! in drydep_mod.F90 instead.
!-----------------------------------------------------------------

! Dry deposition velocity [cm/s]
IF ( State_Diag%Archive_DryDepVel ) THEN
S = State_Diag%Map_DryDepVel%id2slot(ND)
IF ( S > 0 ) THEN
Expand Down Expand Up @@ -5068,6 +5082,7 @@ SUBROUTINE Compute_Sflx_for_Vdiff( Input_Opt, State_Chm, State_Diag, &
ThisSpc => NULL()
ENDDO
!$OMP END PARALLEL DO

ENDIF

!=======================================================================
Expand Down

0 comments on commit d9ee2e2

Please sign in to comment.