Skip to content

Commit

Permalink
Now pick box closest to local noon, using local time in seconds
Browse files Browse the repository at this point in the history
In time_mod.F, we have added a function GET_LOCALTIME_IN_SEC, which
returns the local time in seconds in the range 0-86400.

The local time in seconds is then used to compute the field
State_Met%IsLocalNoon.  This will be used for local noon
J-value diagnostics

Signed-off-by: Bob Yantosca <[email protected]>
  • Loading branch information
yantosca committed Apr 18, 2019
1 parent f083b7a commit 8577e97
Show file tree
Hide file tree
Showing 2 changed files with 86 additions and 11 deletions.
32 changes: 21 additions & 11 deletions GeosCore/dao_mod.F
Original file line number Diff line number Diff line change
Expand Up @@ -275,6 +275,8 @@ SUBROUTINE AIRQNT( am_I_Root, Input_Opt, State_Met,
USE PhysConstants, ONLY : AIRMW, AVO
USE Pressure_Mod
USE Time_Mod, ONLY : Get_LocalTime
USE Time_Mod, ONLY : Get_LocalTime_In_Sec
USE Time_Mod, ONLY : Get_Ts_Dyn
!
! !INPUT PARAMETERS:
!
Expand Down Expand Up @@ -388,18 +390,20 @@ SUBROUTINE AIRQNT( am_I_Root, Input_Opt, State_Met,
! !LOCAL VARIABLES:
!
! Scalars
INTEGER :: Dt_Sec
INTEGER :: I, J, L
INTEGER :: L_CG, L_TP, N
REAL(fp) :: PEdge_Top, Esat, Ev_mid, Ev_edge
REAL(fp) :: Ev_mean, PMEAN, PMEAN_DRY, EsatA
REAL(fp) :: EsatB, EsatC, EsatD, AREA_M2
REAL(fp) :: SPHU_kgkg, AVGW_moist, H, FRAC
REAL(fp) :: Pb, Pt
LOGICAL :: UpdtMR
LOGICAL :: UpdtMR

! Arrays
LOGICAL :: IsLocNoon(IIPAR,JJPAR)
REAL(f8) :: LocTime (IIPAR,JJPAR)
LOGICAL :: IsLocNoon (IIPAR,JJPAR)
REAL(f8) :: LocTime (IIPAR,JJPAR)
INTEGER :: LocTimeSec(IIPAR,JJPAR)

! Strings
CHARACTER(LEN=255) :: ErrMsg, ThisLoc
Expand Down Expand Up @@ -436,27 +440,33 @@ SUBROUTINE AIRQNT( am_I_Root, Input_Opt, State_Met,
RC = GC_SUCCESS
ErrMsg = ''
ThisLoc = ' -> at AIRQNT (in module GeosCore/dao_mod.F)'
Dt_Sec = Get_Ts_Dyn()

! Shadow variable for mixing ratio update
UpdtMR = .TRUE.
IF ( PRESENT(update_mixing_ratio) ) UpdtMR = update_mixing_ratio

! Pre-compute local solar time = UTC + Lon/15
!$OMP PARALLEL DO
!$OMP+DEFAULT( SHARED )
!$OMP+PRIVATE( I, J )
DO J = 1, JJPAR
DO I = 1, IIPAR

! Local time only depends on longitude, but longitude is a
! function of (I,J) for cubed-sphere grids. Therefore, use
! (I,J) in the call to GET_LOCALTIME. (bmy, 4/16/19)
LocTime(I,J) = GET_LOCALTIME( I, J, 1 )

! Set a flag if the location is within 1hr of local noon,
! which matches what we did for the bpch diagnostics.
! (Avoid roundoff by setting an epsilon of 0.00001.)
IsLocNoon(I,J) = ( LocTime(I,J) >= 10.99999_f8 .and.
& LocTime(I,J) <= 13.00001_f8 )
! (I,J) in the call to GET_LOCALTIME. Obtain the local time
! both in hours and in seconds (bmy, 4/18/19)
LocTime (I,J) = Get_LocalTime ( I, J, 1 )
LocTimeSec(I,J) = Get_LocalTime_In_Sec( I, J, 1 )

! Pick the boxes that are closest to local noon (12hr = 43200 s).
! Use local time in seconds, which avoids roundoff issues.
IsLocNoon(I,J) = ( LocTimeSec(I,J) <= 43200 .and.
& LocTimeSec(I,J) + Dt_Sec >= 43200 )
ENDDO
ENDDO
!$OMP END PARALLEL DO

!=============================================================
! Update air quantities
Expand Down
65 changes: 65 additions & 0 deletions GeosUtil/time_mod.F
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,7 @@ MODULE TIME_MOD
PUBLIC :: GET_DIAGb
PUBLIC :: GET_DIAGe
PUBLIC :: GET_LOCALTIME
PUBLIC :: GET_LOCALTIME_IN_SEC
PUBLIC :: GET_SEASON
PUBLIC :: GET_TS_CHEM
PUBLIC :: GET_TS_CONV
Expand Down Expand Up @@ -2120,6 +2121,70 @@ END FUNCTION GET_LOCALTIME
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Get_LocalTime_In_Sec
!
! !DESCRIPTION: Function GET\_LOCALTIME returns the local time of a grid
! box to the calling program. (bmy, 2/5/03)
!\\
!\\
! !INTERFACE:
!
FUNCTION Get_LocalTime_In_Sec( I, J, L ) RESULT( Lt_In_Sec )
!
! !USES:
!
USE GC_GRID_MOD, ONLY : GET_XMID
!
! !INPUT PARAMETERS:
!
INTEGER, INTENT(IN) :: I ! Longitude index
INTEGER, INTENT(IN) :: J ! Latitude index
INTEGER, INTENT(IN) :: L ! Level index
!
! !RETURN VALUE:
!
INTEGER :: Lt_In_Sec ! Local time [s]
!
! !REMARKS:
! Local Time = GMT + ( longitude / 15 ) since each hour of time
! corresponds to 15 degrees of longitude on the globe
!
! !REVISION HISTORY:
! 18 Apr 2019 - R. Yantosca - Initial Version
!EOP
!------------------------------------------------------------------------------
!BOC
!
! !LOCAL VARIABLES:
!
INTEGER :: Offset_Sec, UTC_In_Sec
! Compute UTC value in seconds
UTC_In_Sec = ( Hour * 3600 ) + ( Minute * 60 ) + Second
! 15 degrees of longitude on Earth is 1 hour or 3600 sec of time
! Use NINT to avoid roundoff issues
Offset_Sec = NINT( ( Get_Xmid( I, J, L ) / 15.0_f8 ) * 3600.0_f8 )
! Add offset to UTC to get local time
Lt_In_Sec = UTC_In_Sec + Offset_Sec
! Make sure that local time is in the range 0-86400
IF ( Lt_In_Sec > 86400 ) THEN
Lt_In_Sec = Lt_In_Sec - 86400
ENDIF
IF ( Lt_In_Sec < 0 ) THEN
Lt_In_Sec = Lt_In_Sec + 86400
ENDIF
END FUNCTION Get_LocalTime_In_Sec
!EOC
!------------------------------------------------------------------------------
! GEOS-Chem Global Chemical Transport Model !
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: Get_season
!
! !DESCRIPTION: Function GET\_SEASON returns the climatological season number
Expand Down

0 comments on commit 8577e97

Please sign in to comment.