Skip to content

Commit

Permalink
Structural updates to fast-jx/cloud-j work so far
Browse files Browse the repository at this point in the history
- Replace Headers/photol_obj_mod.F90 with Headers/phot_container_mod.F90
- Rename State_Chm%Photol to State_Chm%Phot
- Rename derived type PhotolState to PhotContainer
- Retire CMN_Phot_Mod.F90
- Create photolysis_mod.F90
- Replace Init_Chemistry with Init_Photolysis
- Pass State_Chm to RRTMG subroutine Set_SpecMask
- Replace local variable DO_PHOTCHEM in mercury_mod with Input_Opt var
  set from toggle in geoschem_config.yml photolysis menu
- Pass State_Chm to Photo_JX
- Change order of arguments in Init_Mercury to put all IN-only first
- Move duplicate subroutines out of fjx_interface_mod.F90 and
  cldj_interface_mod.F90 and put in photolysis_mod.F90
- Retire fast-jx subroutine GC_EXITC
- Rename subroutine Fast_JX to Run_FastJX
- Rename subroutine Init_Fjx to Init_RastJX

Signed-off-by: Lizzie Lundgren <elundgren@seas.harvard.edu>
  • Loading branch information
lizziel committed Mar 23, 2023
1 parent 3f25207 commit 4e92687
Show file tree
Hide file tree
Showing 23 changed files with 2,808 additions and 4,507 deletions.
1 change: 1 addition & 0 deletions GeosCore/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,7 @@ add_library(GeosCore
ocean_mercury_mod.F90
olson_landmap_mod.F90
pbl_mix_mod.F90
photolysis_mod.F90
planeflight_mod.F90
pops_mod.F90
RnPbBe_mod.F90
Expand Down
117 changes: 87 additions & 30 deletions GeosCore/aerosol_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -173,7 +173,6 @@ SUBROUTINE AEROSOL_CONC( Input_Opt, State_Chm, State_Diag, &
!
! !USES:
!
USE CMN_Phot_MOD, ONLY : REAA
USE ErrCode_Mod
USE ERROR_MOD
#if !defined( MODEL_CESM )
Expand Down Expand Up @@ -245,6 +244,7 @@ SUBROUTINE AEROSOL_CONC( Input_Opt, State_Chm, State_Diag, &

! Pointers
TYPE(SpcConc), POINTER :: Spc(:)
REAL*8, POINTER :: REAA(:,:)
REAL(fp), POINTER :: AIRVOL(:,:,:)
REAL(fp), POINTER :: PMID(:,:,:)
REAL(fp), POINTER :: T(:,:,:)
Expand Down Expand Up @@ -299,6 +299,9 @@ SUBROUTINE AEROSOL_CONC( Input_Opt, State_Chm, State_Diag, &
Is_SimpleSOA = ( id_SOAS > 0 )
Is_ComplexSOA = Input_Opt%LSOA

! Set pointers
REAA => State_Chm%Phot%REAA

! Convert species to [kg] for this routine
CALL Convert_Spc_Units( Input_Opt, State_Chm, State_Grid, State_Met, &
'kg', RC, OrigUnit=OrigUnit )
Expand Down Expand Up @@ -1017,6 +1020,7 @@ SUBROUTINE AEROSOL_CONC( Input_Opt, State_Chm, State_Diag, &

! Free pointers
Spc => NULL()
REAA => NULL()
AIRVOL => NULL()
PMID => NULL()
T => NULL()
Expand Down Expand Up @@ -1045,14 +1049,7 @@ SUBROUTINE RDAER( Input_Opt, State_Chm, State_Diag, State_Grid, State_Met, &
!
! !USES:
!
USE CMN_SIZE_Mod, ONLY : NRH, NRHAER, NSTRATAER
USE CMN_Phot_MOD, ONLY : IRHARR, ODAER, NWVAA, NWVAA0, NWVREQUIRED
USE CMN_Phot_MOD, ONLY : IWV1000, REAA, QQAA, ALPHAA, SSAA
USE CMN_Phot_MOD, ONLY : ASYMAA, ISOPOD, NDUST, IWVSELECT
USE CMN_Phot_MOD, ONLY : ACOEF_WV, BCOEF_WV, NAER, IWVREQUIRED
#ifdef RRTMG
USE CMN_Phot_MOD, ONLY : RTODAER, RTSSAER, RTASYMAER
#endif
USE CMN_SIZE_Mod, ONLY : NAER, NRH, NDUST, NRHAER, NSTRATAER
USE ErrCode_Mod
USE ERROR_MOD, ONLY : ERROR_STOP, Safe_Div
USE Input_Opt_Mod, ONLY : OptInput
Expand Down Expand Up @@ -1182,14 +1179,33 @@ SUBROUTINE RDAER( Input_Opt, State_Chm, State_Diag, State_Grid, State_Met, &
REAL(fp) :: GF_RH
REAL(fp) :: BCAE_1, BCAE_2

! Pointers
REAL(fp), POINTER :: BXHEIGHT(:,:,:)
REAL(fp), POINTER :: ERADIUS(:,:,:,:)
REAL(fp), POINTER :: TAREA(:,:,:,:)
REAL(fp), POINTER :: WERADIUS(:,:,:,:)
REAL(fp), POINTER :: WTAREA(:,:,:,:)
! Pointers to State_Chm%Phot
INTEGER, POINTER :: IWVREQUIRED(:)
INTEGER, POINTER :: IWVSELECT (:,:)
INTEGER, POINTER :: IRHARR (:,:,:)
REAL*8, POINTER :: ACOEF_WV (:)
REAL*8, POINTER :: BCOEF_WV (:)
REAL*8, POINTER :: REAA (:,:)
REAL*8, POINTER :: QQAA (:,:,:)
REAL*8, POINTER :: ALPHAA (:,:,:)
REAL*8, POINTER :: SSAA (:,:,:)
REAL*8, POINTER :: ASYMAA (:,:,:)
REAL*8, POINTER :: ISOPOD (:,:,:,:)
REAL*8, POINTER :: ODAER (:,:,:,:,:)
#ifdef RRTMG
REAL*8, POINTER :: RTODAER (:,:,:,:,:)
REAL*8, POINTER :: RTSSAER (:,:,:,:,:)
REAL*8, POINTER :: RTASYMAER(:,:,:,:,:)
#endif

! Other pointers
REAL(fp), POINTER :: BXHEIGHT (:,:,:)
REAL(fp), POINTER :: ERADIUS (:,:,:,:)
REAL(fp), POINTER :: TAREA (:,:,:,:)
REAL(fp), POINTER :: WERADIUS (:,:,:,:)
REAL(fp), POINTER :: WTAREA (:,:,:,:)
REAL(fp), POINTER :: ACLRADIUS(:,:,:)
REAL(fp), POINTER :: ACLAREA(:,:,:)
REAL(fp), POINTER :: ACLAREA (:,:,:)

! For diagnostics
LOGICAL :: IsWL1
Expand Down Expand Up @@ -1228,13 +1244,30 @@ SUBROUTINE RDAER( Input_Opt, State_Chm, State_Diag, State_Grid, State_Met, &
IS_POA = ( id_POA1 > 0 .AND. id_POA2 > 0 )

! Initialize pointers
BXHEIGHT => State_Met%BXHEIGHT ! Grid box height [m]
ERADIUS => State_Chm%AeroRadi ! Aerosol Radius [cm]
TAREA => State_Chm%AeroArea ! Aerosol Area [cm2/cm3]
WERADIUS => State_Chm%WetAeroRadi ! Wet Aerosol Radius [cm]
WTAREA => State_Chm%WetAeroArea ! Wet Aerosol Area [cm2/cm3]
ACLRADIUS => State_Chm%AClRadi ! Fine Cl- Radius [cm]
ACLAREA => State_Chm%AClArea ! Fine Cl- Area [cm2/cm3]
IWVREQUIRED => State_Chm%Phot%IWVREQUIRED ! WL indexes for interpolation
IWVSELECT => State_Chm%Phot%IWVSELECT ! Indexes of requested WLs
IRHARR => State_Chm%Phot%IRHARR ! Relative humidity indexes
ACOEF_WV => State_Chm%Phot%ACOEF_WV ! Coeffs for WL interpolation
BCOEF_WV => State_Chm%Phot%BCOEF_WV ! Coeffs for WL interpolation
REAA => State_Chm%Phot%REAA
QQAA => State_Chm%Phot%QQAA
ALPHAA => State_Chm%Phot%ALPHAA
SSAA => State_Chm%Phot%SSAA
ASYMAA => State_Chm%Phot%ASYMAA
ISOPOD => State_Chm%Phot%ISOPOD ! Isoprene optical depth
ODAER => State_Chm%Phot%ODAER ! Aerosol optical depth
#ifdef RRTMG
RTODAER => State_Chm%Phot%RTODAER ! Optical dust
RTSSAER => State_Chm%Phot%RTSSAER
RTASYMAER => State_Chm%Phot%RTASYMAER
#endif
BXHEIGHT => State_Met%BXHEIGHT ! Grid box height [m]
ERADIUS => State_Chm%AeroRadi ! Aerosol Radius [cm]
TAREA => State_Chm%AeroArea ! Aerosol Area [cm2/cm3]
WERADIUS => State_Chm%WetAeroRadi ! Wet Aerosol Radius [cm]
WTAREA => State_Chm%WetAeroArea ! Wet Aerosol Area [cm2/cm3]
ACLRADIUS => State_Chm%AClRadi ! Fine Cl- Radius [cm]
ACLAREA => State_Chm%AClArea ! Fine Cl- Area [cm2/cm3]

! Initialize the mapping between hygroscopic species in the
! species database and the species order in NRHAER
Expand Down Expand Up @@ -1466,12 +1499,13 @@ SUBROUTINE RDAER( Input_Opt, State_Chm, State_Diag, State_Grid, State_Met, &
IF ( LRAD ) THEN
!Loop over all RT wavelengths (30)
! plus any required for calculating the AOD
NWVS = NWVAA-NWVAA0+NWVREQUIRED
NWVS = State_Chm%Phot%NWVAA - State_Chm%Phot%NWVAA0 + &
State_Chm%Phot%NWVREQUIRED
ELSE
!Loop over wavelengths needed for
!interpolation to those requested in geoschem_config.yml
!(determined in RD_AOD)
NWVS = NWVREQUIRED
NWVS = State_Chm%Phot%NWVREQUIRED
ENDIF
ENDIF

Expand All @@ -1480,16 +1514,16 @@ SUBROUTINE RDAER( Input_Opt, State_Chm, State_Diag, State_Grid, State_Met, &
IF (ODSWITCH .EQ. 0) THEN
! only doing for 1000nm (IWV1000 is set in RD_AOD)
! N.B. NWVS is fixed to 1 above - only one wavelength
IWV=IWV1000
IWV=State_Chm%Phot%IWV1000
ELSE
IF ( LRAD ) THEN
! RRTMG wavelengths begin after NWVAA0 standard wavelengths
! but add on any others required
IF (IIWV.LE.30) THEN
!index of RRTMG wavelengths starts after the standard NWVAA0
!(currently NWVAA0=11, set in CMN_Phot_mod based on the
! .dat LUT)
IWV = IIWV+NWVAA0
!(currently NWVAA0=11, hard-coded in phot_container_mod based
! on the .dat LUT)
IWV = IIWV + State_Chm%Phot%NWVAA0
ELSE
!now we calculate at wvs for the requested AOD
IWV = IWVREQUIRED(IIWV-30)
Expand Down Expand Up @@ -2246,7 +2280,30 @@ SUBROUTINE RDAER( Input_Opt, State_Chm, State_Diag, State_Grid, State_Met, &
!TAREA(:,NDUST+NRHAER+2) = 0.d0 !SPA

! Free pointers
NULLIFY( BXHEIGHT, ERADIUS, TAREA, WERADIUS, WTAREA, ACLRADIUS, ACLAREA )
IWVREQUIRED => NULL()
IWVSELECT => NULL()
IRHARR => NULL()
ACOEF_WV => NULL()
BCOEF_WV => NULL()
REAA => NULL()
QQAA => NULL()
ALPHAA => NULL()
SSAA => NULL()
ASYMAA => NULL()
ISOPOD => NULL()
ODAER => NULL()
#ifdef RRTMG
RTODAER => NULL()
RTSSAER => NULL()
RTASYMAER => NULL()
#endif
BXHEIGHT => NULL()
ERADIUS => NULL()
TAREA => NULL()
WERADIUS => NULL()
WTAREA => NULL()
ACLRADIUS => NULL()
ACLAREA => NULL()

! Reset first-time flag
FIRST = .FALSE.
Expand Down
107 changes: 0 additions & 107 deletions GeosCore/chemistry_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,6 @@ MODULE Chemistry_Mod
!
! !PUBLIC MEMBER FUNCTIONS:
!
PUBLIC :: Init_Chemistry
PUBLIC :: Do_Chemistry
PUBLIC :: Recompute_OD
!
Expand Down Expand Up @@ -1431,110 +1430,4 @@ SUBROUTINE Chem_Passive_Species( Input_Opt, State_Chm, State_Grid, &

END SUBROUTINE Chem_Passive_Species
!EOC
!------------------------------------------------------------------------------
! GEOS-Chem Global Chemical Transport Model !
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: init_chemistry
!
! !DESCRIPTION: Subroutine INIT\_CHEMISTRY initializes chemistry
! variables.
!\\
!\\
! !INTERFACE:
!
SUBROUTINE Init_Chemistry( Input_Opt, State_Chm, State_Diag, State_Grid, RC )
!
! !USES:
!
USE ErrCode_Mod
#ifdef CLOUDJ
USE Cldj_Interface_Mod, ONLY : Init_CloudJ
#else
USE FJX_Interface_Mod, ONLY : Init_FJX
#endif
USE FullChem_Mod, ONLY : Init_FullChem
USE Input_Opt_Mod, ONLY : OptInput
USE State_Chm_Mod, ONLY : ChmState
USE State_Chm_Mod, ONLY : Ind_
USE State_Diag_Mod, ONLY : DgnState
USE State_Grid_Mod, ONLY : GrdState
!
! !INPUT PARAMETERS:
!
TYPE(GrdState), INTENT(IN) :: State_Grid ! Grid State object
!
! !INPUT/OUTPUT PARAMETERS:
!
TYPE(OptInput), INTENT(INOUT) :: Input_Opt ! Input Options object
TYPE(ChmState), INTENT(INOUT) :: State_Chm ! Chemistry State object
TYPE(DgnState), INTENT(INOUT) :: State_Diag ! Diagnostics State object
INTEGER, INTENT(INOUT) :: RC ! Success or failure?
!
! !REMARKS:
! We initialize relevant fullchem and carbon KPP mechanism variables
! here in order to use values from the Species Database. When the other
! modules are initialized (most of which are done in GC_Init_Extra), at
! that point the Species Database has not been read from the YAML file,
! so we must call Init_FullChem and Init_Carbon_Gases here.
!
! !REVISION HISTORY:
! 19 May 2014 - C. Keller - Initial version
! See https://github.com/geoschem/geos-chem for complete history
!EOP
!------------------------------------------------------------------------------
!BOC
!
! !LOCAL VARIABLES:

! SAVEd scalars
LOGICAL, SAVE :: FIRST = .TRUE.

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

!=======================================================================
! INIT_CHEMISTRY begins here!
!=======================================================================

! Initialize
RC = GC_SUCCESS
ErrMsg = ''
ThisLoc = ' -> at Init_Chemistry (in module GeosCore/chemistry_mod.F90)'

! Skip if we have already done this
IF ( FIRST ) THEN

! Adjust first flag
FIRST = .FALSE.

!--------------------------------------------------------------------
! Initialize photolysis except for carbon
!
! NOTE: we need to call this for a dry-run so that we can get
! a list of all of the lookup tables etc read by Fast-JX/Cloud-J
!--------------------------------------------------------------------
IF ( .not. Input_Opt%ITS_A_CARBON_SIM ) THEN
#ifdef CLOUDJ
CALL Init_CloudJ( Input_Opt, State_Chm, State_Diag, State_Grid, RC )
IF ( RC /= GC_SUCCESS ) THEN
ErrMsg = 'Error encountered in "Init_CloudJ"!'
CALL GC_Error( ErrMsg, RC, ThisLoc )
RETURN
ENDIF
#else
CALL Init_FJX( Input_Opt, State_Chm, State_Diag, State_Grid, RC )
IF ( RC /= GC_SUCCESS ) THEN
ErrMsg = 'Error encountered in "Init_FJX"!'
CALL GC_Error( ErrMsg, RC, ThisLoc )
RETURN
ENDIF
#endif
ENDIF

ENDIF

END SUBROUTINE Init_Chemistry
!EOC
END MODULE Chemistry_Mod
Loading

0 comments on commit 4e92687

Please sign in to comment.