Skip to content

Commit

Permalink
Fixes to enable building in GEOSgcm
Browse files Browse the repository at this point in the history
Signed-off-by: Lizzie Lundgren <elundgren@seas.harvard.edu>
  • Loading branch information
lizziel committed Feb 15, 2024
1 parent 6e7c0de commit ac1da8d
Show file tree
Hide file tree
Showing 10 changed files with 19 additions and 14 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,10 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),

### Changed
- Updated Harvard Cannon operational run scripts to use `huce_cascade` instead of `huce_intel`; also added `sapphire`
- Changed exponent 'e' to 'd' for one entry in KPP to prevent precision error in external models

### Fixed
- Fixed unit conversions in GEOS-only code

## [14.3.0] - 2024-02-07
### Added
Expand Down
1 change: 1 addition & 0 deletions Interfaces/GCHP/Chem_GridCompMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2075,6 +2075,7 @@ SUBROUTINE Run_( GC, Import, Export, Clock, Phase, RC )
USE GEOS_AeroCoupler, ONLY : GEOS_FillAeroBundle
USE GEOS_CarbonInterface, ONLY : GEOS_CarbonSetConc, &
GEOS_CarbonRunPhoto
USE UnitConv_Mod, ONLY : KG_SPECIES_PER_KG_TOTAL_AIR
#endif

!
Expand Down
2 changes: 1 addition & 1 deletion Interfaces/GEOS/Includes_After_Run.H
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@
! testing only
!if(MAPL_am_I_Root()) write(*,*) 'Copied to internal: ',I,Int2Spc(I)%ID,trim(Int2Spc(I)%Name),MINVAL(State_Chm%Species(Int2Spc(I)%ID)%Conc(:,:,LM:1:-1)),MAXVAL(State_Chm%Species(Int2Spc(I)%ID)%Conc(:,:,LM:1:-1)),SUM(State_Chm%Species(Int2Spc(I)%ID)%Conc(:,:,LM:1:-1))/IM/JM/LM
ENDDO
State_Chm%Spc_Units = 'kg/kg total'
State_Chm%Spc_Units = KG_SPECIES_PER_KG_TOTAL_AIR

!=========================================================================
! Various other archived variables needed in internal state.
Expand Down
2 changes: 1 addition & 1 deletion Interfaces/GEOS/Includes_Before_Run.H
Original file line number Diff line number Diff line change
Expand Up @@ -247,7 +247,7 @@
ENDIF
!IF ( MAPL_am_I_Root() ) WRITE(*,*) 'Copying from internal: ',I,Int2Spc(I)%ID,MINVAL(Int2Spc(I)%Internal(:,:,:)),MAXVAL(Int2Spc(I)%Internal(:,:,:)),SUM(Int2Spc(I)%Internal(:,:,:))/IM/JM/LM
ENDDO
State_Chm%Spc_Units = 'kg/kg total'
State_Chm%Spc_Units = KG_SPECIES_PER_KG_TOTAL_AIR

