Skip to content

Commit

Permalink
after updating the code based on climbfuji comments from CCPP
Browse files Browse the repository at this point in the history
  • Loading branch information
SMoorthi-emc committed Jan 27, 2020
1 parent 372bd9d commit 06aeee6
Show file tree
Hide file tree
Showing 21 changed files with 254 additions and 1,129 deletions.
12 changes: 6 additions & 6 deletions physics/GFS_DCNV_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -20,14 +20,14 @@ end subroutine GFS_DCNV_generic_pre_finalize
subroutine GFS_DCNV_generic_pre_run (im, levs, ldiag3d, do_cnvgwd, do_ca, cplchm,&
isppt_deep, gu0, gv0, gt0, gq0_water_vapor, &
save_u, save_v, save_t, save_qv, ca_deep, &
dqdti, lprnt, ipr, errmsg, errflg)
dqdti, errmsg, errflg)

use machine, only: kind_phys

implicit none

integer, intent(in) :: im, levs, ipr
logical, intent(in) :: ldiag3d, do_cnvgwd, do_ca, cplchm, isppt_deep, lprnt
integer, intent(in) :: im, levs
logical, intent(in) :: ldiag3d, do_cnvgwd, do_ca, cplchm, isppt_deep
real(kind=kind_phys), dimension(im,levs), intent(in) :: gu0
real(kind=kind_phys), dimension(im,levs), intent(in) :: gv0
real(kind=kind_phys), dimension(im,levs), intent(in) :: gt0
Expand Down Expand Up @@ -107,14 +107,14 @@ subroutine GFS_DCNV_generic_post_run (im, levs, lssav, ldiag3d, ras, cscnv, do_c
gq0_water_vapor, ud_mf, dd_mf, dt_mf, con_g, npdf3d, num_p3d, ncnvcld3d, &
rainc, cldwrk, dt3dt, dq3dt, du3dt, dv3dt, upd_mf, dwn_mf, det_mf, &
cnvw, cnvc, cnvw_phy_f3d, cnvc_phy_f3d, &
cape, tconvtend, qconvtend, uconvtend, vconvtend, lprnt, ipr, errmsg, errflg)
cape, tconvtend, qconvtend, uconvtend, vconvtend, errmsg, errflg)

use machine, only: kind_phys

implicit none

integer, intent(in) :: im, levs, ipr
logical, intent(in) :: lssav, ldiag3d, ras, cscnv, do_ca, isppt_deep, lprnt
integer, intent(in) :: im, levs
logical, intent(in) :: lssav, ldiag3d, ras, cscnv, do_ca, isppt_deep

real(kind=kind_phys), intent(in) :: frain, dtf
real(kind=kind_phys), dimension(im), intent(in) :: rain1, cld1d
Expand Down
32 changes: 0 additions & 32 deletions physics/GFS_DCNV_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -147,22 +147,6 @@
kind = kind_phys
intent = inout
optional = F
[lprnt]
standard_name = flag_print
long_name = control flag for diagnostic print out
units = flag
dimensions = ()
type = logical
intent = inout
optional = F
[ipr]
standard_name = horizontal_index_of_printed_column
long_name = horizontal index of printed column
units = index
dimensions = ()
type = integer
intent = inout
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down Expand Up @@ -579,22 +563,6 @@
kind = kind_phys
intent = inout
optional = F
[lprnt]
standard_name = flag_print
long_name = control flag for diagnostic print out
units = flag
dimensions = ()
type = logical
intent = inout
optional = F
[ipr]
standard_name = horizontal_index_of_printed_column
long_name = horizontal index of printed column
units = index
dimensions = ()
type = integer
intent = inout
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
20 changes: 6 additions & 14 deletions physics/GFS_MP_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,13 +16,13 @@ end subroutine GFS_MP_generic_pre_init
!> \section arg_table_GFS_MP_generic_pre_run Argument Table
!! \htmlinclude GFS_MP_generic_pre_run.html
!!
subroutine GFS_MP_generic_pre_run(im, levs, ldiag3d, do_aw, ntcw, nncl, ntrac, gt0, gq0, save_t, save_q, lprnt, ipr, errmsg, errflg)
subroutine GFS_MP_generic_pre_run(im, levs, ldiag3d, do_aw, ntcw, nncl, ntrac, gt0, gq0, save_t, save_q, errmsg, errflg)
!
use machine, only: kind_phys

