Skip to content

Commit

Permalink
CHGRES_CUBE GRIB2 Bug Fix
Browse files Browse the repository at this point in the history
Update chgres_cube to create the wgrib2 inventory file on one 
mpi task, instead of all tasks. When using all tasks, random failures 
can occur if one task is still writing the file while another is trying to read it.

All programs: replace instances of 'include mpif.h' with 'use mpi'.

For details, see #157.
  • Loading branch information
GeorgeGayno-NOAA authored Oct 1, 2020
1 parent 8bef319 commit 745fdbd
Show file tree
Hide file tree
Showing 16 changed files with 53 additions and 58 deletions.
8 changes: 4 additions & 4 deletions sorc/chgres_cube.fd/atmosphere.F90
Original file line number Diff line number Diff line change
Expand Up @@ -144,9 +144,9 @@ module atmosphere

subroutine atmosphere_driver(localpet)

implicit none
use mpi

include 'mpif.h'
implicit none

integer, intent(in) :: localpet

Expand Down Expand Up @@ -1407,9 +1407,9 @@ SUBROUTINE VINTG
! LANGUAGE: FORTRAN
!
!
IMPLICIT NONE
use mpi

include 'mpif.h'
IMPLICIT NONE

REAL(ESMF_KIND_R8), PARAMETER :: DLTDZ=-6.5E-3*287.05/9.80665
REAL(ESMF_KIND_R8), PARAMETER :: DLPVDRT=-2.5E6/461.50
Expand Down
3 changes: 1 addition & 2 deletions sorc/chgres_cube.fd/chgres.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ program chgres
!
!-------------------------------------------------------------------------

use mpi
use esmf

use atmosphere, only : atmosphere_driver
Expand All @@ -34,8 +35,6 @@ program chgres
! Initialize mpi and esmf environment.
!-------------------------------------------------------------------------

include 'mpif.h'

call mpi_init(ierr)

print*,"- INITIALIZE ESMF"
Expand Down
8 changes: 4 additions & 4 deletions sorc/chgres_cube.fd/input_data.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1728,9 +1728,9 @@ end subroutine read_input_atm_restart_file

subroutine read_input_atm_gaussian_netcdf_file(localpet)

implicit none
use mpi

include 'mpif.h'
implicit none

integer, intent(in) :: localpet

Expand Down Expand Up @@ -2111,9 +2111,9 @@ end subroutine read_input_atm_gaussian_netcdf_file

subroutine read_input_atm_tiled_history_file(localpet)

implicit none
use mpi

include 'mpif.h'
implicit none

integer, intent(in) :: localpet

Expand Down
15 changes: 11 additions & 4 deletions sorc/chgres_cube.fd/model_grid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -602,6 +602,8 @@ end subroutine define_input_grid_mosaic

subroutine define_input_grid_gfs_grib2(localpet, npets)

use mpi

use wgrib2api

use program_setup, only : data_dir_input_grid, &
Expand All @@ -613,7 +615,7 @@ subroutine define_input_grid_gfs_grib2(localpet, npets)

character(len=250) :: the_file

integer :: i, j, rc, clb(2), cub(2)
integer :: i, j, rc, clb(2), cub(2), ierr

real(esmf_kind_r8), allocatable :: latitude(:,:)
real(esmf_kind_r8), allocatable :: longitude(:,:)
Expand All @@ -631,10 +633,15 @@ subroutine define_input_grid_gfs_grib2(localpet, npets)
num_tiles_input_grid = 1

the_file = trim(data_dir_input_grid) // "/" // grib2_file_input_grid
print*,'- OPEN AND INVENTORY GRIB2 FILE: ',trim(the_file)
rc=grb2_mk_inv(the_file,inv_file)
if (rc /=0) call error_handler("OPENING GRIB2 FILE",rc)
if(localpet == 0) then
print*,'- OPEN AND INVENTORY GRIB2 FILE: ',trim(the_file)
rc=grb2_mk_inv(the_file,inv_file)
if (rc /=0) call error_handler("OPENING GRIB2 FILE",rc)
endif

! Wait for localpet 0 to create inventory.
call mpi_barrier(mpi_comm_world, ierr)

rc = grb2_inq(the_file,inv_file,':PRES:',':surface:',nx=i_input, ny=j_input, &
lat=lat4, lon=lon4)
if (rc /= 1) call error_handler("READING GRIB2 FILE", rc)
Expand Down
3 changes: 1 addition & 2 deletions sorc/chgres_cube.fd/search_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -34,12 +34,11 @@ subroutine search (field, mask, idim, jdim, tile, field_num, latitude)
! future upgrade.
!-----------------------------------------------------------------------

