Skip to content

Commit

Permalink
Merge pull request NOAA-EMC#27 from climbfuji/update_dtc_develop_from…
Browse files Browse the repository at this point in the history
…_emc

Update dtc/develop from emc/develop 2020/03/04
  • Loading branch information
climbfuji authored Mar 9, 2020
2 parents 756ef51 + c6e17ef commit 1a385e3
Show file tree
Hide file tree
Showing 14 changed files with 1,100 additions and 249 deletions.
2 changes: 1 addition & 1 deletion atmos_cubed_sphere
10 changes: 5 additions & 5 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1740,7 +1740,7 @@ subroutine assign_importdata(rc)

! get upward LW flux: for sea ice covered area
!----------------------------------------------
fldname = 'mean_up_lw_flx'
fldname = 'mean_up_lw_flx_ice'
if (trim(impfield_name) == trim(fldname)) then
findex = QueryFieldList(ImportFieldsList,fldname)
if (importFieldsValid(findex)) then
Expand All @@ -1767,7 +1767,7 @@ subroutine assign_importdata(rc)

! get latent heat flux: for sea ice covered area
!------------------------------------------------
fldname = 'mean_laten_heat_flx'
fldname = 'mean_laten_heat_flx_atm_into_ice'
if (trim(impfield_name) == trim(fldname)) then
findex = QueryFieldList(ImportFieldsList,fldname)
if (importFieldsValid(findex)) then
Expand All @@ -1787,7 +1787,7 @@ subroutine assign_importdata(rc)

! get sensible heat flux: for sea ice covered area
!--------------------------------------------------
fldname = 'mean_sensi_heat_flx'
fldname = 'mean_sensi_heat_flx_atm_into_ice'
if (trim(impfield_name) == trim(fldname)) then
findex = QueryFieldList(ImportFieldsList,fldname)
if (importFieldsValid(findex)) then
Expand All @@ -1807,7 +1807,7 @@ subroutine assign_importdata(rc)

! get zonal compt of momentum flux: for sea ice covered area
!------------------------------------------------------------
fldname = 'mean_zonal_moment_flx'
fldname = 'stress_on_air_ice_zonal'
if (trim(impfield_name) == trim(fldname)) then
findex = QueryFieldList(ImportFieldsList,fldname)
if (importFieldsValid(findex)) then
Expand All @@ -1827,7 +1827,7 @@ subroutine assign_importdata(rc)

! get meridional compt of momentum flux: for sea ice covered area
!-----------------------------------------------------------------
fldname = 'mean_merid_moment_flx'
fldname = 'stress_on_air_ice_merid'
if (trim(impfield_name) == trim(fldname)) then
findex = QueryFieldList(ImportFieldsList,fldname)
if (importFieldsValid(findex)) then
Expand Down
108 changes: 105 additions & 3 deletions cpl/module_cap_cpl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,8 @@ subroutine realizeConnectedCplFields(state, grid,
numLevels, numSoilLayers, numTracers, &
num_diag_sfc_emis_flux, num_diag_down_flux, &
num_diag_type_down_flux, num_diag_burn_emis_flux, &
num_diag_cmass, fieldNames, fieldTypes, fieldList, rc)
num_diag_cmass, fieldNames, fieldTypes, state_tag,&
fieldList, rc)