implicit none
integer, intent(in) :: im, levs, ntcw, nncl, ntrac, ipr
logical, intent(in) :: ldiag3d, do_aw, lprnt
integer, intent(in) :: im, levs, ntcw, nncl, ntrac
logical, intent(in) :: ldiag3d, do_aw
real(kind=kind_phys), dimension(im, levs), intent(in) :: gt0
real(kind=kind_phys), dimension(im, levs, ntrac), intent(in) :: gq0

Expand Down Expand Up @@ -86,15 +86,15 @@ subroutine GFS_MP_generic_post_run(im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, nt
graupel0, del, rain, domr_diag, domzr_diag, domip_diag, doms_diag, tprcp, srflag, sr, cnvprcp, totprcp, totice, &
totsnw, totgrp, cnvprcpb, totprcpb, toticeb, totsnwb, totgrpb, dt3dt, dq3dt, rain_cpl, rainc_cpl, snow_cpl, pwat, &
do_sppt, dtdtr, dtdtc, drain_cpl, dsnow_cpl, lsm, lsm_ruc, lsm_noahmp, raincprv, rainncprv, iceprv, snowprv, &
graupelprv, draincprv, drainncprv, diceprv, dsnowprv, dgraupelprv, dtp, lprnt, ipr, errmsg, errflg)
graupelprv, draincprv, drainncprv, diceprv, dsnowprv, dgraupelprv, dtp, errmsg, errflg)
!
use machine, only: kind_phys

implicit none

integer, intent(in) :: im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, ntrac, ipr
integer, intent(in) :: im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, ntrac
integer, intent(in) :: imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_mg, imp_physics_fer_hires
logical, intent(in) :: cal_pre, lssav, ldiag3d, cplflx, cplchm, lprnt
logical, intent(in) :: cal_pre, lssav, ldiag3d, cplflx, cplchm

real(kind=kind_phys), intent(in) :: dtf, frain, con_g
real(kind=kind_phys), dimension(im), intent(in) :: rainc, rain1, xlat, xlon, tsfc
Expand Down Expand Up @@ -217,14 +217,6 @@ subroutine GFS_MP_generic_post_run(im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, nt
rain, phii, tsfc, & ! input
domr, domzr, domip, doms) ! output
!
! if (lprnt) print*,'debug calpreciptype: DOMR,DOMZR,DOMIP,DOMS '
! &,DOMR(ipr),DOMZR(ipr),DOMIP(ipr),DOMS(ipr)
! do i=1,im
! if (abs(xlon(i)*57.29578-114.0) .lt. 0.2 .and.
! & abs(xlat(i)*57.29578-40.0) .lt. 0.2)
! & print*,'debug calpreciptype: DOMR,DOMZR,DOMIP,DOMS ',
! & DOMR(i),DOMZR(i),DOMIP(i),DOMS(i)
! end do
! HCHUANG: use new precipitation type to decide snow flag for LSM snow accumulation

if (imp_physics /= imp_physics_gfdl .and. imp_physics /= imp_physics_thompson) then
Expand Down
32 changes: 0 additions & 32 deletions physics/GFS_MP_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -98,22 +98,6 @@
kind = kind_phys
intent = inout
optional = F
[lprnt]
standard_name = flag_print
long_name = control flag for diagnostic print out
units = flag
dimensions = ()
type = logical
intent = inout
optional = F
[ipr]
standard_name = horizontal_index_of_printed_column
long_name = horizontal index of printed column
units = index
dimensions = ()
type = integer
intent = inout
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down Expand Up @@ -897,22 +881,6 @@
kind = kind_phys
intent = in
optional = F
[lprnt]
standard_name = flag_print
long_name = control flag for diagnostic print out
units = flag
dimensions = ()
type = logical
intent = inout
optional = F
[ipr]
standard_name = horizontal_index_of_printed_column
long_name = horizontal index of printed column
units = index
dimensions = ()
type = integer
intent = inout
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
39 changes: 2 additions & 37 deletions physics/GFS_PBL_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ subroutine GFS_PBL_generic_pre_run (im, levs, nvdiff, ntrac,
ntwa, ntia, ntgl, ntoz, ntke, ntkev, nqrimef, trans_aero, ntchs, ntchm, &
imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_wsm6, &
imp_physics_zhao_carr, imp_physics_mg, imp_physics_fer_hires, cplchm, ltaerosol, &
hybedmf, do_shoc, satmedmf, qgrs, vdftra, xlon, xlat, lprnt, ipt, kdt, me,errmsg, errflg)
hybedmf, do_shoc, satmedmf, qgrs, vdftra, errmsg, errflg)

