Skip to content

Commit

Permalink
Merge branch 'HEMCO' of github.com:geoschem/geos-chem into HEMCO
Browse files Browse the repository at this point in the history
Merge the fix for GetIndex2Interp into the updated HEMCO branch
containing GEOS-5 updates from Christoph Keller

Signed-off-by: Bob Yantosca <yantosca@seas.harvard.edu>
  • Loading branch information
yantosca committed Mar 7, 2019
2 parents e947fc8 + a5b56d3 commit 15eec4f
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 2 deletions.
12 changes: 11 additions & 1 deletion HEMCO/Core/hco_readlist_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -265,7 +265,10 @@ SUBROUTINE ReadList_Read( am_I_Root, HcoState, RC, ReadAll )
! Read all fields?
RdAll = .FALSE.
IF ( PRESENT(ReadAll) ) RdAll = ReadAll
IF ( HcoClock_First( HcoState%Clock, .FALSE. ) ) RdAll = .TRUE.
! Now use internal counter to determine first-time reading
! (ckeller, 02/07/2019).
!IF ( HcoClock_First( HcoState%Clock, .FALSE. ) ) RdAll = .TRUE.
IF ( HcoState%ReadLists%Counter == 0 ) RdAll = .TRUE

! Read content from one-time list on the first call
IF ( RdAll ) THEN
Expand Down Expand Up @@ -325,6 +328,9 @@ SUBROUTINE ReadList_Read( am_I_Root, HcoState, RC, ReadAll )
CALL ReadList_Fill ( am_I_Root, HcoState, HcoState%ReadLists%Always, RC )
IF ( RC /= HCO_SUCCESS ) RETURN

! Update counter
HcoState%ReadLists%Counter = HcoState%ReadLists%Counter + 1

! Leave w/ success
CALL HCO_LEAVE ( HcoState%Config%Err, RC )

Expand Down Expand Up @@ -633,6 +639,7 @@ SUBROUTINE ReadList_Init( am_I_Root, ReadLists, RC )
!
! !REVISION HISTORY:
! 20 Apr 2013 - C. Keller - Initial version
! 07 Feb 2019 - C. Keller - Added counter
!EOP
!------------------------------------------------------------------------------
!BOC
Expand Down Expand Up @@ -667,6 +674,9 @@ SUBROUTINE ReadList_Init( am_I_Root, ReadLists, RC )
ReadLists%FileInArchive = ''
ReadLists%FileLun = -1

! Initialize counter
ReadLists%Counter = 0

END SUBROUTINE ReadList_Init
!EOC
!------------------------------------------------------------------------------
Expand Down
11 changes: 11 additions & 0 deletions HEMCO/Core/hco_state_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -365,6 +365,13 @@ SUBROUTINE HcoState_Init( am_I_Root, HcoState, HcoConfig, nSpecies, RC )
IF ( RC /= HCO_SUCCESS ) RETURN
IF ( .NOT. Found ) HcoState%Options%ScaleEmis = .TRUE.

! Only shift hh/mm when applying time shift?
CALL GetExtOpt ( HcoConfig, CoreNr, 'Cap time shift', &
OptValBool=HcoState%Options%TimeShiftCap, &
Found=Found, RC=RC )
IF ( RC /= HCO_SUCCESS ) RETURN
IF ( .NOT. Found ) HcoState%Options%TimeShiftCap = .FALSE.

