Skip to content

Commit

Permalink
FV3: this commits #refs 41313, various interpolation methods to outpu…
Browse files Browse the repository at this point in the history
…t fields in history file and accumulated precip rate

        modified:   atmos_cubed_sphere/tools/fv_nggps_diag.F90
        modified:   atmos_model.F90
        modified:   fv3_cap.F90
        modified:   gfsphysics/GFS_layer/GFS_driver.F90
        modified:   gfsphysics/GFS_layer/GFS_typedefs.F90
        modified:   io/FV3GFS_io.F90
        modified:   io/module_fv3_io_def.F90
        modified:   io/module_write_nemsio.F90
        modified:   io/module_wrt_grid_comp.F90
        modified:   module_fcst_grid_comp.F90
  • Loading branch information
junwang-noaa committed Jan 23, 2018
1 parent 025d0a7 commit 3bca217
Show file tree
Hide file tree
Showing 10 changed files with 1,385 additions and 638 deletions.
253 changes: 198 additions & 55 deletions atmos_cubed_sphere/tools/fv_nggps_diag.F90

Large diffs are not rendered by default.

7 changes: 4 additions & 3 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -433,7 +433,7 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
!rab call atmosphere_tracer_postinit (IPD_Data, Atm_block)

call atmosphere_nggps_diag (Time, init=.true.)
call gfdl_diag_register (Time, IPD_Data(:)%Sfcprop, IPD_Data(:)%Cldprop, IPD_Data(:)%IntDiag, Atm_block, IPD_Control, Atmos%axes)
call gfdl_diag_register (Time, IPD_Data(:)%Sfcprop, IPD_Data(:)%Cldprop, IPD_Data(:)%IntDiag, IPD_Data(:)%grid, Atm_block, IPD_Control, Atmos%axes)
call FV3GFS_restart_read (IPD_Data, IPD_Restart, Atm_block, IPD_Control, Atmos%domain)

!--- set the initial diagnostic timestamp
Expand Down Expand Up @@ -502,7 +502,7 @@ subroutine update_atmos_model_state (Atmos)
type (atmos_data_type), intent(inout) :: Atmos
!--- local variables
integer :: isec,seconds
real(kind=kind_phys) :: time_int
real(kind=kind_phys) :: time_int, time_intfull

call set_atmosphere_pelist()
call mpp_clock_begin(fv3Clock)
Expand All @@ -524,10 +524,11 @@ subroutine update_atmos_model_state (Atmos)
if (mpp_pe() == mpp_root_pe()) write(6,*) "---isec,seconds",isec,seconds
if (ANY(nint(fdiag(:)*3600.0) == seconds) .or. (IPD_Control%kdt == 1) ) then
time_int = real(isec)
time_intfull = real(seconds)
if (mpp_pe() == mpp_root_pe()) write(6,*) ' gfs diags time since last bucket empty: ',time_int/3600.,'hrs'
call atmosphere_nggps_diag(Atmos%Time)
call gfdl_diag_output(Atmos%Time, Atm_block, IPD_Control%nx, IPD_Control%ny, &
IPD_Control%levs, 1, 1, 1.d0, time_int)
IPD_Control%levs, 1, 1, 1.d0, time_int, time_intfull)
if (mod(isec,3600*nint(IPD_Control%fhzero)) == 0) diag_time = Atmos%Time
endif
call diag_send_complete_extra (Atmos%Time)
Expand Down
8 changes: 4 additions & 4 deletions fv3_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -483,7 +483,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
enddo
k = k + wrttasks_per_group
last_wrttask(i) = k - 1
if(mype==0)print *,'af wrtComp(i)=',i,'k=',k
! if(mype==0)print *,'af wrtComp(i)=',i,'k=',k

! prepare name of the wrtComp(i)
write(cwrtcomp,"(A,I2.2)") "wrtComp_", i
Expand Down Expand Up @@ -607,7 +607,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
regridMethod=regridmethod, routehandle=routehandle(j,i), &
srcTermProcessing=isrctermprocessing, rc=rc)

print *,'after regrid store, group i=',i,' fb=',j,' time=',mpi_wtime()-timewri
if(mype==0) print *,'after regrid store, group i=',i,' fb=',j,' time=',mpi_wtime()-timewri
call ESMF_LogWrite('af FieldBundleRegridStore', ESMF_LOGMSG_INFO, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, &
Expand All @@ -634,7 +634,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)

! end write_groups
enddo
print *,'in fv3cap init, time wrtcrt/regrdst',mpi_wtime()-timerhs
if(mype==0) print *,'in fv3cap init, time wrtcrt/regrdst',mpi_wtime()-timerhs
deallocate(petList)
deallocate(originPetList)
deallocate(targetPetList)
Expand Down Expand Up @@ -705,7 +705,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
!end quilting
endif
!
print *,'in fv3_cap, init time=',mpi_wtime()-timeis
if(mype==0) print *,'in fv3_cap, init time=',mpi_wtime()-timeis
!-----------------------------------------------------------------------
!
end subroutine InitializeAdvertise
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 @@ -149,7 +149,7 @@ subroutine GFS_initialize (Model, Statein, Stateout, Sfcprop, &
Init_parm%input_nml_file)