use machine, only : kind_phys
use GFS_PBL_generic_common, only : set_aerosol_tracer_index
Expand All @@ -99,17 +99,11 @@ subroutine GFS_PBL_generic_pre_run (im, levs, nvdiff, ntrac,
integer, intent(in) :: imp_physics_zhao_carr, imp_physics_mg, imp_physics_fer_hires
logical, intent(in) :: cplchm, ltaerosol, hybedmf, do_shoc, satmedmf

real(kind=kind_phys), dimension(im), intent(in) :: xlat, xlon
real(kind=kind_phys), dimension(im, levs, ntrac), intent(in) :: qgrs
real(kind=kind_phys), dimension(im, levs, nvdiff), intent(inout) :: vdftra

logical, intent(inout) :: lprnt
integer, intent(inout) :: ipt
integer, intent(in) :: kdt, me

character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg
real(kind=kind_phys), parameter :: rad2dg = 180.0/3.14159265359

!local variables
integer :: i, k, kk, k1, n
Expand All @@ -118,29 +112,6 @@ subroutine GFS_PBL_generic_pre_run (im, levs, nvdiff, ntrac,
errmsg = ''
errflg = 0


lprnt = .false.
ipt = 1
! do i=1,im
! lprnt = kdt >= 1 .and. abs(xlon(i)*rad2dg-97.50) < 0.101 &
! .and. abs(xlat(i)*rad2dg-24.48) < 0.101
! lprnt = kdt >= 1 .and. abs(xlon(i)*rad2dg-293.91) < 0.101 &
! .and. abs(xlat(i)*rad2dg+72.02) < 0.101
! if (kdt == 1) &
! write(2000+me,*)' i=',i,' xlon=',xlon(i)*rad2dg, &
! ' xlat=',xlat(i)*rad2dg,' me=',me
! if (lprnt) then
! ipt = i
! write(0,*)' GFS_PBL_generic_pre_run ipt=',ipt,'xlon=',xlon(i)*rad2dg,' xlat=',xlat(i)*rad2dg,' me=',me
! exit
! endif
! enddo
! if (lprnt) then
! write(0,*)' qgrsv=',qgrs(ipt,:,1)
! write(0,*)' qgrsi=',qgrs(ipt,:,ntiw)
! write(0,*)' qgrsw=',qgrs(ipt,:,ntcw)
! endif

!DH: dvdftra is only used if nvdiff != ntrac or (nvdiff == ntrac .and. )
if (nvdiff == ntrac .and. (hybedmf .or. do_shoc .or. satmedmf)) then
vdftra = qgrs
Expand Down Expand Up @@ -316,8 +287,7 @@ subroutine GFS_PBL_generic_post_run (im, levs, nvdiff, ntrac,
dqsfc_cpl, dusfci_cpl, dvsfci_cpl, dtsfci_cpl, dqsfci_cpl, dusfc_diag, dvsfc_diag, dtsfc_diag, dqsfc_diag, &
dusfci_diag, dvsfci_diag, dtsfci_diag, dqsfci_diag, dt3dt, du3dt_PBL, du3dt_OGWD, dv3dt_PBL, dv3dt_OGWD, dq3dt, &
dq3dt_ozone, rd, cp,fvirt, hvap, t1, q1, prsl, hflx, ushfsfci, oceanfrac, fice, dusfc_cice, dvsfc_cice, dtsfc_cice, &
dqsfc_cice, wet, dry, icy, wind, stress_ocn, hflx_ocn, evap_ocn, ugrs1, vgrs1, dkt_cpl, dkt, &
lprnt, ipt, kdt, me, errmsg, errflg)
dqsfc_cice, wet, dry, icy, wind, stress_ocn, hflx_ocn, evap_ocn, ugrs1, vgrs1, dkt_cpl, dkt, errmsg, errflg)

use machine, only : kind_phys
use GFS_PBL_generic_common, only : set_aerosol_tracer_index
Expand All @@ -332,11 +302,6 @@ subroutine GFS_PBL_generic_post_run (im, levs, nvdiff, ntrac,
logical, intent(in) :: ltaerosol, cplflx, cplchm, lssav, ldiag3d, lsidea
logical, intent(in) :: hybedmf, do_shoc, satmedmf, shinhong, do_ysu

logical, intent(inout) :: lprnt
integer, intent(inout) :: ipt
integer, intent(in) :: kdt, me


real(kind=kind_phys), intent(in) :: dtf
real(kind=kind_phys), intent(in) :: rd, cp, fvirt, hvap
real(kind=kind_phys), dimension(:), intent(in) :: t1, q1, hflx, oceanfrac, fice
Expand Down
82 changes: 0 additions & 82 deletions physics/GFS_PBL_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -307,56 +307,6 @@
kind = kind_phys
intent = inout
optional = F
[xlon]
standard_name = longitude
long_name = longitude
units = radians
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[xlat]
standard_name = latitude
long_name = latitude
units = radians
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[lprnt]
standard_name = flag_print
long_name = control flag for diagnostic print out
units = flag
dimensions = ()
type = logical
intent = inout
optional = F
[ipt]
standard_name = horizontal_index_of_printed_column
long_name = horizontal index of printed column
units = index
dimensions = ()
type = integer
intent = inout
optional = F
[kdt]
standard_name = index_of_time_step
long_name = current forecast iteration
units = index
dimensions = ()
type = integer
intent = in
optional = F
[me]
standard_name = mpi_rank
long_name = current MPI-rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down Expand Up @@ -1270,38 +1220,6 @@
kind = kind_phys
intent = in
optional = F
[lprnt]
standard_name = flag_print
long_name = control flag for diagnostic print out
units = flag
dimensions = ()
type = logical
intent = inout
optional = F
[ipt]
standard_name = horizontal_index_of_printed_column
long_name = horizontal index of printed column
units = index
dimensions = ()
type = integer
intent = inout
optional = F
[kdt]
standard_name = index_of_time_step
long_name = current forecast iteration
units = index
dimensions = ()
type = integer
intent = in
optional = F
[me]
standard_name = mpi_rank
long_name = current MPI-rank
units = index
dimensions = ()
type = integer
intent = in
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
6 changes: 3 additions & 3 deletions physics/GFS_SCNV_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,14 +15,14 @@ end subroutine GFS_SCNV_generic_pre_finalize
!! \htmlinclude GFS_SCNV_generic_pre_run.html
!!
subroutine GFS_SCNV_generic_pre_run (im, levs, ldiag3d, gt0, gq0_water_vapor, &
save_t, save_qv, lprnt, ipr, errmsg, errflg)
save_t, save_qv, errmsg, errflg)

use machine, only: kind_phys

implicit none

integer, intent(in) :: im, levs, ipr
logical, intent(in) :: ldiag3d, lprnt
integer, intent(in) :: im, levs
logical, intent(in) :: ldiag3d
real(kind=kind_phys), dimension(im,levs), intent(in) :: gt0, gq0_water_vapor

real(kind=kind_phys), dimension(im,levs), intent(inout) :: save_t, save_qv
Expand Down
16 changes: 0 additions & 16 deletions physics/GFS_SCNV_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -61,22 +61,6 @@
kind = kind_phys
intent = inout
optional = F
[lprnt]
standard_name = flag_print
long_name = control flag for diagnostic print out
units = flag
dimensions = ()
type = logical
intent = inout
optional = F
[ipr]
standard_name = horizontal_index_of_printed_column
long_name = horizontal index of printed column
units = index
dimensions = ()
type = integer
intent = inout
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
Loading

3 comments on commit 06aeee6

@climbfuji
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Wow, this was super quick. Thanks for making all those changes!

@SMoorthi-emc
Copy link
Collaborator Author

@SMoorthi-emc SMoorthi-emc commented on 06aeee6 Jan 27, 2020 via email

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@SMoorthi-emc
Copy link
Collaborator Author

@SMoorthi-emc SMoorthi-emc commented on 06aeee6 Jan 28, 2020 via email

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Please sign in to comment.