! Get MaxDepExp from configuration file. If not found, set to default
! value of 20.
CALL GetExtOpt ( HcoConfig, CoreNr, 'Maximum dep x ts', &
Expand Down Expand Up @@ -424,6 +431,10 @@ SUBROUTINE HcoState_Init( am_I_Root, HcoState, HcoConfig, nSpecies, RC )
CALL HCO_MSG(HcoConfig%Err,MSG)
WRITE(MSG,'(A33,F6.2)') 'Upper limit for deposition x ts: ', HcoState%Options%MaxDepExp
CALL HCO_MSG(HcoConfig%Err,MSG,SEP2='-')
WRITE(MSG,'(A33,L2)') 'Scale emissions : ', HcoState%Options%ScaleEmis
CALL HCO_MSG(HcoConfig%Err,MSG)
WRITE(MSG,'(A33,L2)') 'Cap time shift : ', HcoState%Options%TimeShiftCap
CALL HCO_MSG(HcoConfig%Err,MSG)
ENDIF

! Leave w/ success
Expand Down
34 changes: 34 additions & 0 deletions HEMCO/Core/hco_timeshift_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -220,6 +220,7 @@ SUBROUTINE TimeShift_Apply( am_I_Root, HcoState, Lct, &
!
! !REVISION HISTORY:
! 29 Feb 2016 - C. Keller - Initial version
! 19 Nov 2018 - C. Keller - Add option TimeShiftCap
!
!EOP
!------------------------------------------------------------------------------
Expand All @@ -228,6 +229,7 @@ SUBROUTINE TimeShift_Apply( am_I_Root, HcoState, Lct, &
! !LOCAL VARIABLES:
!
INTEGER :: nYr, nMt, nDy, nHr, nMn
INTEGER :: oYr, oMt, oDy
INTEGER :: SHFT, IDX
INTEGER :: YYYYMMDD, HHMMSS
REAL(dp) :: TimeShift, DAY, UTC, JD
Expand All @@ -253,6 +255,11 @@ SUBROUTINE TimeShift_Apply( am_I_Root, HcoState, Lct, &
nHr = MAX(Hr,0)
nMn = MAX(Mn,0)

! Archive original values
oYr = nYr
oMt = nMt
oDy = nDy

! Get time shift in days
TimeShift = REAL(Lct%Dct%Dta%tShift(2),dp) / 86400.0_dp

Expand Down Expand Up @@ -293,6 +300,33 @@ SUBROUTINE TimeShift_Apply( am_I_Root, HcoState, Lct, &
nHr = FLOOR ( MOD( HHMMSS, 1000000 ) / 1.0e4_dp )
nMn = FLOOR ( MOD( HHMMSS, 10000 ) / 1.0e2_dp )

! Eventually cap time shift for the same day.
IF ( HcoState%Options%TimeShiftCap ) THEN
IF ( ( nYr < oYr ) .OR. &
( nMt < oMt .AND. nYr == oYr ) .OR. &
( nDy < oDy .AND. nMt == oMt ) ) THEN
nYr = oYr
nMt = oMt
nDy = oDy
nHr = 0
nMn = 0
IF ( HCO_IsVerb(HcoState%Config%Err,3) ) THEN
MSG = 'Options set to cap time shift - set to low bound'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
ELSEIF ( nYr > oYr .OR. nMt > oMt .OR. nDy > oDy ) THEN
nYr = oYr
nMt = oMt
nDy = oDy
nHr = 23
nMn = 59
IF ( HCO_IsVerb(HcoState%Config%Err,3) ) THEN
MSG = 'Options set to cap time shift - set to high bound'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
ENDIF
ENDIF

! verbose mode
IF ( HCO_IsVerb(HcoState%Config%Err,3) ) THEN
WRITE(MSG,*) 'Adjusted time stamp of field ', TRIM(Lct%Dct%cName), ': '
Expand Down
3 changes: 3 additions & 0 deletions HEMCO/Core/hco_types_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,7 @@ MODULE HCO_TYPES_MOD
! upon level depths?
LOGICAL :: ScaleEmis ! Scale emissions by uniform scale factors set
! in HEMCO configuration file? Defaults to yes.
LOGICAL :: TimeShiftCap ! Cap time shift to same day. Defaults to no.
END TYPE HcoOpt

!=========================================================================
Expand Down Expand Up @@ -297,6 +298,7 @@ MODULE HCO_TYPES_MOD
TYPE(ListCont), POINTER :: Hour
INTEGER :: FileLun = -1 ! LUN of file in archive
CHARACTER(LEN=2023) :: FileInArchive = '' ! name of file in archive
INTEGER :: Counter = 0 ! ReadList read counter
END TYPE RdList

!-------------------------------------------------------------------------
Expand Down Expand Up @@ -532,6 +534,7 @@ MODULE HCO_TYPES_MOD
! 23 Oct 2018 - M. Sulprizio- Added derived type for external model species
! to ConfigObj to facilitate reading GEOS-Chem
! restart file via HEMCO.
! 07 Feb 2019 - C. Keller - Added ReadList read counter.
!EOP
!------------------------------------------------------------------------------
!BOC
Expand Down
6 changes: 5 additions & 1 deletion HEMCO/Interfaces/hcoi_esmf_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,8 @@ SUBROUTINE HCO_SetServices( am_I_Root, GC, HcoConfig, &
LOGICAL :: FOUND, DefaultSet
CHARACTER(LEN=31) :: cName, SpcName, OutUnit
CHARACTER(LEN=63) :: DefaultSNAME, DefaultLNAME, DefaultUnit
CHARACTER(LEN=63) :: SNAME, LNAME, UnitName
CHARACTER(LEN=63) :: SNAME, UnitName

CHARACTER(LEN=63), POINTER :: Spc(:)
TYPE(ListCont), POINTER :: CurrCont

Expand Down Expand Up @@ -280,6 +281,9 @@ SUBROUTINE HCO_SetServices( am_I_Root, GC, HcoConfig, &
DO I = 1, LEN(TRIM(ADJUSTL(UnitName)))
IF ( UnitName(I:I) == '_' ) UnitName(I:I) = ' '
ENDDO
DO I = 1, LEN(TRIM(ADJUSTL(lName)))
IF ( lName(I:I) == '_' ) lName(I:I) = ' '
ENDDO

! Add to export state
CALL MAPL_AddExportSpec(GC, &
Expand Down

0 comments on commit 15eec4f

Please sign in to comment.