type(ESMF_State), intent(inout) :: state
type(ESMF_Grid), intent(in) :: grid
Expand All @@ -116,6 +117,7 @@ subroutine realizeConnectedCplFields(state, grid,
integer, intent(in) :: num_diag_cmass
character(len=*), dimension(:), intent(in) :: fieldNames
character(len=*), dimension(:), intent(in) :: fieldTypes
character(len=*), intent(in) :: state_tag !< Import or export.
type(ESMF_Field), dimension(:), intent(out) :: fieldList
integer, intent(out) :: rc

Expand Down Expand Up @@ -196,10 +198,14 @@ subroutine realizeConnectedCplFields(state, grid,
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
! -- save field
fieldList(item) = field
call ESMF_LogWrite('realizeConnectedCplFields '//trim(state_tag)//' Field '//trim(fieldNames(item)) &
// ' is connected ', ESMF_LOGMSG_INFO, line=__LINE__, file=__FILE__, rc=rc)
else
! remove a not connected Field from State
call ESMF_StateRemove(state, (/trim(fieldNames(item))/), rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
call ESMF_LogWrite('realizeConnectedCplFields '//trim(state_tag)//' Field '//trim(fieldNames(item)) &
// ' is not connected ', ESMF_LOGMSG_INFO, line=__LINE__, file=__FILE__, rc=rc)
end if
end do

Expand All @@ -217,6 +223,7 @@ subroutine Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
integer :: timeslice
!
character(len=160) :: nuopcMsg
character(len=160) :: filename
integer :: rc
!
call ESMF_ClockPrint(clock_fv3, options="currTime", &
Expand All @@ -237,12 +244,18 @@ subroutine Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
timeslice = timeslice + 1
call ESMF_GridCompGet(gcomp, importState=importState, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
call ESMFPP_RegridWriteState(importState, "fv3_cap_import_", timeslice, rc=rc)
! replace with tiled field dumps
!call ESMFPP_RegridWriteState(importState, "fv3_cap_import_", timeslice, rc=rc)
write(filename,'(a,i6.6)') 'fv3_cap_import_',timeslice
call State_RWFields_tiles(importState,trim(filename), timeslice, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
call ESMF_GridCompGet(gcomp, exportState=exportState, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

call ESMFPP_RegridWriteState(exportState, "fv3_cap_export_", timeslice, rc=rc)
! replace with tiled field dumps
!call ESMFPP_RegridWriteState(exportState, "fv3_cap_export_", timeslice, rc=rc)
write(filename,'(a,i6.6)') 'fv3_cap_export_',timeslice
call State_RWFields_tiles(exportState,trim(filename), timeslice, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
endif
!
Expand Down Expand Up @@ -345,6 +358,95 @@ subroutine ESMFPP_RegridWrite(inField, outGrid, regridMethod, fileName, fieldNam

end subroutine ESMFPP_RegridWrite

!-----------------------------------------------------------------------------

! This subroutine requires ESMFv8 - for coupled FV3
subroutine State_RWFields_tiles(state,filename,timeslice,rc)

type(ESMF_State), intent(in) :: state
character(len=*), intent(in) :: fileName
integer, intent(in) :: timeslice
integer, intent(out) :: rc

! local
type(ESMF_Field) :: firstESMFFLD
type(ESMF_Field),allocatable :: flds(:)
type(ESMF_GridComp) :: IOComp
type(ESMF_Grid) :: gridFv3

character(len=256) :: msgString
integer :: i, icount, ifld
integer :: fieldcount, firstfld
character(64), allocatable :: itemNameList(:), fldNameList(:)
type(ESMF_StateItem_Flag), allocatable :: typeList(:)

character(len=*),parameter :: subname='(module_cap_cpl:State_RWFields_tiles)'

! local variables

rc = ESMF_SUCCESS
!call ESMF_LogWrite(trim(subname)//trim(filename)//": called",
!ESMF_LOGMSG_INFO, rc=rc)

call ESMF_StateGet(state, itemCount=icount, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
allocate(typeList(icount), itemNameList(icount))
call ESMF_StateGet(state, itemTypeList=typeList, itemNameList=itemNameList, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

! find first stateitem that is a field and the count of fields
firstfld = 0; fieldcount = 0
do i = icount,1,-1
if(typeList(i) == ESMF_STATEITEM_FIELD) firstfld = i
if(typeList(i) == ESMF_STATEITEM_FIELD) fieldcount = fieldcount + 1
enddo
!write(msgString,*) trim(subname)//' icount = ',icount," fieldcount =
!",fieldcount," firstfld = ",firstfld
!call ESMF_LogWrite(trim(msgString), ESMF_LOGMSG_INFO, rc=rc)

allocate(flds(fieldCount),fldNameList(fieldCount))
ifld = 1
do i = 1, icount
if(typeList(i) == ESMF_STATEITEM_FIELD) then
fldNameList(ifld) = itemNameList(i)
ifld = ifld + 1
endif
enddo

call ESMF_LogWrite(trim(subname)//": write "//trim(filename)//"tile1-tile6", ESMF_LOGMSG_INFO, rc=rc)
! get first field
call ESMF_StateGet(state, itemName=itemNameList(firstfld), field=firstESMFFLD, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__)) return ! bail out

call ESMF_FieldGet(firstESMFFLD, grid=gridFv3, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__)) return ! bail out

IOComp = ESMFIO_Create(gridFv3, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__)) return ! bail out
call ESMF_LogWrite(trim(subname)//": write "//trim(filename), ESMF_LOGMSG_INFO, rc=rc)

do ifld=1, fieldCount
call ESMF_StateGet(state, itemName=fldNameList(ifld), field=flds(ifld), rc=rc)
enddo

call ESMFIO_Write(IOComp, filename, flds, filePath='./', rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__)) return ! bail out

! -- Finalize ESMFIO
deallocate(flds)
deallocate(fldNameList)
call ESMFIO_Destroy(IOComp, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__)) call ESMF_Finalize()

!call ESMF_LogWrite(trim(subname)//trim(filename)//": finished",
!ESMF_LOGMSG_INFO, rc=rc)

end subroutine State_RWFields_tiles

!-----------------------------------------------------------------------------

Expand Down
10 changes: 5 additions & 5 deletions cpl/module_cplfields.F90
Original file line number Diff line number Diff line change
Expand Up @@ -152,12 +152,12 @@ module module_cplfields
! "inst_ice_ir_dir_albedo ", &
! "inst_ice_vis_dif_albedo ", &
! "inst_ice_vis_dir_albedo ", &
"mean_up_lw_flx ", &
"mean_laten_heat_flx ", &
"mean_sensi_heat_flx ", &
"mean_up_lw_flx_ice ", &
"mean_laten_heat_flx_atm_into_ice ", &
"mean_sensi_heat_flx_atm_into_ice ", &
! "mean_evap_rate ", &
"mean_zonal_moment_flx ", &
"mean_merid_moment_flx ", &
"stress_on_air_ice_zonal ", &
"stress_on_air_ice_merid ", &
"mean_ice_volume ", &
"mean_snow_volume ", &
"inst_tracer_up_surface_flx ", &
Expand Down
52 changes: 44 additions & 8 deletions fv3_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,8 @@ module fv3gfs_cap_mod
wrttasks_per_group, n_group, &
lead_wrttask, last_wrttask, &
output_grid, output_file, &
imo, jmo, write_nemsioflip, &
imo,jmo,ichunk2d,jchunk2d,write_nemsioflip,&
ichunk3d,jchunk3d,kchunk3d, &
write_fsyncflag, nsout_io, &
cen_lon, cen_lat, ideflate, &
lon1, lat1, lon2, lat2, dlon, dlat, &
Expand Down Expand Up @@ -235,8 +236,9 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)

integer,dimension(6) :: date, date_init
integer :: mpi_comm_atm
integer :: i, j, k, io_unit, urc
integer :: i, j, k, io_unit, urc, ierr
integer :: petcount, mype
integer :: num_output_file
logical :: isPetLocal
logical :: OPENED
character(ESMF_MAXSTR) :: name
Expand Down Expand Up @@ -307,6 +309,14 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
call ESMF_ConfigGetAttribute(config=CF,value=iau_offset,default=0,label ='iau_offset:',rc=rc)
if (iau_offset < 0) iau_offset=0

! chunksizes for netcdf_parallel
call ESMF_ConfigGetAttribute(config=CF,value=ichunk2d,default=0,label ='ichunk2d:',rc=rc)
call ESMF_ConfigGetAttribute(config=CF,value=jchunk2d,default=0,label ='jchunk2d:',rc=rc)
call ESMF_ConfigGetAttribute(config=CF,value=ichunk3d,default=0,label ='ichunk3d:',rc=rc)
call ESMF_ConfigGetAttribute(config=CF,value=jchunk3d,default=0,label ='jchunk3d:',rc=rc)
call ESMF_ConfigGetAttribute(config=CF,value=kchunk3d,default=0,label ='kchunk3d:',rc=rc)

! zlib compression flag
call ESMF_ConfigGetAttribute(config=CF,value=ideflate,default=0,label ='ideflate:',rc=rc)
if (ideflate < 0) ideflate=0

Expand Down Expand Up @@ -346,8 +356,33 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
CALL ESMF_ConfigGetAttribute(config=CF,value=filename_base(i), rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
enddo
if(mype == 0) print *,'af nems config,num_files=',num_files, &
'filename_base=',filename_base

allocate(output_file(num_files))
num_output_file = ESMF_ConfigGetLen(config=CF, label ='output_file:',rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
if (num_files == num_output_file) then
CALL ESMF_ConfigGetAttribute(CF,valueList=output_file,label='output_file:', &
count=num_files, rc=RC)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
do i = 1, num_files
if(output_file(i) /= "netcdf" .and. output_file(i) /= "netcdf_parallel") then
write(0,*)"fv3_cap.F90: only netcdf and netcdf_parallel are allowed for multiple values of output_file"
call ESMF_Finalize(endflag=ESMF_END_ABORT)
endif
enddo
else if ( num_output_file == 1) then
CALL ESMF_ConfigGetAttribute(CF,valuelist=output_file,label='output_file:', count=1, rc=RC)
output_file(1:num_files) = output_file(1)
else
output_file(1:num_files) = 'netcdf'
endif
if(mype == 0) then
print *,'af nems config,num_files=',num_files
do i=1,num_files
print *,'num_file=',i,'filename_base= ',trim(filename_base(i)),&
' output_file= ',trim(output_file(i))
enddo
endif
!
! variables for alarms
call ESMF_ConfigGetAttribute(config=CF, value=nfhout, label ='nfhout:', rc=rc)
Expand All @@ -359,10 +394,8 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)

! variables for I/O options
call ESMF_ConfigGetAttribute(config=CF, value=output_grid, label ='output_grid:',rc=rc)
call ESMF_ConfigGetAttribute(config=CF, value=output_file, label ='output_file:',rc=rc)
if (mype == 0) then
print *,'output_grid=',trim(output_grid)
print *,'output_file=',trim(output_file)
end if
write_nemsioflip =.false.
write_fsyncflag =.false.
Expand Down Expand Up @@ -880,14 +913,17 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
call realizeConnectedCplFields(exportState, fcstGrid, &
numLevels, numSoilLayers, numTracers, num_diag_sfc_emis_flux, &
num_diag_down_flux, num_diag_type_down_flux, num_diag_burn_emis_flux, &
num_diag_cmass, exportFieldsList, exportFieldTypes, exportFields, rc)
num_diag_cmass, exportFieldsList, exportFieldTypes, 'FV3 Export', &
exportFields, rc)

if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

! -- realize connected fields in importState
call realizeConnectedCplFields(importState, fcstGrid, &
numLevels, numSoilLayers, numTracers, num_diag_sfc_emis_flux, &
num_diag_down_flux, num_diag_type_down_flux, num_diag_burn_emis_flux, &
num_diag_cmass, importFieldsList, importFieldTypes, importFields, rc)
num_diag_cmass, importFieldsList, importFieldTypes, 'FV3 Import', &
importFields, rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
end if
endif
Expand Down
5 changes: 4 additions & 1 deletion gfsphysics/GFS_layer/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1074,7 +1074,7 @@ module GFS_typedefs
real(kind=kind_phys) :: iau_delthrs ! iau time interval (to scale increments) in hours
character(len=240) :: iau_inc_files(7)! list of increment files
real(kind=kind_phys) :: iaufhrs(7) ! forecast hours associated with increment files
logical :: iau_filter_increments
logical :: iau_filter_increments, iau_drymassfixer

#ifdef CCPP
! From physcons.F90, updated/set in control_initialize
Expand Down Expand Up @@ -3058,6 +3058,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
character(len=240) :: iau_inc_files(7) = '' !< list of increment files
real(kind=kind_phys) :: iaufhrs(7) = -1 !< forecast hours associated with increment files
logical :: iau_filter_increments = .false. !< filter IAU increments
logical :: iau_drymassfixer = .false. !< IAU dry mass fixer

!--- debug flag
logical :: debug = .false.
Expand Down Expand Up @@ -3170,6 +3171,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
ca_sgs, ca_global,iseed_ca,ca_smooth,isppt_deep,nspinup, &
!--- IAU
iau_delthrs,iaufhrs,iau_inc_files,iau_filter_increments, &
iau_drymassfixer, &
!--- debug options
debug, pre_rad, &
!--- parameter range for critical relative humidity
Expand Down Expand Up @@ -3650,6 +3652,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%iau_inc_files = iau_inc_files
Model%iau_delthrs = iau_delthrs
Model%iau_filter_increments = iau_filter_increments
Model%iau_drymassfixer = iau_drymassfixer
if(Model%me==0) print *,' model init,iaufhrs=',Model%iaufhrs

!--- tracer handling
Expand Down
4 changes: 2 additions & 2 deletions gfsphysics/physics/ugwp_driver_v0.f
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,8 @@ subroutine cires_ugwp_driver_v0(me, master,

real(kind=kind_phys), intent(in), dimension(im,levs) :: ugrs
&, vgrs, tgrs, qgrs, prsl, prslk, phil, del
real(kind=kind_phys), intent(in), dimension(im,levs+1) ::
& phii, prsi
real(kind=kind_phys), intent(in), dimension(im,levs+1) :: prsi
&, phii

! real(kind=kind_phys), intent(in) :: oro_stat(im,nmtvr)
real(kind=kind_phys), intent(in), dimension(im) :: hprime, oc
Expand Down
Loading

0 comments on commit 1a385e3

Please sign in to comment.