Skip to content

Commit

Permalink
Pass am_I_Root to several HEMCO subroutines to restrict prints if usi…
Browse files Browse the repository at this point in the history
…ng MPI

This update is relevant only for use of HEMCO read routines within
MPI models. It does not impact GCHP.

Signed-off-by: Lizzie Lundgren <[email protected]>
  • Loading branch information
lizziel committed Nov 7, 2024
1 parent 3bd40ad commit d663fc9
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 16 deletions.
5 changes: 3 additions & 2 deletions src/Core/hco_driver_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ MODULE HCO_Driver_Mod
!\\
! !INTERFACE:
!
SUBROUTINE HCO_Run( HcoState, Phase, RC, IsEndStep )
SUBROUTINE HCO_Run( am_I_Root, HcoState, Phase, RC, IsEndStep )
!
! !USES:
!
Expand All @@ -75,6 +75,7 @@ SUBROUTINE HCO_Run( HcoState, Phase, RC, IsEndStep )
!
! !INPUT PARAMETERS:
!
LOGICAL, INTENT(IN ) :: am_I_Root ! Root thread?
INTEGER, INTENT(IN ) :: Phase ! Run phase (1 or 2)
LOGICAL, INTENT(IN ), OPTIONAL :: IsEndStep ! Last timestep of simulation?
!
Expand Down Expand Up @@ -162,7 +163,7 @@ SUBROUTINE HCO_Run( HcoState, Phase, RC, IsEndStep )

