Skip to content

Commit

Permalink
add fh00 post control file, add restart output at specified forecast …
Browse files Browse the repository at this point in the history
…hours, ugwd bug fixes
  • Loading branch information
junwang-noaa committed Dec 15, 2019
1 parent 8a56781 commit 5d51b12
Show file tree
Hide file tree
Showing 10 changed files with 136 additions and 63 deletions.
4 changes: 2 additions & 2 deletions .gitmodules
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
[submodule "atmos_cubed_sphere"]
path = atmos_cubed_sphere
url = https://github.com/NOAA-EMC/GFDL_atmos_cubed_sphere
branch = dev/emc
url = https://github.com/junwang-noaa/GFDL_atmos_cubed_sphere
branch = postRstUgwd
[submodule "ccpp/framework"]
path = ccpp/framework
url = https://github.com/NCAR/ccpp-framework
Expand Down
2 changes: 1 addition & 1 deletion atmos_cubed_sphere
15 changes: 10 additions & 5 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,8 @@ module atmos_model_mod
FV3GFS_diag_register, FV3GFS_diag_output, &
DIAG_SIZE
use fv_iau_mod, only: iau_external_data_type,getiauforcing,iau_initialize
use module_fv3_config, only: output_1st_tstep_rst, first_kdt, nsout
use module_fv3_config, only: output_1st_tstep_rst, first_kdt, nsout, &
frestart, restart_endfcst

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

Expand Down Expand Up @@ -944,17 +945,21 @@ end subroutine update_atmos_model_state
subroutine atmos_model_end (Atmos)
type (atmos_data_type), intent(inout) :: Atmos
!---local variables
integer :: idx
integer :: idx, seconds
#ifdef CCPP
integer :: ierr
#endif

!-----------------------------------------------------------------------
!---- termination routine for atmospheric model ----

call atmosphere_end (Atmos % Time, Atmos%grid)
call FV3GFS_restart_write (IPD_Data, IPD_Restart, Atm_block, &
IPD_Control, Atmos%domain)
! if (mpp_pe() == mpp_root_pe() )print *,'in atmos_model_end,restart_endfcst=',restart_endfcst
call atmosphere_end (Atmos % Time, Atmos%grid, restart_endfcst)
if(restart_endfcst) then
call FV3GFS_restart_write (IPD_Data, IPD_Restart, Atm_block, &
IPD_Control, Atmos%domain)
! if (mpp_pe() == mpp_root_pe() )print *,'in atmos_model_end,write final restart'
endif

#ifdef CCPP
! Fast physics (from dynamics) are finalized in atmosphere_end above;
Expand Down
18 changes: 12 additions & 6 deletions fv3_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ module fv3gfs_cap_mod
calendar, calendar_type, cpl, &
force_date_from_configure, &
cplprint_flag,output_1st_tstep_rst, &
first_kdt
first_kdt,num_restart_interval