use mpi
use esmf

implicit none

include 'mpif.h'

integer, intent(in) :: idim, jdim, tile, field_num
integer(esmf_kind_i8), intent(in) :: mask(idim,jdim)

Expand Down
3 changes: 1 addition & 2 deletions sorc/chgres_cube.fd/surface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -242,6 +242,7 @@ end subroutine surface_driver

subroutine interp(localpet)

use mpi
use esmf

use input_data, only : canopy_mc_input_grid, &
Expand Down Expand Up @@ -301,8 +302,6 @@ subroutine interp(localpet)

implicit none

include 'mpif.h'

integer, intent(in) :: localpet

integer :: l(1), u(1)
Expand Down
7 changes: 3 additions & 4 deletions sorc/chgres_cube.fd/utils.f90
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
subroutine error_handler(string, rc)

implicit none
use mpi

include 'mpif.h'
implicit none

character(len=*), intent(in) :: string

Expand All @@ -18,6 +18,7 @@ end subroutine error_handler

subroutine netcdf_err( err, string )

use mpi
use netcdf

implicit none
Expand All @@ -26,8 +27,6 @@ subroutine netcdf_err( err, string )
character(len=256) :: errmsg
integer :: iret

include "mpif.h"

if( err.EQ.NF90_NOERR )return
errmsg = NF90_STRERROR(err)
print*,''
Expand Down
8 changes: 4 additions & 4 deletions sorc/global_cycle.fd/cycle.f90
Original file line number Diff line number Diff line change
Expand Up @@ -88,10 +88,10 @@ PROGRAM SFC_DRV
! Added mpi directives.
!----------------------------------------------------------------------

use mpi

IMPLICIT NONE
!
include 'mpif.h'

