Skip to content

Commit

Permalink
Merge branch 'patch/13.3.1' into release
Browse files Browse the repository at this point in the history
  • Loading branch information
yantosca committed Nov 15, 2021
2 parents 5267748 + abca1a5 commit e9a4f1f
Show file tree
Hide file tree
Showing 9 changed files with 271 additions and 108 deletions.
6 changes: 5 additions & 1 deletion .github/ISSUE_TEMPLATE/report-a-bug-or-technical-issue.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,10 @@ labels: bug
assignees: ''

---

### What institution are you from?
Please tell us what institution you are from.

### Description of the problem
Describe your problem here. Describe the steps to reproduce the problem here, if possible.

Expand All @@ -26,4 +30,4 @@ Describe your modifications here.
### Software versions
- CMake version:
- Compilers (Intel or GNU, and version):
- NetCDF version:
- NetCDF version:
2 changes: 1 addition & 1 deletion GeosCore/YuIMN_Code.F90
Original file line number Diff line number Diff line change
Expand Up @@ -303,7 +303,7 @@ SUBROUTINE READJIMN5D( Input_Opt, RC )
RC = GC_SUCCESS

! Data directory path in shared disk space where files live
DATA_DIR = TRIM( Input_Opt%DATA_DIR ) // 'GEOS_NATIVE/TOMAS_201402/'
DATA_DIR = TRIM( Input_Opt%DATA_DIR ) // 'CHEM_INPUTS/TOMAS_201402/'

WRITE(6,*) "Read IMN look-up tables"

Expand Down
256 changes: 190 additions & 66 deletions GeosCore/fullchem_mod.F90

Large diffs are not rendered by default.