! Update data, as specified in ReadList.
IF ( Phase /= 2 ) THEN
CALL ReadList_Read( HcoState, RC )
CALL ReadList_Read( am_I_Root, HcoState, RC )
IF ( RC /= HCO_SUCCESS ) THEN
PRINT *, "Error in ReadList_Read called from hco_run"
RETURN
Expand Down
22 changes: 12 additions & 10 deletions src/Core/hco_readlist_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -223,7 +223,7 @@ END SUBROUTINE ReadList_Set
!\\
! !INTERFACE:
!
SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
SUBROUTINE ReadList_Read( am_I_Root, HcoState, RC, ReadAll )
!
! !USES:
!
Expand All @@ -236,6 +236,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
!
! !INPUT PARAMETERS:
!
LOGICAL, INTENT(IN ) :: am_I_Root ! root thread?
LOGICAL, OPTIONAL, INTENT(IN ) :: ReadAll ! read all fields?
!
! !INPUT/OUTPUT PARAMETERS:
Expand Down Expand Up @@ -285,7 +286,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
WRITE(MSG,*) 'Now reading once list!'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
CALL ReadList_Fill( HcoState, HcoState%ReadLists%Once, RC )
CALL ReadList_Fill( am_I_Root, HcoState, HcoState%ReadLists%Once, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in ReadList_Fill (1) called from HEMCO ReadList_Read'
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand All @@ -299,7 +300,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
WRITE(MSG,*) 'Now reading year list!'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
CALL ReadList_Fill( HcoState, HcoState%ReadLists%Year, RC )
CALL ReadList_Fill( am_I_Root, HcoState, HcoState%ReadLists%Year, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in ReadList_Fill (2) called from HEMCO ReadList_Read'
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand All @@ -313,7 +314,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
WRITE(MSG,*) 'Now reading month list!'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
CALL ReadList_Fill( HcoState, HcoState%ReadLists%Month, RC )
CALL ReadList_Fill( am_I_Root, HcoState, HcoState%ReadLists%Month, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in ReadList_Fill (3) called from HEMCO ReadList_Read'
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand All @@ -327,7 +328,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
WRITE(MSG,*) 'Now reading day list!'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
CALL ReadList_Fill( HcoState, HcoState%ReadLists%Day, RC )
CALL ReadList_Fill( am_I_Root, HcoState, HcoState%ReadLists%Day, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in ReadList_Fill (4) called from HEMCO ReadList_Read'
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand All @@ -341,7 +342,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
WRITE(MSG,*) 'Now reading hour list!'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
CALL ReadList_Fill( HcoState, HcoState%ReadLists%Hour, RC )
CALL ReadList_Fill( am_I_Root, HcoState, HcoState%ReadLists%Hour, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in ReadList_Fill (5) called from HEMCO ReadList_Read'
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand All @@ -355,7 +356,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
WRITE(MSG,*) 'Now reading 3-hour list!'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
CALL ReadList_Fill( HcoState, HcoState%ReadLists%Hour3, RC )
CALL ReadList_Fill( am_I_Root, HcoState, HcoState%ReadLists%Hour3, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in ReadList_Fill (6) called from HEMCO ReadList_Read'
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand All @@ -368,7 +369,7 @@ SUBROUTINE ReadList_Read( HcoState, RC, ReadAll )
WRITE(MSG,*) 'Now reading always list!'
CALL HCO_MSG(HcoState%Config%Err,MSG)
ENDIF
CALL ReadList_Fill( HcoState, HcoState%ReadLists%Always, RC )
CALL ReadList_Fill( am_I_Root, HcoState, HcoState%ReadLists%Always, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in called ReadList_Fill (7) from HEMCO ReadList_Read'
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand Down Expand Up @@ -407,7 +408,7 @@ END SUBROUTINE ReadList_Read
!\\
! !INTERFACE:
!
SUBROUTINE ReadList_Fill( HcoState, ReadList, RC )
SUBROUTINE ReadList_Fill( am_I_Root, HcoState, ReadList, RC )
!
! !USES:
!
Expand All @@ -422,6 +423,7 @@ SUBROUTINE ReadList_Fill( HcoState, ReadList, RC )
!
! !INPUT/OUTPUT PARAMETERS:
!
LOGICAL, INTENT(IN) :: am_I_Root ! Root thread?
TYPE(HCO_State), POINTER :: HcoState ! HEMCO state object
TYPE(ListCont), POINTER :: ReadList ! Current reading list
INTEGER, INTENT(INOUT) :: RC ! Success or failure?
Expand Down Expand Up @@ -499,7 +501,7 @@ SUBROUTINE ReadList_Fill( HcoState, ReadList, RC )
ELSE

! Read data
CALL HCOIO_DATAREAD( HcoState, Lct, RC )
CALL HCOIO_DATAREAD( am_I_Root, HcoState, Lct, RC )
IF ( RC /= HCO_SUCCESS ) THEN
MSG = 'Error in HCOIO_DATAREAD called from HEMCO ReadList_Fill: ' // TRIM(Lct%Dct%cname)
CALL HCO_ERROR( MSG, RC, THISLOC = LOC )
Expand Down
5 changes: 3 additions & 2 deletions src/Core/hcoio_dataread_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -158,14 +158,15 @@ MODULE HCOIO_DataRead_Mod
!\\
! !INTERFACE:
!
SUBROUTINE HCOIO_DataRead( HcoState, Lct, RC )
SUBROUTINE HCOIO_DataRead( am_I_Root, HcoState, Lct, RC )
!
! !USES:
!
USE HCOIO_READ_MOD, ONLY : HCOIO_READ
!
! !INPUT PARAMETERS:
!
LOGICAL, INTENT(IN) :: am_I_Root
TYPE(HCO_State), POINTER :: HcoState
TYPE(ListCont), POINTER :: Lct
!
Expand Down Expand Up @@ -203,7 +204,7 @@ SUBROUTINE HCOIO_DataRead( HcoState, Lct, RC )

! Call the HEMCO Data Input Layer
! Selection of which HCOIO module to be used is performed at compile level
CALL HCOIO_READ( HcoState, Lct, RC )
CALL HCOIO_READ( am_I_Root, HcoState, Lct, RC )

! Trap potential errors
IF ( RC /= HCO_SUCCESS ) THEN
Expand Down
5 changes: 3 additions & 2 deletions src/Core/hcoio_read_std_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ MODULE HCOIO_Read_Mod
!\\
! !INTERFACE:
!
SUBROUTINE HCOIO_Read( HcoState, Lct, RC )
SUBROUTINE HCOIO_Read( am_I_Root, HcoState, Lct, RC )
!
! !USES:
!
Expand Down Expand Up @@ -147,6 +147,7 @@ SUBROUTINE HCOIO_Read( HcoState, Lct, RC )
!
! !INPUT PARAMETERS:
!
LOGICAL, INTENT(IN) :: am_I_Root ! Root thread?
TYPE(HCO_State), POINTER :: HcoState ! HEMCO state object
TYPE(ListCont), POINTER :: Lct ! HEMCO list container
!
Expand Down Expand Up @@ -413,7 +414,7 @@ SUBROUTINE HCOIO_Read( HcoState, Lct, RC )
ELSE

! Write a mesage to stdout (HEMCO: Opening...)
WRITE( 6, 100 ) TRIM( srcFile )
IF ( am_I_Root ) WRITE( 6, 100 ) TRIM( srcFile )

ENDIF

Expand Down

0 comments on commit d663fc9

Please sign in to comment.