Skip to content

Commit

Permalink
W3NMIN bottleneck fix (#784)
Browse files Browse the repository at this point in the history
  • Loading branch information
MatthewMasarik-NOAA authored Sep 16, 2022
1 parent ba332b3 commit 63e91ce
Show file tree
Hide file tree
Showing 2 changed files with 28 additions and 15 deletions.
17 changes: 6 additions & 11 deletions model/src/w3parall.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1204,17 +1204,13 @@ SUBROUTINE INIT_GET_JSEA_ISPROC(ISEA, JSEA, ISPROC)
#ifdef W3_S
CALL STRACE (IENT, 'INIT_GET_JSEA_ISPROC')
#endif
!!/DEBUG WRITE(740+IAPROC,*) 'PDLIB=', PDLIB
!!/DEBUG WRITE(740+IAPROC,*) 'GTYPE=', GTYPE, ' UNGTYPE=', UNGTYPE
!!/DEBUG FLUSH(740+IAPROC)
IF (.NOT. LPDLIB) THEN
JSEA = 1 + (ISEA-1)/NAPROC
ISPROC = ISEA - (JSEA-1)*NAPROC
ELSE

#ifdef W3_PDLIB
IF ((.NOT. LPDLIB ).or.(GTYPE .ne. UNGTYPE)) THEN
#endif
JSEA = 1 + (ISEA-1)/NAPROC
ISPROC = ISEA - (JSEA-1)*NAPROC
#ifdef W3_PDLIB
IF (GTYPE .ne. UNGTYPE) THEN
JSEA = 1 + (ISEA-1)/NAPROC
ISPROC = ISEA - (JSEA-1)*NAPROC
ELSE
IP_glob = MAPSF(ISEA,1)
IF (IAPROC .le. NAPROC) THEN
Expand All @@ -1225,7 +1221,6 @@ SUBROUTINE INIT_GET_JSEA_ISPROC(ISEA, JSEA, ISPROC)
ISPROC = IPGL_TO_PROC(IP_glob)
ENDIF
#endif
ENDIF
!/
!/ End of JACOBI_INIT ------------------------------------------------ /
!/
Expand Down
26 changes: 22 additions & 4 deletions model/src/w3wavemd.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ MODULE W3WAVEMD
!/ | WAVEWATCH III NOAA/NCEP |
!/ | H. L. Tolman |
!/ | FORTRAN 90 |
!/ | Last update : 22-Mar-2021 |
!/ | Last update : 13-Sep-2022 |
!/ +-----------------------------------+
!/
!/ 04-Feb-2000 : Origination. ( version 2.00 )
Expand Down Expand Up @@ -95,7 +95,9 @@ MODULE W3WAVEMD
!/ 22-Mar-2021 : Update TAUA, RHOA ( version 7.13 )
!/ 06-May-2021 : Use ARCTC and SMCTYPE options. JGLi ( version 7.13 )
!/ 19-Jul-2021 : Momentum and air density support ( version 7.14 )
!/ 11-Nov-2021 : Remove XYB since it is obsolete ( version 7.xx )
!/ 11-Nov-2021 : Remove XYB since it is obsolete ( version 7.xx )
!/ 13-Sep-2022 : Add OMP for W3NMIN loops. Hide
!/ W3NMIN in W3_DEBUGRUN for scaling. ( version 7.xx )
!/
!/ Copyright 2009-2014 National Weather Service (NWS),
!/ National Oceanic and Atmospheric Administration. All rights
Expand Down Expand Up @@ -162,7 +164,10 @@ MODULE W3WAVEMD
! Subr. Basic MPI routines.
! ----------------------------------------------------------------
!
! 5. Remarks :
! 5. Remarks : Call to W3NMIN hidden behind W3_DEBUGRUN. This call
! currently only serves to warn when one or more procs
! have no active seapoints. It has been hid as this
! dramatically increases runtime performance.
!
! 6. Switches :
!
Expand Down Expand Up @@ -1710,9 +1715,14 @@ SUBROUTINE W3WAVE ( IMOD, ODAT, TEND, STAMP, NO_OUT &
#ifdef W3_PR3
CALL W3MAPT
#endif
END IF !! GTYPE
END IF !! GTYPE

!! Hides call to W3NMIN, which currently only serves to warn when
!! one or more procs have zero active seapoints.
#ifdef W3_DEBUGRUN
CALL W3NMIN ( MAPSTA, FLAG0 )
IF ( FLAG0 .AND. IAPROC.EQ.NAPERR ) WRITE (NDSE,1030) IMOD
#endif
FLMAP = .FALSE.
END IF
!
Expand Down Expand Up @@ -4442,6 +4452,10 @@ SUBROUTINE W3NMIN ( MAPSTA, FLAG0 )
!
NMIN = NSEA
!
#ifdef W3_OMPG
!$OMP PARALLEL PRIVATE (IPROC,NLOC,ISEA,JSEA,ISPROC,IXY,NMIN)
!$OMP DO SCHEDULE (DYNAMIC,1)
#endif
DO IPROC=1, NAPROC
NLOC = 0
DO ISEA=1, NSEA
Expand All @@ -4462,6 +4476,10 @@ SUBROUTINE W3NMIN ( MAPSTA, FLAG0 )
#endif
NMIN = MIN ( NMIN , NLOC )
END DO
#ifdef W3_OMPG
!$OMP END DO
!$OMP END PARALLEL
#endif
!
FLAG0 = NMIN .EQ. 0
#ifdef W3_T
Expand Down

0 comments on commit 63e91ce

Please sign in to comment.