Skip to content

Commit

Permalink
GEOS-only updates by Christoph Keller
Browse files Browse the repository at this point in the history
1. Identify internal state fields not set by restart file by determining
   if all negative in region per thread.
   NOTE: In GCHP the threshold is <= 0. Ideally both models would extract
   whether each field was skipped or bootstrapped from ESMF instead.

2. Read mass tuning factor from external file based on run grid
   resolution. Previously tuning factor was read from HEMCO_Config.rc
   and had to be manually changed every time grid resolution changed.

Signed-off-by: Lizzie Lundgren <[email protected]>
  • Loading branch information
lizziel committed Feb 14, 2023
1 parent 16541aa commit cf7d4ed
Show file tree
Hide file tree
Showing 3 changed files with 145 additions and 2 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,10 @@ All notable changes to this project will be documented in this file.
The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),
and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html).

## [Unreleased 3.6.1]
### Added
- GEOS-only updates

## [3.6.0] - 2023-02-01
### Added
- Added MAPL_ESMF compiler option for use with GCHP and GEOS
Expand Down
12 changes: 10 additions & 2 deletions src/Core/hco_restart_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -330,9 +330,13 @@ SUBROUTINE HCO_RestartGet_3D( HcoState, Name, Arr3D, &
RETURN
ENDIF

! If field is all negatives or zero assume it to be not filled
! Determine if fields has not been filled
IF ( FLD ) THEN
#if defined(MODEL_GEOS)
IF ( MAXVAL(Arr3D) < 0.0 ) FLD = .FALSE.
#else
IF ( MAXVAL(Arr3D) <= 0.0 ) FLD = .FALSE.
#endif
ENDIF

! Log output
Expand Down Expand Up @@ -491,9 +495,13 @@ SUBROUTINE HCO_RestartGet_2D( HcoState, Name, Arr2D, &
RETURN
ENDIF

! If field is all negatives or zero assume it to be not filled
! Determine if field has been filled
IF ( FLD ) THEN
#if defined(MODEL_GEOS)
IF ( MAXVAL(Arr2D) < 0.0 ) FLD = .FALSE.
#else
IF ( MAXVAL(Arr2D) <= 0.0 ) FLD = .FALSE.
#endif
ENDIF

! Log output
Expand Down
131 changes: 131 additions & 0 deletions src/Extensions/hcox_dustdead_mod.F
Original file line number Diff line number Diff line change
Expand Up @@ -603,6 +603,11 @@ SUBROUTINE HCOX_DustDead_Init ( HcoState, ExtName,
REAL(dp) :: TmpScal
LOGICAL :: FOUND
TYPE(MyInst), POINTER :: Inst
#if defined ( MODEL_GEOS )
CHARACTER(LEN=2047) :: TuningTable
CHARACTER(LEN=2047), PARAMETER :: TuningTable_Default =
& 'DustDead_TuningTable.txt'
#endif
!=================================================================
! HCOX_DUST_DEAD_INIT begins here!
Expand Down Expand Up @@ -684,6 +689,22 @@ SUBROUTINE HCOX_DustDead_Init ( HcoState, ExtName,
Inst%FLX_MSS_FDG_FCT = -999.0e0
ENDIF
#if defined ( MODEL_GEOS )
! Determine mass flux tuning factor based on grid resolution
IF ( Inst%FLX_MSS_FDG_FCT == -999.0e0 ) THEN
CALL GetExtOpt( HcoState%Config, ExtNr,
& 'Mass tuning table',
& OptValChar=TuningTable, Found=FOUND, RC=RC )
IF ( .NOT. FOUND ) TuningTable = TuningTable_Default
CALL ReadTuningFactor(HcoState, TuningTable,
& Inst%FLX_MSS_FDG_FCT, RC)
IF ( RC /= HCO_SUCCESS ) THEN
CALL HCO_ERROR( 'ERROR ReadTuningFactor', RC, THISLOC=LOC )
RETURN
ENDIF
ENDIF
#endif
! Error
IF ( Inst%FLX_MSS_FDG_FCT == -999.0e0 ) THEN
MSG = 'Mass flux tuning factor not defined. ' //
Expand Down Expand Up @@ -5754,5 +5775,115 @@ SUBROUTINE InstRemove ( Instance )

END SUBROUTINE InstRemove
!EOC
#if defined ( MODEL_GEOS )
!------------------------------------------------------------------------------
SUBROUTINE ReadTuningFactor(HcoState, TuningTable, FCT, RC )
!
USE HCO_CharTools_Mod
USE HCO_inquireMod, ONLY : findFreeLUN

! Arguments
TYPE(HCO_State), POINTER :: HcoState ! Hemco state
CHARACTER(LEN=*), INTENT(IN) :: TuningTable
REAL*8 , INTENT(INOUT) :: FCT
INTEGER , INTENT(INOUT) :: RC

! Return value

! Local variables
REAL(hp) :: AM2, RES
INTEGER :: IU, IDX
CHARACTER(LEN=7) :: CSLABEL, FNDLABEL
CHARACTER(LEN=255) :: MSG, LINE, ICSL
LOGICAL :: EX, EOF

CHARACTER(LEN=255), PARAMETER :: LOC =
& 'ReadTuningFactor (hcox_dustdead_mod)'

!================================================================
! ReadTuningFactor begins here!
!================================================================

! Enter
CALL HCO_ENTER ( HcoState%Config%Err, LOC, RC )

! Init
FCT = -999.0

! Determine resolution based on grid cell area
CSLABEL = 'UNKNOWN'
FNDLABEL = TRIM(CSLABEL)
IF ( .NOT. HcoState%Grid%AREA_M2%Alloc ) THEN
MSG = 'Warning: AREA_M2 not found, will use default number'
CALL HCO_WARNING( MSG, RC, 1, LOC )
ELSE
AM2 = SUM(HcoState%Grid%AREA_M2%Val)/(HcoState%NX*HcoState%NY)
RES = SQRT(AM2)
IF ( RES > 280.0_hp ) THEN
CSLABEL = 'C24'
ELSEIF ( RES > 140.0_hp .AND. RES <= 280.0_hp ) THEN
CSLABEL = 'C48'
ELSEIF ( RES > 70.0_hp .AND. RES <= 140.0_hp ) THEN
CSLABEL = 'C90'
ELSEIF ( RES > 35.0_hp .AND. RES <= 70.0_hp ) THEN
CSLABEL = 'C180'
ELSEIF ( RES > 17.5_hp .AND. RES <= 35.0_hp ) THEN
CSLABEL = 'C360'
ELSEIF ( RES > 8.75_hp .AND. RES <= 17.5_hp ) THEN
CSLABEL = 'C720'
ELSEIF ( RES > 4.375_hp .AND. RES <= 8.75_hp ) THEN
CSLABEL = 'C1440'
ELSEIF ( RES <= 4.375_hp ) THEN
CSLABEL = 'C2880'
ENDIF
ENDIF

! Open file
INQUIRE( FILE=TRIM(TuningTable), EXIST=EX )
IF ( .NOT. EX ) THEN
MSG = 'FILE NOT FOUND: '//TRIM(TuningTable)
CALL HCO_ERROR( MSG, RC, THISLOC=LOC )
RETURN
ENDIF
IU = findFreeLUN()
OPEN( IU, FILE=TRIM(TuningTable) )

! Search for resolution entry in file, assuming they are listed as follows:
! C360: 1.0
! C48: 2.0e2
! C90: 1.0e-4
DO
CALL HCO_ReadLine ( IU, LINE, EOF, RC )
IF ( EOF ) EXIT
IDX = INDEX( LINE, ':' )
IF ( IDX > 0 ) ICSL = ADJUSTL(LINE(1:(IDX-1)))
! If cube-sphere label matches current resolution, read factor
IF ( TRIM(ICSL)==TRIM(CSLABEL) ) THEN
READ(LINE(IDX+1:LEN(LINE)),*) FCT
FNDLABEL = TRIM(ICSL)
EXIT
ENDIF
ENDDO

! All done
CLOSE ( IU )

! Verbose
IF ( HcoState%amIRoot ) THEN
MSG = 'Read dust tuning factor from '//TRIM(TuningTable)
CALL HCO_MSG(HcoState%Config%Err,MSG, SEP1='-' )
MSG = 'Model resolution: '//TRIM(CSLABEL)
CALL HCO_MSG(HcoState%Config%Err,MSG, SEP1='-' )
MSG = 'Resolution label in file: '//TRIM(FNDLABEL)
CALL HCO_MSG(HcoState%Config%Err,MSG, SEP1='-' )
WRITE(MSG,*) 'Scale factor: ',FCT
CALL HCO_MSG(HcoState%Config%Err,MSG, SEP1='-' )
ENDIF

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

END SUBROUTINE ReadTuningFactor
#endif
END MODULE HCOX_DUSTDEAD_MOD
!EOM

0 comments on commit cf7d4ed

Please sign in to comment.