Skip to content

Commit

Permalink
Update hcoi_gc_main_mod.F90 to assume BCs are 3-hourly and to only ge…
Browse files Browse the repository at this point in the history
…t from HEMCO when needed

Previously, the subroutine Get_Boundary_Conditions in hcoi_gc_main_mod.F90
was called every emissions timestep, but boundary conditions are generally
saved out every three hours and only needed to be updated at that frequency.
New routines have been added to GeosUtil/time_mod.F90 to check if it's time
to update the boundary conditions and assume the update frequency is 3-hourly.
In the future, we may want to make those routines more flexible and allow
for other update frequencies.

Signed-off-by: Melissa Sulprizio <mpayer@seas.harvard.edu>
  • Loading branch information
msulprizio committed Feb 25, 2020
1 parent 8d2a8c2 commit 722a151
Show file tree
Hide file tree
Showing 2 changed files with 190 additions and 9 deletions.
43 changes: 34 additions & 9 deletions GeosCore/hcoi_gc_main_mod.F90
Expand Up @@ -638,7 +638,7 @@ SUBROUTINE HCOI_GC_Run( am_I_Root, Input_Opt, State_Chm, State_Grid, &
USE State_Chm_Mod, ONLY : ChmState
USE State_Grid_Mod, ONLY : GrdState
USE State_Met_Mod, ONLY : MetState
USE Time_Mod, ONLY : Get_Tau
USE Time_Mod

! HEMCO routines
USE HCO_Clock_Mod, ONLY : HcoClock_Get
Expand Down Expand Up @@ -690,6 +690,9 @@ SUBROUTINE HCOI_GC_Run( am_I_Root, Input_Opt, State_Chm, State_Grid, &
CHARACTER(LEN=255) :: ThisLoc, Instr
CHARACTER(LEN=512) :: ErrMsg

! Arrays
INTEGER :: D(2) ! Variable for date and time

!=======================================================================
! HCOI_GC_RUN begins here!
!=======================================================================
Expand Down Expand Up @@ -852,11 +855,18 @@ SUBROUTINE HCOI_GC_Run( am_I_Root, Input_Opt, State_Chm, State_Grid, &
!=======================================================================
! Get boundary conditions from HEMCO (GEOS-Chem "Classic" only)
!=======================================================================
IF ( State_Grid%NestedGrid .and. &
(Phase == 0 .or. PHASE == 1) .and. notDryRun ) THEN

! Assume BCs are 3-hourly and only get from HEMCO when needed
IF ( PHASE == 0 ) THEN
D = GET_FIRST_BC_TIME()
ELSE
D = GET_BC_TIME()
ENDIF
IF ( State_Grid%NestedGrid .and. notDryRun .and. &
( Phase == 0 .or. ( PHASE == 1 .and. ITS_TIME_FOR_BC() ) ) ) THEN
IF ( Input_Opt%LTRAN ) THEN
CALL Get_Boundary_Conditions( am_I_Root, Input_Opt, State_Chm, &
State_Grid, State_Met, RC )
State_Grid, State_Met, D(1), D(2), RC )
IF ( RC /= HCO_SUCCESS ) THEN
ErrMsg = 'Error encountered in "Get_Boundary_Conditions"!'
CALL GC_Error( ErrMsg, RC, ThisLoc )
Expand Down Expand Up @@ -3483,7 +3493,7 @@ SUBROUTINE Get_Met_Fields( am_I_Root, Input_Opt, State_Chm, State_Grid, &
ENDIF
IF ( PHASE == 0 .or. ITS_TIME_FOR_A1() .and. &
.not. ITS_TIME_FOR_EXIT() ) THEN
CALL FlexGrid_Read_A1 ( D(1), D(2), Input_Opt, State_Grid, State_Met )
CALL FlexGrid_Read_A1( D(1), D(2), Input_Opt, State_Grid, State_Met )
ENDIF

!----------------------------------
Expand All @@ -3496,7 +3506,7 @@ SUBROUTINE Get_Met_Fields( am_I_Root, Input_Opt, State_Chm, State_Grid, &
ENDIF
IF ( PHASE == 0 .or. ITS_TIME_FOR_A3() .and. &
.not. ITS_TIME_FOR_EXIT() ) THEN
CALL FlexGrid_Read_A3 ( D(1), D(2), Input_Opt, State_Grid, State_Met )
CALL FlexGrid_Read_A3( D(1), D(2), Input_Opt, State_Grid, State_Met )
ENDIF

!----------------------------------
Expand Down Expand Up @@ -4530,7 +4540,8 @@ END SUBROUTINE Get_GC_Restart
! !INTERFACE:
!
SUBROUTINE Get_Boundary_Conditions( am_I_Root, Input_Opt, State_Chm, &
State_Grid, State_Met, RC )
State_Grid, State_Met, &
YYYYMMDD, HHMMSS, RC )
!
! ! USES:
!
Expand All @@ -4550,6 +4561,8 @@ SUBROUTINE Get_Boundary_Conditions( am_I_Root, Input_Opt, State_Chm, &
LOGICAL, INTENT(IN ) :: am_I_Root ! root CPU?
TYPE(OptInput), INTENT(IN ) :: Input_Opt ! Input options
TYPE(GrdState), INTENT(IN ) :: State_Grid ! Grid State
INTEGER, INTENT(IN ) :: YYYYMMDD ! GMT date
INTEGER, INTENT(IN ) :: HHMMSS ! GMT time
!
! !INPUT/OUTPUT PARAMETERS:
!
Expand All @@ -4569,6 +4582,7 @@ SUBROUTINE Get_Boundary_Conditions( am_I_Root, Input_Opt, State_Chm, &
! !LOCAL VARIABLES:
!
INTEGER :: I, J, L, N, NA ! lon, lat, lev, spc indexes
INTEGER :: t_index ! Time index
LOGICAL :: FOUND ! Found in restart file?
CHARACTER(LEN=60) :: Prefix ! utility string
CHARACTER(LEN=255) :: LOC ! routine location
Expand All @@ -4586,7 +4600,7 @@ SUBROUTINE Get_Boundary_Conditions( am_I_Root, Input_Opt, State_Chm, &
TYPE(Species), POINTER :: SpcInfo

!=================================================================
! READ_BOUNDARY_CONDITIONS begins here!
! GET_BOUNDARY_CONDITIONS begins here!
!=================================================================

! Assume success
Expand All @@ -4602,6 +4616,17 @@ SUBROUTINE Get_Boundary_Conditions( am_I_Root, Input_Opt, State_Chm, &
! Name of this routine
LOC = ' -> at Get_Boundary_Conditions (in GeosCore/hcoi_gc_main_mod.F)'

! Find the proper time-slice to read from disk
t_index = ( HHMMSS / 030000 ) + 1

! Stop w/ error if the time index is invalid
IF ( t_index < 1 .or. t_index > 8 ) THEN
WRITE( MSG, 100 ) t_index
100 FORMAT( 'Time_index value ', i5, ' must be in the range 1 to 8!' )
CALL GC_Error( MSG, RC, LOC)
RETURN
ENDIF

!=================================================================
! Read species concentrations from NetCDF [mol/mol] and
! store in State_Chm%BoundaryCond in [kg/kg dry]
Expand Down Expand Up @@ -4637,7 +4662,7 @@ SUBROUTINE Get_Boundary_Conditions( am_I_Root, Input_Opt, State_Chm, &

! Get variable from HEMCO and store in local array
CALL HCO_GetPtr( am_I_Root, HcoState, TRIM(v_name), &
Ptr3D, RC, FOUND=FOUND )
Ptr3D, RC, TIDX=t_index, FOUND=FOUND )

! Check if BCs are found
IF ( FOUND ) THEN
Expand Down
156 changes: 156 additions & 0 deletions GeosUtil/time_mod.F
Expand Up @@ -63,9 +63,11 @@ MODULE TIME_MOD
PUBLIC :: GET_A1_TIME
PUBLIC :: GET_A3_TIME
PUBLIC :: GET_I3_TIME
PUBLIC :: GET_BC_TIME
PUBLIC :: GET_FIRST_A1_TIME
PUBLIC :: GET_FIRST_A3_TIME
PUBLIC :: GET_FIRST_I3_TIME
PUBLIC :: GET_FIRST_BC_TIME
PUBLIC :: ITS_TIME_FOR_CHEM
PUBLIC :: ITS_TIME_FOR_CONV
PUBLIC :: ITS_TIME_FOR_DYN
Expand All @@ -77,6 +79,7 @@ MODULE TIME_MOD
PUBLIC :: ITS_TIME_FOR_A1
PUBLIC :: ITS_TIME_FOR_A3
PUBLIC :: ITS_TIME_FOR_I3
PUBLIC :: ITS_TIME_FOR_BC
PUBLIC :: ITS_TIME_FOR_EXIT
PUBLIC :: ITS_A_LEAPYEAR
PUBLIC :: ITS_A_NEW_YEAR
Expand Down Expand Up @@ -2440,6 +2443,74 @@ END FUNCTION GET_I3_TIME
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Get_bc_time
!
! !DESCRIPTION: Function GET\_BC\_TIME returns the correct YYYYMMDD and HHMMSS
! values that are needed to read in the next 3-hour boundary condition fields.
!\\
!\\
! !INTERFACE:
!
FUNCTION GET_BC_TIME() RESULT( DATE )
!
! !RETURN VALUE:
!
INTEGER :: DATE(2) ! YYYYMMDD and HHMMSS values
!
! !REVISION HISTORY:
! 24 Feb 2020 - M. Sulprizio- Initial version, based on GET_I3_TIME
! See the Git history with the gitk browser!
!EOP
!------------------------------------------------------------------------------
!BOC
LOGICAL, SAVE :: FIRST = .TRUE.
INTEGER :: HH, MM, SS, SECS, OFFSET

!=================================================================
! ALL MET FIELDS:
!=================================================================

IF ( FIRST ) THEN

!--------------------------------------------------------------
! FIRST-TIME ONLY! Get the proper # of hours until the next
! BC time. Also works for start times other than 0 GMT.
!--------------------------------------------------------------

! Split NHMS into hours, mins, seconds
CALL YMD_EXTRACT( NHMS, HH, MM, SS )

! Compute seconds elapsed in the 3-hour interval
SECS = MOD( HH, 3 )*3600 + MM*60 + SS

! Compute offset to next I-3 time
OFFSET = 10800 - SECS

! Get YYYY/MM/DD and hh:mm:ss to next BC time
DATE = GET_TIME_AHEAD( OFFSET )

! Reset first-time flag
FIRST = .FALSE.

ELSE

!--------------------------------------------------------------
! Other than the 1st time: Search 180 mins ahead
!--------------------------------------------------------------

! We need to read in the I-3 fields 3h (180 mins, or 10800 secs)
! ahead of time
DATE = GET_TIME_AHEAD( 10800 )

ENDIF

END FUNCTION GET_BC_TIME
!EOC
!------------------------------------------------------------------------------
! GEOS-Chem Global Chemical Transport Model !
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Get_first_a1_time
!
! !DESCRIPTION: Function GET\_FIRST\_A1\_TIME returns the correct YYYYMMDD
Expand Down Expand Up @@ -2567,6 +2638,54 @@ END FUNCTION GET_FIRST_I3_TIME
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Get_first_bc_time
!
! !DESCRIPTION: Function GET\_FIRST\_BC\_TIME returns the correct YYYYMMDD and
! HHMMSS values the first time that boundary conditions are read in from disk.
!\\
!\\
! !INTERFACE:
!
FUNCTION GET_FIRST_BC_TIME() RESULT( DATE )
!
! !RETURN VALUE:
!
INTEGER :: DATE(2) ! YYYYMMDD, HHMMSS values
!
! !REVISION HISTORY:
! 24 Feb 2020 - M. Sulprizio- Initial version, based on GET_FIRST_3_TIME
! See the Git history with the gitk browser!
!EOP
!------------------------------------------------------------------------------
!BOC
!
! !LOCAL VARIABLES:
!
INTEGER :: HH, MM, SS, SECS, OFFSET

!==================================================================
! Compute first time for boundary conditions
!==================================================================

! Split NYMS into hours, mins, seconds
CALL YMD_EXTRACT( NHMS, HH, MM, SS )

! Compute seconds elapsed in the 3-hour interval
SECS = MOD( HH, 3 )*3600 + MM*60 + SS

! Compute offset to nearest I-6 time
OFFSET = -SECS

! Get YYYY/MM/DD and hh:mm:ss to nearest I-6 time
DATE = GET_TIME_AHEAD( OFFSET )

END FUNCTION GET_FIRST_BC_TIME
!EOC
!------------------------------------------------------------------------------
! GEOS-Chem Global Chemical Transport Model !
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Its_Time_For_chem
!
! !DESCRIPTION: Function ITS\_TIME\_FOR\_CHEM returns TRUE if it is time to do
Expand Down Expand Up @@ -3020,6 +3139,43 @@ END FUNCTION ITS_TIME_FOR_I3
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Its_Time_For_bc
!
! !DESCRIPTION: Function ITS\_TIME\_FOR\_BC returns TRUE if it is time to read
! in 3-hourly boundary conditions and FALSE otherwise.
!\\
!\\
! !INTERFACE:
!
FUNCTION ITS_TIME_FOR_BC() RESULT( FLAG )
!
! !RETURN VALUE:
!
LOGICAL :: FLAG
!
! !REVISION HISTORY:
! 24 Feb 2020 - M. Sulprizio- Initial version, based on ITS_TIME_FOR_I3
! See the Git history with the gitk browser!
!EOP
!------------------------------------------------------------------------------
!BOC
!
! !LOCAL VARAIABLES:
!
LOGICAL, SAVE :: FIRST = .TRUE.
! We read in boundary conditions at 00, 03, 06, 09, 12, 15, 18, 21 GMT
FLAG = ( ( MOD( NHMS, 030000 ) == 0 ) .or. FIRST )
FIRST = .FALSE.
END FUNCTION ITS_TIME_FOR_BC
!EOC
!------------------------------------------------------------------------------
! GEOS-Chem Global Chemical Transport Model !
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Its_Time_For_exit
!
! !DESCRIPTION: Function ITS\_TIME\_FOR\_EXIT returns TRUE if it is the end of
Expand Down

0 comments on commit 722a151

Please sign in to comment.