17 changes: 7 additions & 10 deletions GeosCore/planeflight_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1546,6 +1546,11 @@ SUBROUTINE PLANEFLIGHT( Input_Opt, State_Chm, State_Diag, &
! some of the legacy unit conversions were incorrect but have now been
! fixed. -- Bob Yantosca, 30 Jul 2021
!
! Also note: The calls to Convert_Spc_Units were not necessary, and have
! since been removed. Direct unit conversions for kg/kg dry -> v/v dry
! and kg/kg dry -> molec/cm3 are now done, which are more computationally
! efficient. -- Bob Yantosca, 27 Oct 2021
!
! !REVISION HISTORY:
! 08 Jul 2002 - M. Evans - Initial version
! See https://github.com/geoschem/geos-chem for complete history
Expand Down Expand Up @@ -1700,10 +1705,6 @@ SUBROUTINE PLANEFLIGHT( Input_Opt, State_Chm, State_Diag, &
! Initialize production count:
PR = 0

! Convert species units to [v/v]
CALL Convert_Spc_Units( Input_Opt, State_Chm, State_Grid, State_Met, &
'v/v dry', RC, OrigUnit=OrigUnit )

! Initialize GEOS-Chem species array
Spc => State_Chm%Species

Expand Down Expand Up @@ -2272,7 +2273,7 @@ SUBROUTINE PLANEFLIGHT( Input_Opt, State_Chm, State_Diag, &
MW_g = State_Chm%SpcData(N)%Info%MW_g
VARI(V) = Spc(I,J,L,N) * ( AIRMW / MW_g )

IF ( VARI(V) < TINY ) VARI(V) = 0.e+0_fp
IF ( VARI(V) < TINY ) VARI(V) = 0.0_fp

#ifdef TOMAS
#ifdef BPCH_DIAG
Expand Down Expand Up @@ -2310,12 +2311,8 @@ SUBROUTINE PLANEFLIGHT( Input_Opt, State_Chm, State_Diag, &

ENDDO

! Convert species units back to original unit
CALL Convert_Spc_Units( Input_Opt, State_Chm, State_Grid, State_Met, &
OrigUnit, RC )

! Free pointer
NULLIFY( Spc )
Spc => NULL()

! Write data for the Mth plane point out to disk
CALL WRITE_VARS_TO_FILE( Input_Opt, State_Grid, State_Met, M, VARI )
Expand Down
35 changes: 20 additions & 15 deletions Headers/diaglist_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -222,6 +222,7 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
IsFullChem = .FALSE.
InDefSection = .FALSE.
InFieldsSection = .FALSE.
Name = ''
LastCollName = ''

! Create DiagList object
Expand Down Expand Up @@ -259,11 +260,7 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
IF ( INDEX( Line, 'Simulation name' ) > 0 ) THEN
CALL StrSplit( Line, ':', SubStrs, N )
SELECT CASE( To_UpperCase( ADJUSTL( SubStrs(2) ) ) )
CASE( 'ACIDUPTAKE', 'APM', 'BENCHMARK', &
'COMPLEXSOA', 'COMPLEXSOA_SVPOA', 'HEMCO', &
'MARINEPOA', 'RRTMG', 'STANDARD', &
'TROPCHEM', 'TOMAS12', 'TOMAS15', &
'TOMAS30', 'TOMAS40' )
CASE( 'FULLCHEM' )
IsFullChem = .TRUE.
CASE DEFAULT
IsFullChem = .FALSE.
Expand All @@ -274,7 +271,6 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
IF ( INDEX( Line, 'Diag alt above sfc [m]' ) > 0 ) THEN
CALL StrSplit( Line, ':', SubStrs, N )
AltAboveSfc = TRIM( ADJUSTL( SubStrs(2) ) ) // 'm'
found = .TRUE.
ENDIF

! Update wavelength(s) with string in file
Expand Down Expand Up @@ -329,8 +325,13 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
CALL GC_Error( ErrMsg, RC, ThisLoc, ErrorLine )
RETURN
ENDIF

! Skip if there is a commment at the start of the line
IF ( Line(1:1) == '#' ) CYCLE

! Skip the EXPID tag at the top of the file
IF ( INDEX( Line, 'EXPID:' ) > 0 ) CYCLE

!====================================================================
! Set collection name list (uncommented names only)
!====================================================================
Expand Down Expand Up @@ -411,6 +412,7 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
InDefSection = .FALSE.
InFieldsSection = .FALSE.
LastCollName = ''
CYCLE
ENDIF

!--------------------------------------------------------------------
Expand Down Expand Up @@ -518,7 +520,6 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
RETURN
ENDIF
ENDIF

ENDIF

!-----------------------------------------------------------------
Expand All @@ -534,7 +535,7 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
IF ( AttName(1:LineInd-1) /= TRIM( LastCollName ) ) THEN
ErrMsg = 'Attribute "' // TRIM( AttName ) // ' specifies a ' // &
'value for collection "' // &
TRIM( AttName(1:LineInd-1) ) // &
TRIM( AttName(1:LineInd-1) ) // &
'", but the expected collection name is "' // &
TRIM( LastCollName ) // '". This indicates that ' // &
'the end-of-collection delimiter (i.e. "::") is ' // &
Expand Down Expand Up @@ -603,8 +604,15 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
name = CleanText( SubStrs(1) )
ENDIF

! Skip if diagnostic name is commented out
IF ( name(1:1) == '#' ) CYCLE
! Sanity check! Skip to next line if the diagnostic name is
! commented out, missing, or contains an attribute tag.
IF ( name(1:1) == '#' ) CYCLE
IF ( LEN_TRIM( name ) == 0 ) CYCLE
IF ( INDEX( name, '.template' ) > 0 ) CYCLE
IF ( INDEX( name, '.frequency' ) > 0 ) CYCLE
IF ( INDEX( name, '.duration' ) > 0 ) CYCLE
IF ( INDEX( name, '.format' ) > 0 ) CYCLE
IF ( INDEX( name, '.mode' ) > 0 ) CYCLE

! Skip if name is already in diag list
CALL Search_DiagList( am_I_Root, DiagList, name, Found, RC )
Expand Down Expand Up @@ -658,12 +666,10 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
CALL GC_Error( ErrMsg, RC, ThisLoc )
RETURN
#endif

isWildcard = .TRUE.
CALL StrSplit( name, '?', SubStrs, N )
wildcard = SubStrs(N-1)
ENDIF

! Get tag, if any
isTagged = .FALSE.
tag = ''
Expand All @@ -672,13 +678,11 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )
IF ( TRIM(state) == 'DIAG' .AND. N == 2 ) THEN
isTagged = .TRUE.
tag = SubStrs(2)
ELSEIF ( TRIM(state) == 'CHEM' &
.AND. N == 3 ) THEN
ELSE IF ( TRIM(state) == 'CHEM' .AND. N == 3 ) THEN
isTagged = .TRUE.
tag = SubStrs(3)
ENDIF
ENDIF

! Get registryID - start with the full name in HISTORY.rc
registryID = TRIM(nameAllCaps)
! Then strip off the state prefix, if any
Expand All @@ -701,6 +705,7 @@ SUBROUTINE Init_DiagList ( am_I_Root, historyConfigFile, DiagList, RC )

! Get metadataID - start with the registry ID
metadataID = registryID

! Then strip off the tag suffix, if any
IF ( isTagged ) THEN
LineInd = INDEX( TRIM(metadataID), '_' )
Expand Down
18 changes: 11 additions & 7 deletions Headers/state_chm_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2395,21 +2395,25 @@ SUBROUTINE Init_Hg_Simulation_Fields( Input_Opt, State_Chm, State_Grid, &

! Index array: Hg0 species # <--> Hg0 category #
ALLOCATE( State_Chm%Hg0_Id_List( State_Chm%N_Hg_CATS ), STAT=RC )
CALL GC_CheckVar( 'State_Chm%Hg0_Id_List', 0, RC )
IF ( RC /= GC_SUCCESS ) RETURN
State_Chm%Hg0_Id_List = 0

! Index array: Hg2 species # <--> Hg0 category #
ALLOCATE( State_Chm%Hg2_Id_List( State_Chm%N_Hg_CATS ), STAT=RC )
CALL GC_CheckVar( 'State_Chm%Hg2_Id_List', 0, RC )
IF ( RC /= GC_SUCCESS ) RETURN
State_Chm%Hg2_Id_List = 0

! Index array: HgP species # <--> Hg0 category #
ALLOCATE( State_Chm%HgP_Id_List( State_Chm%N_Hg_CATS ), STAT=RC )
CALL GC_CheckVar( 'State_Chm%HgP_Id_List', 0, RC )
IF ( RC /= GC_SUCCESS ) RETURN
State_Chm%HgP_Id_List = 0

! Hg category names
ALLOCATE( State_Chm%Hg_Cat_Name( State_Chm%N_Hg_CATS ), STAT=RC )
CALL GC_CheckVar( 'State_Chm%Hg_Cat_Name', 0, RC )
IF ( RC /= GC_SUCCESS ) RETURN
State_Chm%Hg_Cat_Name = ''

Expand Down Expand Up @@ -2438,7 +2442,7 @@ SUBROUTINE Init_Hg_Simulation_Fields( Input_Opt, State_Chm, State_Grid, &
ThisSpc => NULL()
ENDDO

! Loop over Hg categories (except the first
! Loop over Hg categories (except the first)
DO C = 2, State_Chm%N_Hg_CATS

! Hg0 tracer number corresponding to this category
Expand Down Expand Up @@ -4559,7 +4563,7 @@ SUBROUTINE Init_and_Register_R8_3D( Input_Opt, State_Chm, State_Grid, &
CHARACTER(LEN=255) :: arrayId

!========================================================================
! Init_and_Register_R4_2D begins here!
! Init_and_Register_R8_3D begins here!
!========================================================================

! Initialize
Expand Down Expand Up @@ -4664,7 +4668,7 @@ SUBROUTINE Init_and_Register_R8_4D( Input_Opt, State_Chm, State_Grid, &
CHARACTER(LEN=255) :: arrayId

!========================================================================
! Init_and_Register_R4_2D begins here!
! Init_and_Register_R8_4D begins here!
!========================================================================

! Initialize
Expand Down Expand Up @@ -4846,11 +4850,11 @@ SUBROUTINE Get_Diagnostic_Name( State_Chm, perSpc, N, name, &
! Hg simulation quantities
!---------------------------------------------------------------------

! Append the species name to the diagnostic name with an underscore
diagName = TRIM( name ) // '_' // TRIM( State_Chm%Hg_Cat_Name(N) )
! Append the category name to the diagnostic name
diagName = TRIM( name ) // TRIM( State_Chm%Hg_Cat_Name(N) )

! Append the species name to the diagnostic description
diagDesc = TRIM( desc ) // ' ' // TRIM( State_Chm%Hg_Cat_Name(N) )
! Append the category name to the description
diagDesc = TRIM( desc ) // TRIM( State_Chm%Hg_Cat_Name(N) )

ELSE

Expand Down
38 changes: 30 additions & 8 deletions run/GCClassic/createRunDir.sh
Original file line number Diff line number Diff line change
Expand Up @@ -976,7 +976,7 @@ if [[ "x${nested_sim}" == "xT" ]]; then
replace_colon_sep_val "--> NEI2011_MONMEAN" false HEMCO_Config.rc
replace_colon_sep_val "--> NEI2011_HOURLY" false HEMCO_Config.rc
fi

printf "\n -- Nested-grid simulations use global high-reoslution met fields"
printf "\n by default. To improve run time, you may choose to use cropped"
printf "\n met fields by modifying the file paths and names in HEMCO_Config.rc"
Expand All @@ -1002,17 +1002,39 @@ if [[ ${sim_name} =~ "POPs" ]]; then
fi

#--------------------------------------------------------------------
# Change timesteps for nested-grid simulations
# Transport should be 300s (5min); chemistry should be 600s (10min)
# Nested-grid simulation timesteps:
#
# 0.25 x 0.3125 : Use reduced transport timestep = 300 s (5 min)
# Use reduced chemistry timestep = 600 s (10 min)
#
# 0.5 x 0.625 : Use default transport timestep = 600 s (10 min)
# Use default chemistry timestep = 1200 s (20 min)
#
# It has been shown that fullchem nested-grid simulations on 0.5 x
# 0.625 grids will run more slowly if 300s/600s timesteps are used.
# To avoid this slowdown, it is OK to use 600s/1200s timesteps.
#
# For the 0.25 x 0.3125 grids, it is necessary to use the 300s/600s
# timesteps in order to avoid violating the Courant limit.
#
# %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
# %%% EXCEPTION: 0.5 x 0.625 CH4 simulations will use 300s/600s %%%
# %%% timesteps in order to avoid violating the Courant limit. %%%
# %%% The larger timesteps have proven to be problematic for %%%
# %%% CH4 simulations that are used to set up inversions. %%%
# %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
#--------------------------------------------------------------------
if [[ "x${domain_name}" == "xAS" ]] || \
if [[ "x${met_resolution}" == "x025x03125" ]] || \
[[ "x${met_resolution}" == "x05x0625" && "x${sim_name}" == "xCH4" ]]; then
if [[ "x${domain_name}" == "xAS" ]] || \
[[ "x${domain_name}" == "xEU" ]] || \
[[ "x${domain_name}" == "xNA" ]] || \
[[ "x${domain_name}" == "xcustom" ]]; then
cmd='s|\[sec\]: 600|\[sec\]: 300|'
sed_ie "$cmd" input.geos
cmd='s|\[sec\]: 1200|\[sec\]: 600|'
sed_ie "$cmd" input.geos
cmd='s|\[sec\]: 600|\[sec\]: 300|'
sed_ie "$cmd" input.geos
cmd='s|\[sec\]: 1200|\[sec\]: 600|'
sed_ie "$cmd" input.geos
fi
fi

# Modify default settings for GCAP simulations
Expand Down
5 changes: 5 additions & 0 deletions run/GCHP/GCHP.rc.template
Original file line number Diff line number Diff line change
Expand Up @@ -101,6 +101,11 @@ MEMORY_DEBUG_LEVEL: 0
#
WRITE_RESTART_BY_OSERVER: NO

#
# %%% Advection settings
#
EXCLUDE_ADVECTION_TRACERS: NO

#
# %%% Adjoint variables
#
Expand Down
2 changes: 2 additions & 0 deletions run/shared/cleanRunDir.sh
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,8 @@ rm -fv slurm-*
rm -fv 1
rm -fv EGRESS
rm -fv core.*
rm -fv PET*.ESMF_LogFile
rm -fv allPEs.log

# Clean data too. Prompt user to confirm they want to do this.
# perhaps asking if they want to archive before deletion.
Expand Down

0 comments on commit e9a4f1f

Please sign in to comment.