Skip to content

Commit

Permalink
Add optional attribute to GWD files.
Browse files Browse the repository at this point in the history
  • Loading branch information
dustinswales committed Apr 23, 2024
1 parent eb64212 commit 4e100f8
Show file tree
Hide file tree
Showing 9 changed files with 79 additions and 71 deletions.
5 changes: 3 additions & 2 deletions physics/GWD/cires_ugwp_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,9 @@ subroutine cires_ugwp_post_run (ldiag_ugwp, dtf, im, levs, &
real(kind=kind_phys), intent(in), dimension(:) :: tau_mtb, tau_ogw, tau_tofd, tau_ngw
real(kind=kind_phys), intent(inout), dimension(:) :: tot_mtb, tot_ogw, tot_tofd, tot_ngw
real(kind=kind_phys), intent(inout), dimension(:) :: tot_zmtb, tot_zlwb, tot_zogw
real(kind=kind_phys), intent(in), dimension(:,:) :: gw_dtdt, gw_dudt, gw_dvdt, dudt_mtb, dudt_ogw, dudt_tms
real(kind=kind_phys), intent(inout), dimension(:,:) :: du3dt_mtb, du3dt_ogw, du3dt_tms, du3dt_ngw, dv3dt_ngw
real(kind=kind_phys), intent(in), dimension(:,:) :: gw_dtdt, gw_dudt, gw_dvdt, dudt_mtb, dudt_tms
real(kind=kind_phys), intent(in), dimension(:,:), optional :: dudt_ogw
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: du3dt_mtb, du3dt_ogw, du3dt_tms, du3dt_ngw, dv3dt_ngw
real(kind=kind_phys), intent(inout), dimension(:,:) :: dtdt, dudt, dvdt

character(len=*), intent(out) :: errmsg
Expand Down
15 changes: 8 additions & 7 deletions physics/GWD/drag_suite.F90
Original file line number Diff line number Diff line change
Expand Up @@ -328,9 +328,10 @@ subroutine drag_suite_run( &
logical, intent(in) :: lprnt
integer, intent(in) :: KPBL(:)
real(kind=kind_phys), intent(in) :: deltim, G, CP, RD, RV, cdmbgwd(:)
real(kind=kind_phys), intent(inout) :: dtend(:,:,:)
real(kind=kind_phys), intent(inout), optional :: dtend(:,:,:)
logical, intent(in) :: ldiag3d
integer, intent(in) :: dtidx(:,:), index_of_temperature, &
integer, intent(in) :: dtidx(:,:)
integer, intent(in) :: index_of_temperature, &
& index_of_process_orographic_gwd, index_of_x_wind, index_of_y_wind

integer :: kpblmax
Expand All @@ -353,16 +354,16 @@ subroutine drag_suite_run( &
real(kind=kind_phys), intent(in) :: var(:),oc1(:), &
& oa4(:,:),ol4(:,:), &
& dx(:)
real(kind=kind_phys), intent(in) :: varss(:),oc1ss(:), &
real(kind=kind_phys), intent(in), optional :: varss(:),oc1ss(:), &
& oa4ss(:,:),ol4ss(:,:)
real(kind=kind_phys), intent(in) :: THETA(:),SIGMA(:), &
& GAMMA(:),ELVMAX(:)

! added for small-scale orographic wave drag
real(kind=kind_phys), dimension(im,km) :: utendwave,vtendwave,thx,thvx
real(kind=kind_phys), intent(in) :: br1(:), &
& hpbl(:), &
& slmsk(:)
real(kind=kind_phys), intent(in), optional :: hpbl(:)
real(kind=kind_phys), dimension(im) :: govrth,xland
!real(kind=kind_phys), dimension(im,km) :: dz2
real(kind=kind_phys) :: tauwavex0,tauwavey0, &
Expand All @@ -374,7 +375,7 @@ subroutine drag_suite_run( &
!SPP
real(kind=kind_phys), dimension(im) :: var_stoch, varss_stoch, &
varmax_fd_stoch
real(kind=kind_phys), intent(in) :: spp_wts_gwd(:,:)
real(kind=kind_phys), intent(in), optional :: spp_wts_gwd(:,:)
integer, intent(in) :: spp_gwd

real(kind=kind_phys), dimension(im) :: rstoch
Expand All @@ -383,12 +384,12 @@ subroutine drag_suite_run( &
real(kind=kind_phys), intent(inout) :: &
& dusfc(:), dvsfc(:)
!Output (optional):
real(kind=kind_phys), intent(inout) :: &
real(kind=kind_phys), intent(inout), optional :: &
& dusfc_ms(:),dvsfc_ms(:), &
& dusfc_bl(:),dvsfc_bl(:), &
& dusfc_ss(:),dvsfc_ss(:), &
& dusfc_fd(:),dvsfc_fd(:)
real(kind=kind_phys), intent(inout) :: &
real(kind=kind_phys), intent(inout), optional :: &
& dtaux2d_ms(:,:),dtauy2d_ms(:,:), &
& dtaux2d_bl(:,:),dtauy2d_bl(:,:), &
& dtaux2d_ss(:,:),dtauy2d_ss(:,:), &
Expand Down
2 changes: 1 addition & 1 deletion physics/GWD/gwdc_post.f
Original file line number Diff line number Diff line change
Expand Up @@ -79,4 +79,4 @@ subroutine gwdc_post_run( &

end subroutine gwdc_post_run

end module gwdc_post
end module gwdc_post
6 changes: 3 additions & 3 deletions physics/GWD/gwdps.f
Original file line number Diff line number Diff line change
Expand Up @@ -315,11 +315,11 @@ subroutine gwdps_run( &
& THETA(:), SIGMA(:), GAMMA(:)
real(kind=kind_phys), intent(inout) :: DUSFC(:), DVSFC(:), &
& RDXZB(:)
real(kind=kind_phys), intent(inout) :: dtaux2d_ms(:,:), &
real(kind=kind_phys), intent(inout), optional :: dtaux2d_ms(:,:), &
& dtauy2d_ms(:,:), dtaux2d_bl(:,:), &
& dtauy2d_bl(:,:)
real(kind=kind_phys), intent(inout) :: dusfc_ms(:), dvsfc_ms(:), &
& dusfc_bl(:), dvsfc_bl(:)
real(kind=kind_phys), intent(inout), optional :: dusfc_ms(:), &
& dvsfc_ms(:), dusfc_bl(:), dvsfc_bl(:)
integer, intent(in) :: nmtvr
logical, intent(in) :: lprnt
logical, intent(in) :: ldiag_ugwp
Expand Down
3 changes: 2 additions & 1 deletion physics/GWD/rayleigh_damp.f
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,8 @@ subroutine rayleigh_damp_run ( &
real(kind=kind_phys),intent(in) :: U1(:,:), V1(:,:)
real(kind=kind_phys),intent(inout) :: A(:,:), B(:,:), C(:,:)
real(kind=kind_phys),optional, intent(inout) :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:), &
integer, intent(in) :: dtidx(:,:)
integer, intent(in) :: &
& index_of_process_rayleigh_damping, index_of_temperature, &
& index_of_x_wind, index_of_y_wind
character(len=*), intent(out) :: errmsg
Expand Down
23 changes: 13 additions & 10 deletions physics/GWD/ugwpv1_gsldrag.F90
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,7 @@ subroutine ugwpv1_gsldrag_init ( &
integer, intent (in) :: me
integer, intent (in) :: master
integer, intent (in) :: nlunit
character(len=*), intent (in) :: input_nml_file(:)
character(len=*), intent (in), optional :: input_nml_file(:)
integer, intent (in) :: logunit
integer, intent (in) :: jdat(:)
integer, intent (in) :: lonr
Expand Down Expand Up @@ -378,8 +378,9 @@ subroutine ugwpv1_gsldrag_run(me, master, im, levs, ak, bk, ntrac, lonr, dtp,
real(kind=kind_phys), intent(in), dimension(:) :: elvmax
real(kind=kind_phys), intent(in), dimension(:,:) :: clx, oa4

real(kind=kind_phys), intent(in), dimension(:) :: varss,oc1ss,dx
real(kind=kind_phys), intent(in), dimension(:,:) :: oa4ss,ol4ss
real(kind=kind_phys), intent(in), dimension(:) :: dx
real(kind=kind_phys), intent(in), dimension(:), optional :: varss,oc1ss
real(kind=kind_phys), intent(in), dimension(:,:), optional :: oa4ss,ol4ss

!=====
!ccpp-style passing constants, I prefer to take them out from the "call-subr" list
Expand All @@ -398,7 +399,8 @@ subroutine ugwpv1_gsldrag_run(me, master, im, levs, ak, bk, ntrac, lonr, dtp,
integer, intent(in), dimension(:) :: kpbl

real(kind=kind_phys), intent(in), dimension(:) :: rain
real(kind=kind_phys), intent(in), dimension(:) :: br1, hpbl, slmsk
real(kind=kind_phys), intent(in), dimension(:) :: br1, slmsk
real(kind=kind_phys), intent(in), dimension(:), optional :: hpbl
!
! moved to GFS_phys_time_vary
! real(kind=kind_phys), intent(in), dimension(:) :: ddy_j1tau, ddy_j2tau
Expand All @@ -407,7 +409,7 @@ subroutine ugwpv1_gsldrag_run(me, master, im, levs, ak, bk, ntrac, lonr, dtp,

!Output (optional):

real(kind=kind_phys), intent(out), dimension(:) :: &
real(kind=kind_phys), intent(out), dimension(:), optional :: &
du_ogwcol, dv_ogwcol, du_oblcol, dv_oblcol, &
du_osscol, dv_osscol, du_ofdcol, dv_ofdcol
!
Expand All @@ -417,11 +419,11 @@ subroutine ugwpv1_gsldrag_run(me, master, im, levs, ak, bk, ntrac, lonr, dtp,
real(kind=kind_phys), intent(out), dimension(:) :: dusfcg, dvsfcg
real(kind=kind_phys), intent(out), dimension(:) :: tau_ogw, tau_ngw, tau_oss

real(kind=kind_phys), intent(out) , dimension(:,:) :: &
real(kind=kind_phys), intent(out) , dimension(:,:), optional :: &
dudt_ogw, dvdt_ogw, dudt_obl, dvdt_obl, &
dudt_oss, dvdt_oss, dudt_ofd, dvdt_ofd

real(kind=kind_phys), intent(out) , dimension(:,:) :: dudt_ngw, dvdt_ngw, kdis_ngw
real(kind=kind_phys), intent(out) , dimension(:,:), optional :: dudt_ngw, dvdt_ngw, kdis_ngw
real(kind=kind_phys), intent(out) , dimension(:,:) :: dudt_gw, dvdt_gw, kdis_gw

real(kind=kind_phys), intent(out) , dimension(:,:) :: dtdt_ngw, dtdt_gw
Expand All @@ -431,14 +433,15 @@ subroutine ugwpv1_gsldrag_run(me, master, im, levs, ak, bk, ntrac, lonr, dtp,
!
real(kind=kind_phys), intent(inout), dimension(:,:) :: dudt, dvdt, dtdt

real(kind=kind_phys), intent(inout) :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:), &
real(kind=kind_phys), intent(inout), optional :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:)
integer, intent(in) :: &
index_of_x_wind, index_of_y_wind, index_of_temperature, &
index_of_process_orographic_gwd, index_of_process_nonorographic_gwd

real(kind=kind_phys), intent(out), dimension(:) :: rdxzb ! for stoch phys. mtb-level

real(kind=kind_phys), intent(in) :: spp_wts_gwd(:,:)
real(kind=kind_phys), intent(in), optional :: spp_wts_gwd(:,:)
integer, intent(in) :: spp_gwd

character(len=*), intent(out) :: errmsg
Expand Down
38 changes: 19 additions & 19 deletions physics/GWD/ugwpv1_gsldrag_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -40,25 +40,25 @@ subroutine ugwpv1_gsldrag_post_run ( im, levs, ldiag_ugwp, &
real(kind=kind_phys), intent(inout), dimension(:) :: tot_zmtb, tot_zlwb, tot_zogw

real(kind=kind_phys), intent(in), dimension(:,:) :: dtdt_gw, dudt_gw, dvdt_gw
real(kind=kind_phys), intent(in), dimension(:,:) :: dudt_obl, dvdt_obl, dudt_ogw
real(kind=kind_phys), intent(in), dimension(:,:) :: dvdt_ogw, dudt_ofd, dvdt_ofd
real(kind=kind_phys), intent(in), dimension(:,:) :: dudt_oss, dvdt_oss
real(kind=kind_phys), intent(inout), dimension(:,:) :: du3dt_mtb, du3dt_ogw, du3dt_tms
real(kind=kind_phys), intent(inout), dimension(:,:) :: du3dt_ngw, dv3dt_ngw
real(kind=kind_phys), intent(in), dimension(:,:) :: dudt_ngw, dvdt_ngw, dtdt_ngw
real(kind=kind_phys), intent(inout), dimension(:,:) :: ldu3dt_ngw, ldv3dt_ngw, ldt3dt_ngw
real(kind=kind_phys), intent(inout), dimension(:,:) :: dws3dt_ogw, dws3dt_obl
real(kind=kind_phys), intent(inout), dimension(:,:) :: dws3dt_oss, dws3dt_ofd
real(kind=kind_phys), intent(inout), dimension(:,:) :: ldu3dt_ogw, ldu3dt_obl
real(kind=kind_phys), intent(inout), dimension(:,:) :: ldu3dt_oss, ldu3dt_ofd
real(kind=kind_phys), intent(in), dimension(:) :: du_ogwcol, dv_ogwcol
real(kind=kind_phys), intent(in), dimension(:) :: dv_oblcol
real(kind=kind_phys), intent(in), dimension(:) :: du_osscol, dv_osscol
real(kind=kind_phys), intent(in), dimension(:) :: dv_ofdcol
real(kind=kind_phys), intent(inout), dimension(:) :: du3_ogwcol, dv3_ogwcol
real(kind=kind_phys), intent(inout), dimension(:) :: du3_oblcol, dv3_oblcol
real(kind=kind_phys), intent(inout), dimension(:) :: du3_osscol, dv3_osscol
real(kind=kind_phys), intent(inout), dimension(:) :: du3_ofdcol, dv3_ofdcol
real(kind=kind_phys), intent(in), dimension(:,:), optional :: dudt_obl, dvdt_obl, dudt_ogw
real(kind=kind_phys), intent(in), dimension(:,:), optional :: dvdt_ogw, dudt_ofd, dvdt_ofd
real(kind=kind_phys), intent(in), dimension(:,:), optional :: dudt_oss, dvdt_oss
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: du3dt_mtb, du3dt_ogw, du3dt_tms
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: du3dt_ngw, dv3dt_ngw
real(kind=kind_phys), intent(in), dimension(:,:), optional :: dudt_ngw, dvdt_ngw, dtdt_ngw
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: ldu3dt_ngw, ldv3dt_ngw, ldt3dt_ngw
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: dws3dt_ogw, dws3dt_obl
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: dws3dt_oss, dws3dt_ofd
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: ldu3dt_ogw, ldu3dt_obl
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: ldu3dt_oss, ldu3dt_ofd
real(kind=kind_phys), intent(in), dimension(:), optional :: du_ogwcol, dv_ogwcol
real(kind=kind_phys), intent(in), dimension(:), optional :: dv_oblcol
real(kind=kind_phys), intent(in), dimension(:), optional :: du_osscol, dv_osscol
real(kind=kind_phys), intent(in), dimension(:), optional :: dv_ofdcol
real(kind=kind_phys), intent(inout), dimension(:), optional :: du3_ogwcol, dv3_ogwcol
real(kind=kind_phys), intent(inout), dimension(:), optional :: du3_oblcol, dv3_oblcol
real(kind=kind_phys), intent(inout), dimension(:), optional :: du3_osscol, dv3_osscol
real(kind=kind_phys), intent(inout), dimension(:), optional :: du3_ofdcol, dv3_ofdcol

real(kind=kind_phys), intent(inout), dimension(:,:) :: dtdt, dudt, dvdt

Expand Down
23 changes: 12 additions & 11 deletions physics/GWD/unified_ugwp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ subroutine unified_ugwp_init (me, master, nlunit, input_nml_file, logunit, &
integer, intent (in) :: me
integer, intent (in) :: master
integer, intent (in) :: nlunit
character(len=*), intent (in) :: input_nml_file(:)
character(len=*), intent (in), optional :: input_nml_file(:)
integer, intent (in) :: logunit
integer, intent (in) :: jdat(:)
integer, intent (in) :: lonr
Expand Down Expand Up @@ -272,10 +272,11 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
integer, intent(in), dimension(:) :: kpbl
real(kind=kind_phys), intent(in), dimension(:) :: ak, bk
real(kind=kind_phys), intent(in), dimension(:) :: oro, oro_uf, hprime, oc, theta, sigma, gamma
real(kind=kind_phys), intent(in), dimension(:) :: varss,oc1ss, dx
real(kind=kind_phys), intent(in), dimension(:), optional :: varss,oc1ss
real(kind=kind_phys), intent(in), dimension(:) :: dx

!vay-nov 2020
real(kind=kind_phys), intent(in), dimension(:,:) :: oa4ss,ol4ss
real(kind=kind_phys), intent(in), dimension(:,:), optional :: oa4ss,ol4ss

logical, intent(in) :: flag_for_gwd_generic_tend

Expand All @@ -292,20 +293,19 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
logical, intent(in) :: do_tofd, ldiag_ugwp, ugwp_seq_update

!Output (optional):
real(kind=kind_phys), intent(out) :: &
real(kind=kind_phys), intent(out), optional :: &
& dusfc_ms(:),dvsfc_ms(:), &
& dusfc_bl(:),dvsfc_bl(:), &
& dusfc_ss(:),dvsfc_ss(:), &
& dusfc_fd(:),dvsfc_fd(:)
real(kind=kind_phys), intent(out) :: &
real(kind=kind_phys), intent(out), optional :: &
& dtaux2d_ms(:,:),dtauy2d_ms(:,:), &
& dtaux2d_bl(:,:),dtauy2d_bl(:,:), &
& dtaux2d_ss(:,:),dtauy2d_ss(:,:), &
& dtaux2d_fd(:,:),dtauy2d_fd(:,:), &
& dudt_ngw(:,:),dvdt_ngw(:,:),dtdt_ngw(:,:)

real(kind=kind_phys), intent(in), optional :: hpbl(:)
real(kind=kind_phys), intent(in) :: br1(:), &
& hpbl(:), &
& slmsk(:)

real(kind=kind_phys), intent(out), dimension(:) :: dusfcg, dvsfcg
Expand All @@ -314,14 +314,15 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
real(kind=kind_phys), intent(out), dimension(:,:) :: gw_dudt, gw_dvdt, gw_dtdt, gw_kdis
real(kind=kind_phys), intent(out), dimension(:,:) :: dudt_mtb, dudt_tms

real(kind=kind_phys), intent(inout) :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:), index_of_temperature, index_of_x_wind, &
real(kind=kind_phys), intent(inout), optional :: dtend(:,:,:)
integer, intent(in) :: dtidx(:,:)
integer, intent(in) :: index_of_temperature, index_of_x_wind, &
index_of_y_wind, index_of_process_nonorographic_gwd, &
index_of_process_orographic_gwd
logical, intent(in) :: ldiag3d, lssav

! These arrays only allocated if ldiag_ugwp = .true.
real(kind=kind_phys), intent(inout), dimension(:,:) :: du3dt_mtb, du3dt_ogw, du3dt_tms
real(kind=kind_phys), intent(inout), dimension(:,:), optional :: du3dt_mtb, du3dt_ogw, du3dt_tms

real(kind=kind_phys), intent(inout), dimension(:,:) :: dudt, dvdt, dtdt

Expand All @@ -342,7 +343,7 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
do_gsl_drag_ls_bl, do_gsl_drag_ss, &
do_gsl_drag_tofd

real(kind=kind_phys), intent(in) :: spp_wts_gwd(:,:)
real(kind=kind_phys), intent(in), optional :: spp_wts_gwd(:,:)
integer, intent(in) :: spp_gwd

character(len=*), intent(out) :: errmsg
Expand Down
Loading

0 comments on commit 4e100f8

Please sign in to comment.