call init_stochastic_physics(Model,Init_parm)
print*,'do_skeb=',Model%do_skeb
if(Model%me == Model%master) print*,'do_skeb=',Model%do_skeb

call read_o3data (Model%ntoz, Model%me, Model%master)
call read_h2odata (Model%h2o_phys, Model%me, Model%master)
Expand Down
35 changes: 27 additions & 8 deletions gfsphysics/GFS_layer/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -330,6 +330,7 @@ module GFS_typedefs
character(len=256), pointer :: input_nml_file(:) !< character string containing full namelist
!< for use with internal file reads
real(kind=kind_phys) :: fhzero !< seconds between clearing of diagnostic buckets
logical :: lprecip_accu !< flag for precip accumulation without bucket (fhzero)
logical :: ldiag3d !< flag for 3d diagnostic fields
logical :: lssav !< logical flag for storing diagnostics
real(kind=kind_phys) :: fhcyc !< frequency for surface data cycling (secs)
Expand Down Expand Up @@ -1356,6 +1357,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &

!--- BEGIN NAMELIST VARIABLES
real(kind=kind_phys) :: fhzero = 0.0 !< seconds between clearing of diagnostic buckets
logical :: lprecip_accu = .true. !< flag for precip accumulation without bucket (fhzero)
logical :: ldiag3d = .false. !< flag for 3d diagnostic fields
logical :: lssav = .false. !< logical flag for storing diagnostics
real(kind=kind_phys) :: fhcyc = 0. !< frequency for surface data cycling (secs)
Expand Down Expand Up @@ -1564,7 +1566,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &

NAMELIST /gfs_physics_nml/ &
!--- general parameters
fhzero, ldiag3d, lssav, fhcyc, lgocart, fhgoc3d, &
fhzero,lprecip_accu, ldiag3d, lssav, fhcyc, lgocart, fhgoc3d,&
thermodyn_id, sfcpress_id, &
!--- coupling parameters
cplflx, cplwav, lsidea, &
Expand Down Expand Up @@ -1642,6 +1644,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%nlunit = nlunit
Model%fn_nml = fn_nml
Model%fhzero = fhzero
Model%lprecip_accu = lprecip_accu
Model%ldiag3d = ldiag3d
Model%lssav = lssav
Model%fhcyc = fhcyc
Expand Down Expand Up @@ -2551,6 +2554,9 @@ subroutine diag_create (Diag, IM, Model)
integer, intent(in) :: IM
type(GFS_control_type), intent(in) :: Model

!
logical, save :: linit

!--- Radiation
allocate (Diag%fluxr (IM,Model%nfxr))
allocate (Diag%topfsw (IM))
Expand Down Expand Up @@ -2645,7 +2651,10 @@ subroutine diag_create (Diag, IM, Model)
endif

call Diag%rad_zero (Model)
call Diag%phys_zero (Model)
! print *,'in diag_create, call phys_zero'
linit = .true.
call Diag%phys_zero (Model, linit=linit)
linit = .false.

end subroutine diag_create

Expand All @@ -2672,9 +2681,10 @@ end subroutine diag_rad_zero
!------------------------
! GFS_diag%phys_zero
!------------------------
subroutine diag_phys_zero (Diag, Model)
subroutine diag_phys_zero (Diag, Model, linit)
class(GFS_diag_type) :: Diag
type(GFS_control_type), intent(in) :: Model
logical,optional, intent(in) :: linit

!--- In/Out
Diag%srunoff = zero
Expand All @@ -2691,7 +2701,7 @@ subroutine diag_phys_zero (Diag, Model)
Diag%dvsfc = zero
Diag%dtsfc = zero
Diag%dqsfc = zero
Diag%totprcp = zero
! Diag%totprcp = zero
Diag%gflux = zero
Diag%dlwsfc = zero
Diag%ulwsfc = zero
Expand All @@ -2702,7 +2712,7 @@ subroutine diag_phys_zero (Diag, Model)
Diag%dugwd = zero
Diag%dvgwd = zero
Diag%psmean = zero
Diag%cnvprcp = zero
! Diag%cnvprcp = zero
Diag%spfhmin = huge
Diag%spfhmax = zero
Diag%u10mmax = zero
Expand All @@ -2713,9 +2723,9 @@ subroutine diag_phys_zero (Diag, Model)
Diag%ice = zero
Diag%snow = zero
Diag%graupel = zero
Diag%totice = zero
Diag%totsnw = zero
Diag%totgrp = zero
! Diag%totice = zero
! Diag%totsnw = zero
! Diag%totgrp = zero

!--- Out
Diag%u10m = zero
Expand Down Expand Up @@ -2764,6 +2774,15 @@ subroutine diag_phys_zero (Diag, Model)
Diag%refl_10cm = zero
endif

if ((present (linit).and.linit) .or. .not. Model%lprecip_accu) then
Diag%totprcp = zero
Diag%cnvprcp = zero
Diag%totice = zero
Diag%totsnw = zero
Diag%totgrp = zero
if(Model%me == Model%master) print *,'in diag_phys_zero, set diag variable to zero',&
'size(Diag%totprcp)=',size(Diag%totprcp)
endif
end subroutine diag_phys_zero

end module GFS_typedefs
Loading

0 comments on commit 3bca217

Please sign in to comment.