use module_fv3_io_def, only: num_pes_fcst,write_groups,app_domain, &
num_files, filename_base, &
Expand Down Expand Up @@ -278,9 +278,16 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
CALL ESMF_ConfigLoadFile(config=CF ,filename='model_configure' ,rc=RC)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
!
CALL ESMF_ConfigGetAttribute(config=CF,value=restart_interval, &
label ='restart_interval:',rc=rc)
num_restart_interval = ESMF_ConfigGetLen(config=CF, label ='restart_interval:',rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
if(mype == 0) print *,'af nems config,num_restart_interval=',num_restart_interval
if (num_restart_interval<=0) num_restart_interval = 1
allocate(restart_interval(num_restart_interval))
restart_interval = 0
CALL ESMF_ConfigGetAttribute(CF,valueList=restart_interval,label='restart_interval:', &
count=num_restart_interval, rc=RC)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
if(mype == 0) print *,'af nems config,restart_interval=',restart_interval
!
CALL ESMF_ConfigGetAttribute(config=CF,value=calendar, &
label ='calendar:',rc=rc)
Expand Down Expand Up @@ -326,9 +333,8 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
label ='app_domain:',rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if(mype == 0) print *,'af nems config,restart_interval=',restart_interval, &
'quilting=',quilting,'write_groups=',write_groups,wrttasks_per_group, &
'calendar=',trim(calendar),'calendar_type=',calendar_type
if(mype == 0) print *,'af nems config,quilting=',quilting,'write_groups=', &
write_groups,wrttasks_per_group,'calendar=',trim(calendar),'calendar_type=',calendar_type
!
CALL ESMF_ConfigGetAttribute(config=CF,value=num_files, &
label ='num_files:',rc=rc)
Expand Down
2 changes: 1 addition & 1 deletion gfsphysics/GFS_layer/GFS_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -422,7 +422,7 @@ subroutine GFS_initialize (Model, Statein, Stateout, Sfcprop, &
call cires_ugwp_init(Model%me, Model%master, Model%nlunit, Init_parm%logunit, &
Model%fn_nml, Model%lonr, Model%latr, Model%levs, &
Init_parm%ak, Init_parm%bk, p_ref, Model%dtp, &
Model%cdmbgwd, Model%cgwf, Model%prslrd0, Model%ral_ts)
Model%cdmbgwd(1:2), Model%cgwf, Model%prslrd0, Model%ral_ts)
endif
#endif

Expand Down
4 changes: 3 additions & 1 deletion gfsphysics/physics/ugwp_driver_v0.f
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,9 @@ subroutine cires_ugwp_driver_v0(me, master,
&, rain

real(kind=kind_phys), intent(in), dimension(im,levs) :: ugrs
&, vgrs, tgrs, qgrs, prsi, prsl, prslk, phii, phil, del
&, vgrs, tgrs, qgrs, prsl, prslk, phil, del
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
4 changes: 2 additions & 2 deletions io/FV3GFS_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -157,10 +157,10 @@ subroutine FV3GFS_restart_write (IPD_Data, IPD_Restart, Atm_block, Model, fv_dom
type(domain2d), intent(in) :: fv_domain
character(len=32), optional, intent(in) :: timestamp

!--- read in surface data from chgres
!--- write surface data from chgres
call sfc_prop_restart_write (IPD_Data%Sfcprop, Atm_block, Model, fv_domain, timestamp)

!--- read in physics restart data
!--- write physics restart data
call phys_restart_write (IPD_Restart, Atm_block, Model, fv_domain, timestamp)

end subroutine FV3GFS_restart_write
Expand Down
37 changes: 29 additions & 8 deletions io/post_gfs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ module post_gfs
include 'mpif.h'

integer mype, nbdl
logical setvar_atmfile, setvar_sfcfile, read_postcntrl
public post_run_gfs, post_getattr_gfs

contains
Expand All @@ -28,9 +29,10 @@ subroutine post_run_gfs(wrt_int_state,mypei,mpicomp,lead_write, &
!
use ctlblk_mod, only : komax,ifhr,ifmin,modelname,datapd,fld_info, &
npset,grib,gocart_on,icount_calmict, jsta, &
jend,im, nsoil
jend,im, nsoil, filenameflat
use gridspec_mod, only : maptype, gridtype
use grib2_module, only : gribit2,num_pset,nrecout,first_grbtbl
use xml_perl_data,only : paramset
!
!-----------------------------------------------------------------------
!
Expand All @@ -53,9 +55,8 @@ subroutine post_run_gfs(wrt_int_state,mypei,mpicomp,lead_write, &
integer n,nwtpg,ieof,lcntrl,ierr,i,j,k,jts,jte,mynsoil
integer,allocatable :: jstagrp(:),jendgrp(:)
integer,save :: kpo,kth,kpv
logical,save :: log_postalct=.false.
real,dimension(komax),save :: po, th, pv
logical,save :: log_postalct=.false.
logical,save :: setvar_atmfile=.false.,setvar_sfcfile=.false.
logical :: Log_runpost
character(255) :: post_fname*255

Expand Down Expand Up @@ -124,6 +125,7 @@ subroutine post_run_gfs(wrt_int_state,mypei,mpicomp,lead_write, &
!
log_postalct = .true.
first_grbtbl = .true.
read_postcntrl = .true.
!
ENDIF
!
Expand All @@ -135,6 +137,8 @@ subroutine post_run_gfs(wrt_int_state,mypei,mpicomp,lead_write, &
ifmin = mynfmin
if (ifhr == 0 ) ifmin = 0
if(mype==0) print *,'bf set_postvars,ifmin=',ifmin,'ifhr=',ifhr
setvar_atmfile=.false.
setvar_sfcfile=.false.
call set_postvars_gfs(wrt_int_state,mpicomp,setvar_atmfile, &
setvar_sfcfile)

Expand All @@ -145,8 +149,28 @@ subroutine post_run_gfs(wrt_int_state,mypei,mpicomp,lead_write, &
! 20190807 no need to call microinit for GFDLMP
! call MICROINIT
!
if(grib=="grib2" .and. first_grbtbl) then
call read_xml()
if(grib=="grib2" .and. read_postcntrl) then
if (ifhr == 0) then
filenameflat = 'postxconfig-NT_FH00.txt'
call read_xml()
if(mype==0) print *,'af read_xml at fh00,name=',trim(filenameflat)
else if(ifhr > 0) then
filenameflat = 'postxconfig-NT.txt'
if(size(paramset)>0) then
do i=1,size(paramset)
if (size(paramset(i)%param)>0) then
deallocate(paramset(i)%param)
nullify(paramset(i)%param)
endif
enddo
deallocate(paramset)
nullify(paramset)
endif
num_pset = 0
call read_xml()
if(mype==0) print *,'af read_xml,name=',trim(filenameflat),'ifhr=',ifhr
read_postcntrl = .false.
endif
endif
!
IEOF = 0
Expand Down Expand Up @@ -181,9 +205,6 @@ subroutine post_run_gfs(wrt_int_state,mypei,mpicomp,lead_write, &
endif
!
enddo
!
setvar_atmfile = .false.
setvar_sfcfile = .false.
!
endif

Expand Down
106 changes: 72 additions & 34 deletions module_fcst_grid_comp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,11 +22,12 @@ module module_fcst_grid_comp
!
use time_manager_mod, only: time_type, set_calendar_type, set_time, &
set_date, days_in_month, month_name, &
operator(+), operator (<), operator (>), &
operator (/=), operator (/), operator (==),&
operator (*), THIRTY_DAY_MONTHS, JULIAN, &
NOLEAP, NO_CALENDAR, date_to_string, &
get_date
operator(+), operator(-), operator (<), &
operator (>), operator (/=), operator (/), &
operator (==), operator (*), &
THIRTY_DAY_MONTHS, JULIAN, NOLEAP, &
NO_CALENDAR, date_to_string, get_date, &
get_time

use atmos_model_mod, only: atmos_model_init, atmos_model_end, &
get_atmos_model_ungridded_dim, &
Expand Down Expand Up @@ -70,7 +71,8 @@ module module_fcst_grid_comp
iau_offset
use module_fv3_config, only: dt_atmos, calendar, restart_interval, &
quilting, calendar_type, cpl, &
cplprint_flag, force_date_from_configure
cplprint_flag, force_date_from_configure, &
num_restart_interval, frestart, restart_endfcst
!
!-----------------------------------------------------------------------
!
Expand All @@ -88,7 +90,8 @@ module module_fcst_grid_comp
type(atmos_data_type) :: Atm
type(time_type) :: Time_atmos, Time_init, Time_end, &
Time_step_atmos, Time_step_ocean, &
Time_restart, Time_step_restart
Time_restart, Time_step_restart, &
Time_atstart
integer :: num_atmos_calls, ret, intrm_rst
end type

Expand Down Expand Up @@ -179,12 +182,11 @@ subroutine fcst_initialize(fcst_comp, importState, exportState, clock, rc)

integer :: Run_length
integer,dimension(6) :: date, date_end
integer :: res_intvl
integer :: mpi_comm_comp
!
logical,save :: first=.true.
character(len=9) :: month
integer :: initClock, unit, nfhour
integer :: initClock, unit, nfhour, total_inttime
integer :: mype, ntasks
character(3) cfhour
character(4) dateSY
Expand All @@ -203,7 +205,8 @@ subroutine fcst_initialize(fcst_comp, importState, exportState, clock, rc)
real(ESMF_KIND_R8),parameter :: dtor = 180.0_ESMF_KIND_R8 / 3.1415926535897931_ESMF_KIND_R8
integer :: jsc, jec, isc, iec, nlev
type(domain2D) :: domain
integer :: n, fcstNpes
integer :: n, fcstNpes, tmpvar
logical :: single_restart
integer, allocatable, dimension(:) :: isl, iel, jsl, jel
integer, allocatable, dimension(:,:,:) :: deBlockList

Expand Down Expand Up @@ -317,16 +320,46 @@ subroutine fcst_initialize(fcst_comp, importState, exportState, clock, rc)
!
atm_int_state%Time_step_atmos = set_time (dt_atmos,0)
atm_int_state%num_atmos_calls = Run_length / dt_atmos
atm_int_state%Time_atstart = atm_int_state%Time_atmos
if (mype == 0) write(0,*)'num_atmos_calls=',atm_int_state%num_atmos_calls,'time_init=', &
date_init,'time_atmos=',date,'time_end=',date_end,'dt_atmos=',dt_atmos, &
'Run_length=',Run_length
res_intvl = restart_interval*3600
atm_int_state%Time_step_restart = set_time (res_intvl, 0)
atm_int_state%Time_restart = atm_int_state%Time_atmos + atm_int_state%Time_step_restart
atm_int_state%intrm_rst = 0
if (res_intvl>0) atm_int_state%intrm_rst = 1
atm_int_state%Atm%iau_offset = iau_offset
!
frestart = 0
single_restart = .false.
call get_time(atm_int_state%Time_end - atm_int_state%Time_atstart,total_inttime)
if(num_restart_interval == 2) then
if(restart_interval(2)== -1) single_restart = .true.
endif
if(single_restart) then
frestart(1) = restart_interval(1) * 3600
elseif ( num_restart_interval == 1) then
if(restart_interval(1) == 0) then
frestart(1) = total_inttime
else if(restart_interval(1) > 0) then
tmpvar = restart_interval(1) * 3600
frestart(1) = tmpvar
atm_int_state%Time_step_restart = set_time (tmpvar, 0)
atm_int_state%Time_restart = atm_int_state%Time_atstart + atm_int_state%Time_step_restart
i = 2
do while ( atm_int_state%Time_restart < atm_int_state%Time_end )
frestart(i) = frestart(i-1) + tmpvar
atm_int_state%Time_restart = atm_int_state%Time_restart + atm_int_state%Time_step_restart
i = i + 1
enddo
endif
else if(num_restart_interval > 1) then
do i=1,num_restart_interval
frestart(i) = restart_interval(i) * 3600
enddo
endif
restart_endfcst = .false.
if ( ANY(frestart(:) == total_inttime) ) restart_endfcst = .true.
if (mype == 0) print *,'frestart=',frestart(1:10)/3600, 'restart_endfcst=',restart_endfcst, &
'total_inttime=',total_inttime

atm_int_state%intrm_rst = 0
if (frestart(1)>0) atm_int_state%intrm_rst = 1
atm_int_state%Atm%iau_offset = iau_offset
!
!----- write time stamps (for start time and end time) ------

Expand Down Expand Up @@ -737,9 +770,10 @@ subroutine fcst_run_phase_2(fcst_comp, importState, exportState,clock,rc)
!-----------------------------------------------------------------------
!*** local variables
!
integer :: i,j, mype, na, date(6)
integer :: i,j, mype, na, date(6), seconds
character(20) :: compname


type(time_type) :: restart_inctime
type(ESMF_Time) :: currtime
integer(kind=ESMF_KIND_I8) :: ntimestep_esmf
character(len=64) :: timestamp
Expand Down Expand Up @@ -776,13 +810,16 @@ subroutine fcst_run_phase_2(fcst_comp, importState, exportState,clock,rc)

!--- intermediate restart
if (atm_int_state%intrm_rst>0) then
if ((na /= atm_int_state%num_atmos_calls) .and. &
(atm_int_state%Time_atmos == atm_int_state%Time_restart)) then
timestamp = date_to_string (atm_int_state%Time_restart)
call atmos_model_restart(atm_int_state%Atm, timestamp)

call wrt_atmres_timestamp(atm_int_state,timestamp)
atm_int_state%Time_restart = atm_int_state%Time_restart + atm_int_state%Time_step_restart
if (na /= atm_int_state%num_atmos_calls-1) then
call get_time(atm_int_state%Time_atmos - atm_int_state%Time_atstart, seconds)
if (ANY(frestart(:) == seconds)) then
restart_inctime = set_time(seconds, 0)
atm_int_state%Time_restart = atm_int_state%Time_atstart + restart_inctime
timestamp = date_to_string (atm_int_state%Time_restart)
call atmos_model_restart(atm_int_state%Atm, timestamp)

call wrt_atmres_timestamp(atm_int_state,timestamp)
endif
endif
endif
!
Expand Down Expand Up @@ -847,20 +884,21 @@ subroutine fcst_finalize(fcst_comp, importState, exportState,clock,rc)
'final time does not match expected ending time', WARNING)

!*** write restart file

call get_date (atm_int_state%Time_atmos, date(1), date(2), date(3), &
if( restart_endfcst ) then
call get_date (atm_int_state%Time_atmos, date(1), date(2), date(3), &
date(4), date(5), date(6))
call mpp_open( unit, 'RESTART/coupler.res', nohdrs=.TRUE. )
if (mpp_pe() == mpp_root_pe())then
write( unit, '(i6,8x,a)' )calendar_type, &
call mpp_open( unit, 'RESTART/coupler.res', nohdrs=.TRUE. )
if (mpp_pe() == mpp_root_pe())then
write( unit, '(i6,8x,a)' )calendar_type, &
'(Calendar: no_calendar=0, thirty_day_months=1, julian=2, gregorian=3, noleap=4)'

write( unit, '(6i6,8x,a)' )date_init, &
write( unit, '(6i6,8x,a)' )date_init, &
'Model start time: year, month, day, hour, minute, second'
write( unit, '(6i6,8x,a)' )date, &
write( unit, '(6i6,8x,a)' )date, &
'Current model time: year, month, day, hour, minute, second'
endif
call mpp_close(unit)
endif
call mpp_close(unit)
!
call diag_manager_end(atm_int_state%Time_atmos )

Expand Down
Loading

0 comments on commit 5d51b12

Please sign in to comment.