Skip to content

Commit

Permalink
fortran format fix
Browse files Browse the repository at this point in the history
  • Loading branch information
mzhangw committed Aug 27, 2019
1 parent d5f8a62 commit 73f95a6
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 10 deletions.
15 changes: 10 additions & 5 deletions physics/GFS_suite_interstitial.F90
Original file line number Diff line number Diff line change
Expand Up @@ -581,11 +581,16 @@ end subroutine GFS_suite_interstitial_3_finalize
!! | errflg | ccpp_error_flag | error flag for error handling in CCPP | flag | 0 | integer | | out | F |
!!
#endif
subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, satmedmf, trans_trac, do_shoc, ltaerosol, ntrac, ntcw, &
ntiw, ntclamt, ntrw, ntsw, ntrnc, ntsnc, ntgl, ntgnc, xlat, gq0, imp_physics, imp_physics_mg, imp_physics_zhao_carr,&
imp_physics_zhao_carr_pdf, imp_physics_gfdl, imp_physics_thompson, imp_physics_wsm6, imp_physics_fer_hires, prsi, &
prsl, prslk, rhcbot,hcpbl, rhctop, rhcmax, islmsk, work1, work2, kpbl, kinver,clw, rhc, save_qc, save_qi,errmsg, &
errflg)
subroutine GFS_suite_interstitial_3_run (im, levs, nn, cscnv, &
satmedmf, trans_trac, do_shoc, ltaerosol, ntrac, ntcw, &
ntiw, ntclamt, ntrw, ntsw, ntrnc, ntsnc, ntgl, ntgnc, &
xlat, gq0, imp_physics, imp_physics_mg, &
imp_physics_zhao_carr, imp_physics_zhao_carr_pdf, &
imp_physics_gfdl, imp_physics_thompson, &
imp_physics_wsm6, imp_physics_fer_hires, prsi, &
prsl, prslk, rhcbot,rhcpbl, rhctop, rhcmax, islmsk, &
work1, work2, kpbl, kinver,clw, rhc, save_qc, save_qi, &
errmsg, errflg)

use machine, only: kind_phys

Expand Down
3 changes: 1 addition & 2 deletions physics/module_MP_FER_HIRES.F90
Original file line number Diff line number Diff line change
Expand Up @@ -458,8 +458,7 @@ SUBROUTINE FER_HIRES (DT,RHgrd, &
!GFDL the relative humidity threshold for condensation ("RHgrd")
!6/11/2010 mod - Use lower RHgrd_out threshold for < 850 hPa
!------------------------------------------------------------
IF(DX1 .GE. 10 .AND. P_col(L)<P_RHgrd_out) THEN ! gopal's doing
based on GFDL
IF(DX1 .GE. 10 .AND. P_col(L)<P_RHgrd_out) THEN ! gopal's doing based on GFDL
RHC_col(L)=RHgrd
ELSE
RHC_col(L)=RHgrd_in
Expand Down
5 changes: 2 additions & 3 deletions physics/mp_fer_hires.F90
Original file line number Diff line number Diff line change
Expand Up @@ -184,7 +184,7 @@ SUBROUTINE mp_fer_hires_run(NCOL, NLEV, DT &
real(kind_phys), intent(inout) :: acprec(1:ncol)
real(kind_phys), intent(inout) :: refl_10cm(1:ncol,1:nlev)
real(kind_phys), intent(in ) :: rhgrd
real(kind_phys), intent(in ) :: dx
real(kind_phys), intent(in ) :: dx(1:ncol)
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg
!
Expand Down Expand Up @@ -243,8 +243,7 @@ SUBROUTINE mp_fer_hires_run(NCOL, NLEV, DT &
lm = nlev

! Use the dx of the 1st i point to set an integer value of dx to be used for
! determining where RHgrd
! should be set to 0.98 in the coarse domain when running HAFS.
! determining where RHgrd should be set to 0.98 in the coarse domain when running HAFS.
DX1=NINT(DX(1))


Expand Down

0 comments on commit 73f95a6

Please sign in to comment.