Skip to content

Commit

Permalink
Rename Clock field in State_Met to AgeOfAir for clarity
Browse files Browse the repository at this point in the history
Signed-off-by: Melissa Sulprizio <[email protected]>
  • Loading branch information
msulprizio committed Feb 1, 2019
1 parent fe165a8 commit f5a1d31
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 31 deletions.
19 changes: 10 additions & 9 deletions GeosCore/dao_mod.F
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ MODULE DAO_MOD
PUBLIC :: IS_ICE
PUBLIC :: IS_NEAR
PUBLIC :: SET_DRY_SURFACE_PRESSURE
PUBLIC :: Set_Met_Clock
PUBLIC :: Set_Met_AgeOfAir
#if defined( ESMF_ ) || defined( EXTERNAL_GRID )
PUBLIC :: GIGC_Cap_Tropopause_Prs
#endif
Expand Down Expand Up @@ -140,7 +140,7 @@ MODULE DAO_MOD
! 29 Nov 2016 - R. Yantosca - grid_mod.F90 is now gc_grid_mod.F90
! 24 Aug 2017 - M. Sulprizio- Remove support for GCAP, GEOS-4, GEOS-5 and MERRA
! 08 Mar 2018 - E. Lundgren - Add GIGC_Cap_Tropopause_Prs from GCHP gchp_util
! 21 Dec 2018 - M. Sulprizio- Add new routine Set_Met_Clock
! 21 Dec 2018 - M. Sulprizio- Add new routine Set_Met_AgeOfAir
!EOP
!------------------------------------------------------------------------------
!BOC
Expand Down Expand Up @@ -2034,16 +2034,16 @@ END SUBROUTINE COSSZA
!------------------------------------------------------------------------------
!BOP
!
! !IROUTINE: set_met_clock
! !IROUTINE: set_met_ageofair
!
! !DESCRIPTION: Subroutine SET\_MET\_CLOCK adds the time step (in seconds)
! !DESCRIPTION: Subroutine Set\_Met\_AgeOfAir adds the time step (in seconds)
! to every grid box every time step with a total sink at the surface every
! time step to reproduce GMI tracer mechanism.
!\\
!\\
! !INTERFACE:
!
SUBROUTINE Set_Met_Clock( State_Met )
SUBROUTINE Set_Met_AgeOfAir( State_Met )
!
! !USES:
!
Expand All @@ -2067,7 +2067,7 @@ SUBROUTINE Set_Met_Clock( State_Met )
REAL(fp), SAVE :: TimeStep

!=================================================================
! SET_MET_CLOCK begins here!
! SET_MET_AGEOFAIR begins here!
!=================================================================

! Get timestep [s]
Expand All @@ -2082,17 +2082,18 @@ SUBROUTINE Set_Met_Clock( State_Met )

IF ( L == 1 ) THEN
! Set the surface to a sink
State_Met%Clock(I,J,L) = 0
State_Met%AgeOfAir(I,J,L) = 0
ELSE
! Otherwise add time step [s]
State_Met%Clock(I,J,L) = State_Met%Clock(I,J,L) + TimeStep
State_Met%AgeOfAir(I,J,L) = State_Met%AgeOfAir(I,J,L) +
& TimeStep
ENDIF

ENDDO
ENDDO
ENDDO
!$OMP END PARALLEL DO

END SUBROUTINE Set_Met_Clock
END SUBROUTINE Set_Met_AgeOfAir
!EOC
END MODULE DAO_MOD
4 changes: 2 additions & 2 deletions GeosCore/main.F
Original file line number Diff line number Diff line change
Expand Up @@ -1611,8 +1611,8 @@ PROGRAM GEOS_Chem
ENDIF
! Update clock tracer
CALL Set_Met_Clock( State_Met )
! Update age of air
CALL Set_Met_AgeOfAir( State_Met )
!==============================================================
! ***** C O M P U T E P B L H E I G H T etc. *****
Expand Down
40 changes: 20 additions & 20 deletions Headers/state_met_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -205,9 +205,9 @@ MODULE State_Met_Mod
REAL(fp), POINTER :: DP_DRY_PREV (:,:,:) ! Previous State_Met%DELP_DRY