CHARACTER(LEN=3) :: DONST
INTEGER :: IDIM, JDIM, LSOIL, LUGB, IY, IM, ID, IH, IALB
INTEGER :: ISOT, IVEGSRC, LENSFC, ZSEA1_MM, ZSEA2_MM, IERR
Expand Down Expand Up @@ -542,9 +542,9 @@ SUBROUTINE ADJUST_NSST(RLA,RLO,SLMSK_TILE,SLMSK_FG_TILE,SKINT_TILE,&
SLMSK_GAUS, DTREF_GAUS, &
NSST_DATA

IMPLICIT NONE
USE MPI

include 'mpif.h'
IMPLICIT NONE

INTEGER, INTENT(IN) :: LENSFC, LSOIL, IDIM, JDIM, MON, DAY

Expand Down
27 changes: 13 additions & 14 deletions sorc/global_cycle.fd/read_write_data.f90
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,8 @@ subroutine write_data(slifcs,tsffcs,snofcs,tg3fcs,zorfcs, &
! let the model compute it.
!------------------------------------------------------------------

use mpi

implicit none

integer, intent(in) :: idim, jdim, lensfc, lsoil
Expand Down Expand Up @@ -118,8 +120,6 @@ subroutine write_data(slifcs,tsffcs,snofcs,tg3fcs,zorfcs, &
real(kind=4), allocatable :: lsoil_data(:), x_data(:), y_data(:)
real(kind=8), allocatable :: dum2d(:,:), dum3d(:,:,:)

include "mpif.h"

call mpi_comm_rank(mpi_comm_world, myrank, error)

write(rankch, '(i3.3)') (myrank+1)
Expand Down Expand Up @@ -853,9 +853,9 @@ SUBROUTINE READ_LAT_LON_OROG(RLA,RLO,OROG,OROG_UF,&
! THE "GRID" FILE.
!--------------------------------------------------------------

IMPLICIT NONE
USE MPI

include "mpif.h"
IMPLICIT NONE

INTEGER, INTENT(IN) :: IDIM, JDIM, IJDIM

Expand Down Expand Up @@ -985,9 +985,9 @@ SUBROUTINE NETCDF_ERR( ERR, STRING )
! AND STOP PROCESSING.
!--------------------------------------------------------------

IMPLICIT NONE
USE MPI

include 'mpif.h'
IMPLICIT NONE

INTEGER, INTENT(IN) :: ERR
CHARACTER(LEN=*), INTENT(IN) :: STRING
Expand Down Expand Up @@ -1089,9 +1089,9 @@ SUBROUTINE READ_DATA(TSFFCS,SMCFCS,SNOFCS,STCFCS, &
! SELECTED) FOR A SINGLE CUBED-SPHERE TILE.
!-----------------------------------------------------------------

IMPLICIT NONE
USE MPI

include "mpif.h"
IMPLICIT NONE

INTEGER, INTENT(IN) :: LSOIL, LENSFC

Expand Down Expand Up @@ -1541,9 +1541,9 @@ subroutine read_tf_clim_grb(file_sst,sst,rlats_sst,rlons_sst,mlat_sst,mlon_sst,m
! language: f90
!
!$$$
implicit none
use mpi

include "mpif.h"
implicit none

! declare passed variables and arrays
character(*) , intent(in ) :: file_sst
Expand Down Expand Up @@ -1691,9 +1691,9 @@ subroutine get_tf_clm_dim(file_sst,mlat_sst,mlon_sst)
! machine: ibm rs/6000 sp
!
!$$$
implicit none
use mpi

include "mpif.h"
implicit none

! declare passed variables and arrays
character(*) , intent(in ) :: file_sst
Expand Down Expand Up @@ -1844,10 +1844,9 @@ end subroutine get_dim_nc

subroutine nc_check(status)

use mpi
use netcdf

include "mpif.h"

integer, intent ( in) :: status
integer :: ierr

Expand Down
6 changes: 2 additions & 4 deletions sorc/sfc_climo_gen.fd/interp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -23,11 +23,10 @@ subroutine interp(localpet, method, input_file)
use model_grid
use source_grid
use utils
use mpi

implicit none

include 'mpif.h'

character(len=*), intent(in) :: input_file

integer :: rc, localpet
Expand Down Expand Up @@ -294,11 +293,10 @@ subroutine adjust_for_landice(field, vegt, idim, jdim, field_ch)
!-----------------------------------------------------------------------

use esmf
use mpi

implicit none

include 'mpif.h'

character(len=*), intent(in) :: field_ch

integer, intent(in) :: idim, jdim
Expand Down
3 changes: 1 addition & 2 deletions sorc/sfc_climo_gen.fd/model_grid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -85,11 +85,10 @@ subroutine define_model_grid(localpet, npets)
use netcdf
use program_setup
use utils
use mpi

implicit none

include 'mpif.h'

integer, intent(in) :: localpet, npets

character(len=500) :: the_file
Expand Down
3 changes: 1 addition & 2 deletions sorc/sfc_climo_gen.fd/output.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ subroutine output(data_one_tile, lat_one_tile, lon_one_tile, i_mdl, j_mdl, &
! time Time period to be output.
!--------------------------------------------------------------------------

use mpi
use esmf
use netcdf
use utils
Expand All @@ -36,8 +37,6 @@ subroutine output(data_one_tile, lat_one_tile, lon_one_tile, i_mdl, j_mdl, &

implicit none

include 'mpif.h'

integer, intent(in) :: i_mdl, j_mdl, tile
integer, intent(in) :: record, time, field_idx

Expand Down
4 changes: 2 additions & 2 deletions sorc/sfc_climo_gen.fd/program_setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -102,9 +102,9 @@ subroutine read_setup_namelist(localpet)
! localpet mpi task number
!-----------------------------------------------------------------------

implicit none
use mpi

include 'mpif.h'
implicit none

integer, intent(in) :: localpet

Expand Down
3 changes: 1 addition & 2 deletions sorc/sfc_climo_gen.fd/search.f90
Original file line number Diff line number Diff line change
Expand Up @@ -28,12 +28,11 @@ subroutine search (field, mask, idim, jdim, tile, field_name)
! field field after missing values are replaced
!-----------------------------------------------------------------------

use mpi
use esmf

implicit none

include 'mpif.h'

character(len=*) :: field_name

integer, intent(in) :: idim, jdim, tile
Expand Down
3 changes: 1 addition & 2 deletions sorc/sfc_climo_gen.fd/source_grid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -79,12 +79,11 @@ subroutine define_source_grid(localpet, npets, input_file)
!
!-----------------------------------------------------------------------

use mpi
use netcdf

implicit none

include 'mpif.h'

character(len=*), intent(in) :: input_file

integer, intent(in) :: localpet, npets
Expand Down
Loading

0 comments on commit 745fdbd

Please sign in to comment.