Skip to content

Commit

Permalink
Fix type mismatch compiler error when gfortran 10 is used without '-f…
Browse files Browse the repository at this point in the history
…allow-argument-mismatch' flag (#770)

* Resolve argument mismatch errors when using gfortran

* Switch from 'use mpi' to 'use mpi_f08'

* More argument mismatch fixes

* Merge Dom's ccpp-framework and ccpp-physics feature/depend_on_mpi braches

* Check output_grid type and inline post compatibility

* If output grid is 'cubed_sphere_grid' AND inline post is turned on
print error and terminate the model.

* Use type(MPI_Comm) in io/module_wrt_grid_comp.F90
  • Loading branch information
DusanJovic-NOAA authored Mar 19, 2024
1 parent fae9bc2 commit 6942270
Show file tree
Hide file tree
Showing 13 changed files with 45 additions and 48 deletions.
1 change: 1 addition & 0 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ endif()
### CCPP
###############################################################################

set(MPI ON)
add_subdirectory(ccpp)

###############################################################################
Expand Down
2 changes: 1 addition & 1 deletion atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -450,7 +450,7 @@ end subroutine update_atmos_radiation_physics
! variable type are allocated for the global grid (without halo regions).
! </INOUT>
subroutine atmos_timestep_diagnostics(Atmos)
use mpi
use mpi_f08
implicit none
type (atmos_data_type), intent(in) :: Atmos
!--- local variables---
Expand Down
1 change: 1 addition & 0 deletions ccpp/config/ccpp_prebuild_config.py
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@
TYPEDEFS_NEW_METADATA = {
'ccpp_types' : {
'ccpp_t' : 'cdata',
'MPI_Comm' : '',
'ccpp_types' : '',
},
'machine' : {
Expand Down
28 changes: 7 additions & 21 deletions ccpp/data/GFS_typedefs.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module GFS_typedefs

use mpi_f08
use machine, only: kind_phys, kind_dbl_prec, kind_sngl_prec
use physcons, only: con_cp, con_fvirt, con_g, rholakeice, &
con_hvap, con_hfus, con_pi, con_rd, con_rv, &
Expand Down Expand Up @@ -94,7 +95,7 @@ module GFS_typedefs
type GFS_init_type
integer :: me !< my MPI-rank
integer :: master !< master MPI-rank
integer :: fcst_mpi_comm !< forecast tasks mpi communicator
type(MPI_Comm) :: fcst_mpi_comm !< forecast tasks mpi communicator
integer :: fcst_ntasks !< total number of forecast tasks
integer :: tile_num !< tile number for this MPI rank
integer :: isc !< starting i-index for this MPI-domain
Expand Down Expand Up @@ -700,7 +701,7 @@ module GFS_typedefs

integer :: me !< MPI rank designator
integer :: master !< MPI rank of master atmosphere processor
integer :: communicator !< MPI communicator
type(MPI_Comm) :: communicator !< MPI communicator
integer :: ntasks !< MPI size in communicator
integer :: nthreads !< OpenMP threads available for physics
integer :: nlunit !< unit for namelist
Expand Down Expand Up @@ -3306,7 +3307,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
real(kind=kind_phys), dimension(:), intent(in) :: bk
logical, intent(in) :: restart
logical, intent(in) :: hydrostatic
integer, intent(in) :: communicator
type(MPI_Comm), intent(in) :: communicator
integer, intent(in) :: ntasks
integer, intent(in) :: nthreads

Expand All @@ -3316,9 +3317,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
integer :: seed0
logical :: exists
real(kind=kind_phys) :: tem
real(kind=kind_phys) :: rinc(5)
real(kind=kind_sngl_prec) :: rinc4(5)
real(kind=kind_dbl_prec) :: rinc8(5)
real(kind=kind_dbl_prec) :: rinc(5)
real(kind=kind_phys) :: wrk(1)
real(kind=kind_phys), parameter :: con_hr = 3600.

Expand Down Expand Up @@ -3974,7 +3973,6 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &

real(kind=kind_phys) :: radar_tten_limits(2) = (/ limit_unspecified, limit_unspecified /)
integer :: itime
integer :: w3kindreal,w3kindint

!--- END NAMELIST VARIABLES

Expand Down Expand Up @@ -5608,19 +5606,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%cdec = -9999.
Model%clstp = -9999
rinc(1:5) = 0
call w3kind(w3kindreal,w3kindint)
if (w3kindreal == 8) then
rinc8(1:5) = 0
call w3difdat(jdat,idat,4,rinc8)
rinc = rinc8
else if (w3kindreal == 4) then
rinc4(1:5) = 0
call w3difdat(jdat,idat,4,rinc4)
rinc = rinc4
else
write(0,*)' FATAL ERROR: Invalid w3kindreal'
call abort
endif
call w3difdat(jdat,idat,4,rinc)
Model%phour = rinc(4)/con_hr
Model%fhour = (rinc(4) + Model%dtp)/con_hr
Model%zhour = mod(Model%phour,Model%fhzero)
Expand Down Expand Up @@ -6418,7 +6404,7 @@ subroutine control_print(Model)
print *, 'basic control parameters'
print *, ' me : ', Model%me
print *, ' master : ', Model%master
print *, ' communicator : ', Model%communicator
print *, ' communicator : ', Model%communicator%mpi_val
print *, ' nlunit : ', Model%nlunit
print *, ' fn_nml : ', trim(Model%fn_nml)
print *, ' fhzero : ', Model%fhzero
Expand Down
2 changes: 1 addition & 1 deletion ccpp/data/GFS_typedefs.meta
Original file line number Diff line number Diff line change
Expand Up @@ -3332,7 +3332,7 @@
long_name = MPI communicator
units = index
dimensions = ()
type = integer
type = MPI_Comm
[ntasks]
standard_name = number_of_mpi_tasks
long_name = number of MPI tasks in communicator
Expand Down
2 changes: 1 addition & 1 deletion ccpp/physics
Submodule physics updated 29 files
+8 −1 CMakeLists.txt
+1 −8 physics/GWD/cires_tauamf_data.F90
+2 −2 physics/Interstitials/UFS_SCM_NEPTUNE/GFS_debug.F90
+2 −9 physics/Interstitials/UFS_SCM_NEPTUNE/GFS_phys_time_vary.fv3.F90
+3 −15 physics/Interstitials/UFS_SCM_NEPTUNE/GFS_time_vary_pre.fv3.F90
+3 −15 physics/Interstitials/UFS_SCM_NEPTUNE/GFS_time_vary_pre.scm.F90
+22 −29 physics/Interstitials/UFS_SCM_NEPTUNE/iccninterp.F90
+13 −67 physics/Interstitials/UFS_SCM_NEPTUNE/sfcsub.F
+2 −1 physics/MP/Ferrier_Aligo/mp_fer_hires.F90
+1 −1 physics/MP/Ferrier_Aligo/mp_fer_hires.meta
+6 −23 physics/MP/Morrison_Gettelman/aerinterp.F90
+2 −2 physics/MP/NSSL/mp_nssl.F90
+1 −1 physics/MP/NSSL/mp_nssl.meta
+5 −4 physics/MP/Thompson/module_mp_thompson.F90
+3 −2 physics/MP/Thompson/mp_thompson.F90
+2 −2 physics/MP/Thompson/mp_thompson.meta
+2 −1 physics/MP/Thompson/mp_thompson_post.F90
+1 −1 physics/MP/Thompson/mp_thompson_post.meta
+3 −2 physics/Radiation/RRTMGP/rrtmgp_lw_cloud_optics.F90
+3 −2 physics/Radiation/RRTMGP/rrtmgp_lw_gas_optics.F90
+3 −1 physics/Radiation/RRTMGP/rrtmgp_lw_main.F90
+1 −1 physics/Radiation/RRTMGP/rrtmgp_lw_main.meta
+3 −2 physics/Radiation/RRTMGP/rrtmgp_sw_cloud_optics.F90
+3 −2 physics/Radiation/RRTMGP/rrtmgp_sw_gas_optics.F90
+3 −1 physics/Radiation/RRTMGP/rrtmgp_sw_main.F90
+1 −1 physics/Radiation/RRTMGP/rrtmgp_sw_main.meta
+3 −11 physics/photochem/h2ointerp.f90
+2 −1 physics/smoke_dust/rrfs_smoke_wrapper.F90
+1 −1 physics/smoke_dust/rrfs_smoke_wrapper.meta
10 changes: 6 additions & 4 deletions io/module_write_netcdf.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
!> @author Dusan Jovic @date Nov 1, 2017
module module_write_netcdf

use mpi
use mpi_f08
use esmf
use netcdf
use module_fv3_io_def,only : ideflate, quantize_mode, quantize_nsd, zstandard_level, &
Expand Down Expand Up @@ -44,13 +44,15 @@ module module_write_netcdf
!>
!> @author Dusan Jovic @date Nov 1, 2017
subroutine write_netcdf(wrtfb, filename, &
use_parallel_netcdf, mpi_comm, mype, &
use_parallel_netcdf, comm, mype, &
grid_id, rc)
!
use mpi_f08

type(ESMF_FieldBundle), intent(in) :: wrtfb
character(*), intent(in) :: filename
logical, intent(in) :: use_parallel_netcdf
integer, intent(in) :: mpi_comm
type(MPI_Comm), intent(in) :: comm
integer, intent(in) :: mype
integer, intent(in) :: grid_id
integer, optional,intent(out) :: rc
Expand Down Expand Up @@ -233,7 +235,7 @@ subroutine write_netcdf(wrtfb, filename, &
if (par) then
ncerr = nf90_create(trim(filename),&
cmode=IOR(NF90_CLOBBER,NF90_NETCDF4),&
comm=mpi_comm, info = MPI_INFO_NULL, ncid=ncid); NC_ERR_STOP(ncerr)
comm=comm%mpi_val, info = MPI_INFO_NULL%mpi_val, ncid=ncid); NC_ERR_STOP(ncerr)
else
ncerr = nf90_create(trim(filename),&
cmode=IOR(NF90_CLOBBER,NF90_NETCDF4),&
Expand Down
8 changes: 4 additions & 4 deletions io/module_write_restart_netcdf.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@

module module_write_restart_netcdf

use mpi
use mpi_f08
use esmf
use fms
use mpp_mod, only : mpp_chksum ! needed for fms 2023.02
Expand All @@ -24,13 +24,13 @@ module module_write_restart_netcdf

!----------------------------------------------------------------------------------------
subroutine write_restart_netcdf(wrtfb, filename, &
use_parallel_netcdf, mpi_comm, mype, &
use_parallel_netcdf, comm, mype, &
rc)
!
type(ESMF_FieldBundle), intent(in) :: wrtfb
character(*), intent(in) :: filename
logical, intent(in) :: use_parallel_netcdf
integer, intent(in) :: mpi_comm
type(MPI_Comm), intent(in) :: comm
integer, intent(in) :: mype
integer, optional,intent(out) :: rc
!
Expand Down Expand Up @@ -223,7 +223,7 @@ subroutine write_restart_netcdf(wrtfb, filename, &
if (par) then
ncerr = nf90_create(trim(filename),&
cmode=IOR(NF90_CLOBBER,NF90_NETCDF4),&
comm=mpi_comm, info = MPI_INFO_NULL, ncid=ncid); NC_ERR_STOP(ncerr)
comm=comm%mpi_val, info = MPI_INFO_NULL%mpi_val, ncid=ncid); NC_ERR_STOP(ncerr)
else
ncerr = nf90_create(trim(filename),&
! cmode=IOR(NF90_CLOBBER,NF90_64BIT_OFFSET),&
Expand Down
20 changes: 13 additions & 7 deletions io/module_wrt_grid_comp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module module_wrt_grid_comp
!
!---------------------------------------------------------------------------------
!
use mpi
use mpi_f08
use esmf
use fms_mod, only : uppercase
use fms
Expand Down Expand Up @@ -67,7 +67,7 @@ module module_wrt_grid_comp
integer,save :: itasks, jtasks !<-- # of write tasks in i/j direction in the current group
integer,save :: ngrids

integer,save :: wrt_mpi_comm !<-- the mpi communicator in the write comp
type(MPI_Comm),save :: wrt_mpi_comm !<-- the mpi communicator in the write comp
integer,save :: idate(7), start_time(7)
logical,save :: write_nsflip
logical,save :: change_wrtidate=.false.
Expand Down Expand Up @@ -159,7 +159,7 @@ subroutine wrt_initialize_p1(wrt_comp, imp_state_write, exp_state_write, clock,
integer,dimension(2,6) :: decomptile
integer,dimension(2) :: regDecomp !define delayout for the nest grid
integer :: fieldCount
integer :: vm_mpi_comm
type(MPI_Comm) :: vm_mpi_comm
character(40) :: fieldName
type(ESMF_Config) :: cf, cf_output_grid
type(ESMF_Info) :: info
Expand Down Expand Up @@ -242,7 +242,7 @@ subroutine wrt_initialize_p1(wrt_comp, imp_state_write, exp_state_write, clock,
!
call ESMF_VMGetCurrent(vm=VM,rc=RC)
call ESMF_VMGet(vm=VM, localPet=wrt_int_state%mype, &
petCount=wrt_int_state%petcount,mpiCommunicator=vm_mpi_comm,rc=rc)
petCount=wrt_int_state%petcount,mpiCommunicator=vm_mpi_comm%mpi_val,rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

call mpi_comm_dup(vm_mpi_comm, wrt_mpi_comm, rc)
Expand All @@ -253,7 +253,7 @@ subroutine wrt_initialize_p1(wrt_comp, imp_state_write, exp_state_write, clock,
last_write_task = ntasks -1
lprnt = lead_write_task == wrt_int_state%mype

call fms_init(wrt_mpi_comm)
call fms_init(wrt_mpi_comm%mpi_val)

! print *,'in wrt, lead_write_task=', &
! lead_write_task,'last_write_task=',last_write_task, &
Expand Down Expand Up @@ -386,6 +386,12 @@ subroutine wrt_initialize_p1(wrt_comp, imp_state_write, exp_state_write, clock,
print *,'grid_id= ', n, ' output_grid= ', trim(output_grid(n))
end if

if (trim(output_grid(n)) == 'cubed_sphere_grid' .and. wrt_int_state%write_dopost) then
write(0,*) 'wrt_initialize_p1: Inline post is not supported with cubed_sphere_grid outputs'
call ESMF_LogWrite("wrt_initialize_p1: Inline post is not supported with cubed_sphere_grid output",ESMF_LOGMSG_ERROR,rc=RC)
call ESMF_Finalize(endflag=ESMF_END_ABORT)
end if

call ESMF_ConfigGetAttribute(config=CF, value=itasks,default=1,label ='itasks:',rc=rc)
jtasks = ntasks
if(itasks > 0 ) jtasks = ntasks/itasks
Expand Down Expand Up @@ -3386,7 +3392,7 @@ subroutine ioCompRun(comp, importState, exportState, clock, rc)
logical :: thereAreVerticals
integer :: ch_dimid, timeiso_varid
character(len=ESMF_MAXSTR) :: time_iso
integer :: wrt_mpi_comm
type(MPI_Comm) :: wrt_mpi_comm
type(ESMF_VM) :: vm

rc = ESMF_SUCCESS
Expand Down Expand Up @@ -3439,7 +3445,7 @@ subroutine ioCompRun(comp, importState, exportState, clock, rc)
call ESMF_GridCompGet(comp, localPet=localPet, petCount=petCount, vm=vm, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

call ESMF_VMGet(vm=vm, mpiCommunicator=wrt_mpi_comm, rc=rc)
call ESMF_VMGet(vm=vm, mpiCommunicator=wrt_mpi_comm%mpi_val, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if (petCount > 1) then
Expand Down
6 changes: 3 additions & 3 deletions io/post_fv3.F90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module post_fv3

use mpi
use mpi_f08

use module_fv3_io_def, only : wrttasks_per_group, filename_base, &
lon1, lat1, lon2, lat2, dlon, dlat, &
Expand Down Expand Up @@ -56,7 +56,7 @@ subroutine post_run_fv3(wrt_int_state,grid_id,mype,mpicomp,lead_write, &
type(wrt_internal_state),intent(inout) :: wrt_int_state
integer,intent(in) :: grid_id
integer,intent(in) :: mype
integer,intent(in) :: mpicomp
type(MPI_Comm),intent(in) :: mpicomp
integer,intent(in) :: lead_write
integer,intent(in) :: itasks, jtasks
integer,intent(in) :: mynfhr
Expand Down Expand Up @@ -586,7 +586,7 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
type(wrt_internal_state),intent(in) :: wrt_int_state
integer,intent(in) :: grid_id
integer,intent(in) :: mype
integer,intent(in) :: mpicomp
type(MPI_Comm),intent(in) :: mpicomp
!
!-----------------------------------------------------------------------
!
Expand Down
6 changes: 3 additions & 3 deletions module_fcst_grid_comp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ module module_fcst_grid_comp
!
!---------------------------------------------------------------------------------
!
use mpi
use mpi_f08
use esmf
use nuopc

Expand Down Expand Up @@ -593,7 +593,7 @@ subroutine fcst_initialize(fcst_comp, importState, exportState, clock, rc)
call ESMF_VMGetCurrent(vm=vm,rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

call ESMF_VMGet(vm=vm, localPet=mype, mpiCommunicator=fcst_mpi_comm, &
call ESMF_VMGet(vm=vm, localPet=mype, mpiCommunicator=fcst_mpi_comm%mpi_val, &
petCount=fcst_ntasks, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
if (mype == 0) write(*,*)'in fcst comp init, fcst_ntasks=',fcst_ntasks
Expand All @@ -615,7 +615,7 @@ subroutine fcst_initialize(fcst_comp, importState, exportState, clock, rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
if (mype == 0) print *,'af ufs config,restart_interval=',restart_interval
!
call fms_init(fcst_mpi_comm)
call fms_init(fcst_mpi_comm%mpi_val)
call mpp_init()
initClock = mpp_clock_id( 'Initialization' )
call mpp_clock_begin (initClock) !nesting problem
Expand Down
5 changes: 3 additions & 2 deletions module_fv3_config.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@
!>
!> @author Jun Wang @date 01/2017
module module_fv3_config

use mpi_f08
use esmf

implicit none
Expand All @@ -18,12 +20,11 @@ module module_fv3_config
integer :: first_kdt

!> MPI communicator for the forecast grid component
integer :: fcst_mpi_comm
type(MPI_Comm) :: fcst_mpi_comm

!> Total number of mpi tasks for the forecast grid components
integer :: fcst_ntasks


!> ID number for the coupled grids
integer :: cpl_grid_id

Expand Down

0 comments on commit 6942270

Please sign in to comment.