!----------------------------------------------------------------------
! Clock tracer for diagnosing age of air
! Age of air for diagnosing transport
!----------------------------------------------------------------------
INTEGER, POINTER :: CLOCK (:,:,:) ! Age of air [s]
INTEGER, POINTER :: AgeOfAir (:,:,:) ! Age of air [s]

!----------------------------------------------------------------------
! Offline land type, leaf area index, and chlorophyll fields
Expand Down Expand Up @@ -526,7 +526,7 @@ SUBROUTINE Init_State_Met( am_I_Root, State_Met, RC )
State_Met%InTroposphere => NULL()
State_Met%IsLocalNoon => NULL()
State_Met%LocalSolarTime => NULL()
State_Met%Clock => NULL()
State_Met%AgeOfAir => NULL()

!=======================================================================
! Allocate 2-D Fields
Expand Down Expand Up @@ -1694,13 +1694,13 @@ SUBROUTINE Init_State_Met( am_I_Root, State_Met, RC )
IF ( RC /= GC_SUCCESS ) RETURN

!-------------------------
! Clock [s]
! Age of Air [s]
!-------------------------
ALLOCATE( State_Met%Clock( IM, JM, LM ), STAT=RC )
CALL GC_CheckVar( 'State_Met%Clock', 0, RC )
ALLOCATE( State_Met%AgeOfAir( IM, JM, LM ), STAT=RC )
CALL GC_CheckVar( 'State_Met%AgeOfAir', 0, RC )
IF ( RC /= GC_SUCCESS ) RETURN
State_Met%Clock = 0
CALL Register_MetField( am_I_Root, 'Clock', State_Met%Clock, &
State_Met%AgeOfAir = 0
CALL Register_MetField( am_I_Root, 'AgeOfAir', State_Met%AgeOfAir, &
State_Met, RC )
IF ( RC /= GC_SUCCESS ) RETURN

Expand Down Expand Up @@ -2542,17 +2542,6 @@ SUBROUTINE Cleanup_State_Met( am_I_Root, State_Met, RC )
#endif
ENDIF

IF ( ASSOCIATED( State_Met%Clock ) ) THEN
#if defined( ESMF_ ) || defined( MODEL_WRF )
State_Met%Clock => NULL()
#else
DEALLOCATE( State_Met%Clock, STAT=RC )
CALL GC_CheckVar( 'State_Met%Clock', 2, RC )
IF ( RC /= GC_SUCCESS ) RETURN
State_Met%Clock => NULL()
#endif
ENDIF

IF ( ASSOCIATED( State_Met%CMFMC ) ) THEN
#if defined( ESMF_ ) || defined( MODEL_WRF )
State_Met%CMFMC => NULL()
Expand Down Expand Up @@ -2971,6 +2960,17 @@ SUBROUTINE Cleanup_State_Met( am_I_Root, State_Met, RC )
#endif
ENDIF

IF ( ASSOCIATED( State_Met%AgeOfAir ) ) THEN
#if defined( ESMF_ ) || defined( MODEL_WRF )
State_Met%AgeOfAir => NULL()
#else
DEALLOCATE( State_Met%AgeOfAir, STAT=RC )
CALL GC_CheckVar( 'State_Met%AgeOfAir', 2, RC )
IF ( RC /= GC_SUCCESS ) RETURN
State_Met%AgeOfAir => NULL()
#endif
ENDIF

!=======================================================================
! Fields for querying which vertical regime a grid box is in
! or if it is near local solar noon at a grid box
Expand Down Expand Up @@ -3820,7 +3820,7 @@ SUBROUTINE Get_Metadata_State_Met( am_I_Root, metadataID, Found, &
IF ( isUnits ) Units = 'mg m-3'
IF ( isRank ) Rank = 3

CASE ( 'CLOCK' )
CASE ( 'AGEOFAIR' )
IF ( isDesc ) Desc = 'Age of air'
IF ( isUnits ) Units = 's'
IF ( isRank ) Rank = 3
Expand Down

0 comments on commit f5a1d31

Please sign in to comment.