!=========================================================================
! Various other archived variables needed in internal state. Eventually,
Expand Down
2 changes: 1 addition & 1 deletion Interfaces/GEOS/geos_CarbonInterface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -504,7 +504,7 @@ SUBROUTINE GEOS_CarbonSetConc( Import, Input_Opt, State_Chm, &
!
CHARACTER(LEN=*), PARAMETER :: myname = 'GEOS_CarbonSetConc'
CHARACTER(LEN=*), PARAMETER :: Iam = myname
CHARACTER(LEN=63) :: OrigUnit
INTEGER :: OrigUnit
INTEGER :: I, LM, indCO2, indCO, STATUS
REAL, POINTER :: CO2(:,:,:) => null()
REAL, POINTER :: COmeso(:,:) => null()
Expand Down
14 changes: 7 additions & 7 deletions Interfaces/GEOS/geos_interface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -278,7 +278,7 @@ SUBROUTINE GEOS_RATSandOxDiags( GC, Internal, Export, Input_Opt, State_Met, &
!
! !USES:
!
USE UnitConv_Mod, ONLY : Convert_Spc_Units
USE UnitConv_Mod
!
! !INPUT/OUTPUT PARAMETERS:
!
Expand Down Expand Up @@ -326,7 +326,7 @@ SUBROUTINE GEOS_RATSandOxDiags( GC, Internal, Export, Input_Opt, State_Met, &
REAL, POINTER :: PTR_O1D(:,:,:) => NULL()
REAL, ALLOCATABLE :: OXLOCAL(:,:,:)
LOGICAL :: NeedO3
CHARACTER(LEN=ESMF_MAXSTR) :: OrigUnit
INTEGER :: OrigUnit

__Iam__('GEOS_RATSandOxDiags')

Expand Down Expand Up @@ -461,7 +461,7 @@ SUBROUTINE GEOS_SetH2O( GC, Input_Opt, State_Met, &
!
! !USES:
!
USE UnitConv_Mod, ONLY : Convert_Spc_Units
USE UnitConv_Mod
!
! !INPUT/OUTPUT PARAMETERS:
!
Expand All @@ -488,8 +488,8 @@ SUBROUTINE GEOS_SetH2O( GC, Input_Opt, State_Met, &
!
! LOCAL VARIABLES:
!
INTEGER :: IndH2O, LM
CHARACTER(LEN=ESMF_MAXSTR) :: OrigUnit
INTEGER :: IndH2O, LM
INTEGER :: OrigUnit

__Iam__('GEOS_SetH2O')

Expand Down Expand Up @@ -1218,7 +1218,7 @@ SUBROUTINE GEOS_Diagnostics( GC, IMPORT, EXPORT, Clock, Phase, &
! !USES:
!
USE Diagnostics_Mod, ONLY : Set_Diagnostics_EndofTimestep
USE UnitConv_Mod, ONLY : Convert_Spc_Units
USE UnitConv_Mod
!
! !INPUT/OUTPUT PARAMETERS:
!
Expand Down Expand Up @@ -1276,7 +1276,7 @@ SUBROUTINE GEOS_Diagnostics( GC, IMPORT, EXPORT, Clock, Phase, &
REAL, POINTER :: LFR(:,:) => NULL()
REAL, POINTER :: CNV_FRC(:,:) => NULL()

CHARACTER(LEN=ESMF_MAXSTR) :: OrigUnit
INTEGER :: OrigUnit

__Iam__('GEOS_Diagnostics')

Expand Down
2 changes: 1 addition & 1 deletion KPP/custom/custom.eqn
Original file line number Diff line number Diff line change
Expand Up @@ -707,7 +707,7 @@ HO2 + O = OH + O2 : GCARR_ac(3.00d-11, 200.0d0);
O1D + O3 = O + 1.500O2 : 2.40d-10; {2014/02/03; Eastham2014; SDE}
OCS + O = CO + SO2 : GCARR_ac(2.10d-11, -2200.0d0); {2014/02/03; Eastham2014; SDE}
OCS + OH = CO2 + SO2 : GCARR_ac(7.20d-14, -1070.0d0); {2023/04/18; JPL 19-5; KHB}
NO2 + O = NO + O2 : GCJPLAC_ababac(3.4e-31, 1.6d0, 2.3d-11, 0.2d0, 5.3d-12, 2.0d2, 0.6d0); {2023/04/18; JPL 19-5; KHB}
NO2 + O = NO + O2 : GCJPLAC_ababac(3.4d-31, 1.6d0, 2.3d-11, 0.2d0, 5.3d-12, 2.0d2, 0.6d0); {2023/04/18; JPL 19-5; KHB}
NO3 + O = NO2 + O2 : 1.30d-11; {2023/04/18; JPL 19-5; KHB}
NO + O {+M} = NO2 {+M} : GCJPLPR_aba(9.00d-32, 1.5d+00, 3.0d-11, 0.6d0); {2014/02/03; Eastham2014; SDE}
NO2 + O {+M} = NO3 {+M} : GCJPLPR_abab(3.4d-31, 1.6d0, 2.3d-11, 0.2d0, 0.6d0); {2023/04/18; JPL 19-5; KHB}
Expand Down
2 changes: 1 addition & 1 deletion KPP/fullchem/fullchem.eqn
Original file line number Diff line number Diff line change
Expand Up @@ -705,7 +705,7 @@ HO2 + O = OH + O2 : GCARR_ac(3.00d-11, 200.0d0);
O1D + O3 = O + 1.500O2 : 2.40d-10; {2014/02/03; Eastham2014; SDE}
OCS + O = CO + SO2 : GCARR_ac(2.10d-11, -2200.0d0); {2014/02/03; Eastham2014; SDE}
OCS + OH = CO2 + SO2 : GCARR_ac(7.20d-14, -1070.0d0); {2023/04/18; JPL 19-5; KHB}
NO2 + O = NO + O2 : GCJPLAC_ababac(3.4e-31, 1.6d0, 2.3d-11, 0.2d0, 5.3d-12, 2.0d2, 0.6d0); {2023/04/18; JPL 19-5; KHB}
NO2 + O = NO + O2 : GCJPLAC_ababac(3.4d-31, 1.6d0, 2.3d-11, 0.2d0, 5.3d-12, 2.0d2, 0.6d0); {2023/04/18; JPL 19-5; KHB}
NO3 + O = NO2 + O2 : 1.30d-11; {2023/04/18; JPL 19-5; KHB}
NO + O {+M} = NO2 {+M} : GCJPLPR_aba(9.00d-32, 1.5d+00, 3.0d-11, 0.6d0); {2014/02/03; Eastham2014; SDE}
NO2 + O {+M} = NO3 {+M} : GCJPLPR_abab(3.4d-31, 1.6d0, 2.3d-11, 0.2d0, 0.6d0); {2023/04/18; JPL 19-5; KHB}
Expand Down
2 changes: 1 addition & 1 deletion KPP/fullchem/gckpp_Rates.F90
Original file line number Diff line number Diff line change
Expand Up @@ -619,7 +619,7 @@ SUBROUTINE Update_RCONST ( )
RCONST(186) = (2.40d-10)
RCONST(187) = (GCARR_ac(2.10d-11,-2200.0d0))
RCONST(188) = (GCARR_ac(7.20d-14,-1070.0d0))
RCONST(189) = (GCJPLAC_ababac(3.4e-31,1.6d0,2.3d-11,0.2d0,5.3d-12,2.0d2,0.6d0))
RCONST(189) = (GCJPLAC_ababac(3.4d-31,1.6d0,2.3d-11,0.2d0,5.3d-12,2.0d2,0.6d0))
RCONST(190) = (1.30d-11)
RCONST(191) = (GCJPLPR_aba(9.00d-32,1.5d+00,3.0d-11,0.6d0))
RCONST(192) = (GCJPLPR_abab(3.4d-31,1.6d0,2.3d-11,0.2d0,0.6d0))
Expand Down
2 changes: 1 addition & 1 deletion run/GEOS/geoschem_config.yml
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ operations:
activate: true
input_directories:
fastjx_input_dir: /gpfsm/dnb52/projects/p10/dasilva/fvInput/ExtData/chemistry/GEOSCHEMchem/v0.0.0/CHEM_INPUTS/FAST_JX/v2023-10/
cloudj_input_dir: /discover/nobackup/ewlundgr/data/ExtData/CLOUD_J/v2023-05/
cloudj_input_dir: /gpfsm/dnb52/projects/p10/dasilva/fvInput/ExtData/chemistry/GEOSCHEMchem/v0.0.0/CHEM_INPUTS/CLOUD_J/v2023-05/
overhead_O3:
use_online_O3_from_model: true
use_column_O3_from_met: true
Expand Down

0 comments on commit ac1da8d

Please sign in to comment.