Skip to content

Commit

Permalink
Merge branch 'qingfu_changes' of https://github.com/qingfu-liu/ccpp-p…
Browse files Browse the repository at this point in the history
…hysics into bugfix/ozphys_ccpp_compliant
  • Loading branch information
climbfuji committed Feb 21, 2024
2 parents 877bb1f + 82c6873 commit c468c66
Show file tree
Hide file tree
Showing 7 changed files with 36 additions and 88 deletions.
4 changes: 2 additions & 2 deletions physics/GWD/unified_ugwp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -253,7 +253,7 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
cdmbgwd, jdat, xlat, xlat_d, sinlat, coslat, area, &
ugrs, vgrs, tgrs, q1, prsi, prsl, prslk, phii, phil, &
del, kpbl, dusfcg, dvsfcg, gw_dudt, gw_dvdt, gw_dtdt, gw_kdis, &
tau_tofd, tau_mtb, tau_ogw, tau_ngw, zmtb, zlwb, zogw, &
tau_tofd, tau_mtb, tau_ogw, tau_ngw, &
dudt_mtb, dudt_tms, du3dt_mtb, du3dt_ogw, du3dt_tms, &
dudt, dvdt, dtdt, rdxzb, con_g, con_omega, con_pi, con_cp, con_rd, con_rv, &
con_rerth, con_fvirt, rain, ntke, q_tke, dqdt_tke, lprnt, ipr, &
Expand Down Expand Up @@ -309,7 +309,7 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
& slmsk(:)

real(kind=kind_phys), intent(out), dimension(:) :: dusfcg, dvsfcg
real(kind=kind_phys), intent(out), dimension(:) :: zmtb, zlwb, zogw, rdxzb
real(kind=kind_phys), intent(out), dimension(:) :: rdxzb
real(kind=kind_phys), intent(out), dimension(:) :: tau_mtb, tau_ogw, tau_tofd, tau_ngw
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
Expand Down
24 changes: 0 additions & 24 deletions physics/GWD/unified_ugwp.meta
Original file line number Diff line number Diff line change
Expand Up @@ -900,30 +900,6 @@
type = real
kind = kind_phys
intent = out
[zmtb]
standard_name = height_of_mountain_blocking
long_name = height of mountain blocking drag
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[zlwb]
standard_name = height_of_low_level_wave_breaking
long_name = height of low level wave breaking
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[zogw]
standard_name = height_of_launch_level_of_orographic_gravity_wave
long_name = height of launch level of orographic gravity wave
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[dudt_mtb]
standard_name = instantaneous_change_in_x_wind_due_to_mountain_blocking_drag
long_name = instantaneous change in x wind due to mountain blocking drag
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -61,8 +61,7 @@ end subroutine GFS_surface_generic_pre_init
!!
subroutine GFS_surface_generic_pre_run (nthreads, im, levs, vfrac, islmsk, isot, ivegsrc, stype, scolor,vtype, slope, &
prsik_1, prslk_1, tsfc, phil, con_g, sigmaf, work3, zlvl, &
drain_cpl, dsnow_cpl, rain_cpl, snow_cpl, lndp_type, n_var_lndp, sfc_wts, &
lndp_var_list, lndp_prt_list, &
lndp_type, n_var_lndp, sfc_wts, lndp_var_list, lndp_prt_list, &
z01d, zt1d, bexp1d, xlai1d, vegf1d, lndp_vgf, &
cplflx, flag_cice, islmsk_cice, slimskin_cpl, &
wind, u1, v1, cnvwind, smcwlt2, smcref2, vtype_save, stype_save,scolor_save, slope_save, &
Expand All @@ -87,10 +86,6 @@ subroutine GFS_surface_generic_pre_run (nthreads, im, levs, vfrac, islmsk, isot,
real(kind=kind_phys), dimension(:), intent(inout) :: sigmaf, work3, zlvl

! Stochastic physics / surface perturbations
real(kind=kind_phys), dimension(:), intent(out) :: drain_cpl
real(kind=kind_phys), dimension(:), intent(out) :: dsnow_cpl
real(kind=kind_phys), dimension(:), intent(in) :: rain_cpl
real(kind=kind_phys), dimension(:), intent(in) :: snow_cpl
integer, intent(in) :: lndp_type, n_var_lndp
character(len=3), dimension(:), intent(in) :: lndp_var_list
real(kind=kind_phys), dimension(:), intent(in) :: lndp_prt_list
Expand Down
32 changes: 0 additions & 32 deletions physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_generic_pre.meta
Original file line number Diff line number Diff line change
Expand Up @@ -290,38 +290,6 @@
type = real
kind = kind_phys
intent = inout
[drain_cpl]
standard_name = tendency_of_lwe_thickness_of_rain_amount_on_dynamics_timestep_for_coupling
long_name = change in rain_cpl (coupling_type)
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[dsnow_cpl]
standard_name = tendency_of_lwe_thickness_of_snowfall_amount_on_dynamics_timestep_for_coupling
long_name = change in show_cpl (coupling_type)
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[rain_cpl]
standard_name = cumulative_lwe_thickness_of_precipitation_amount_for_coupling
long_name = total rain precipitation
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[snow_cpl]
standard_name = cumulative_lwe_thickness_of_snow_amount_for_coupling
long_name = total snow precipitation
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[lndp_type]
standard_name = control_for_stochastic_land_surface_perturbation
long_name = index for stochastic land surface perturbations type
Expand Down
8 changes: 4 additions & 4 deletions physics/Interstitials/UFS_SCM_NEPTUNE/dcyc2t3.f
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module dcyc2t3
! input/output: !
! dtdt,dtdtnp, !
! outputs: !
! adjsfcdsw,adjsfcnsw,adjsfcdlw,adjsfculw, !
! adjsfcdsw,adjsfcnsw,adjsfcdlw, !
! adjsfculw_lnd,adjsfculw_ice,adjsfculw_wat,xmu,xcosz, !
! adjnirbmu,adjnirdfu,adjvisbmu,adjvisdfu, !
! adjdnnbmd,adjdnndfd,adjdnvbmd,adjdnvdfd) !
Expand Down Expand Up @@ -181,7 +181,7 @@ subroutine dcyc2t3_run &
! --- input/output:
& dtdt,dtdtnp,htrlw, &
! --- outputs:
& adjsfcdsw,adjsfcnsw,adjsfcdlw,adjsfculw, &
& adjsfcdsw,adjsfcnsw,adjsfcdlw, &
& adjsfculw_lnd,adjsfculw_ice,adjsfculw_wat,xmu,xcosz, &
& adjnirbmu,adjnirdfu,adjvisbmu,adjvisdfu, &
& adjnirbmd,adjnirdfd,adjvisbmd,adjvisdfd, &
Expand Down Expand Up @@ -242,7 +242,7 @@ subroutine dcyc2t3_run &

! --- outputs:
real(kind=kind_phys), dimension(:), intent(out) :: &
& adjsfcdsw, adjsfcnsw, adjsfcdlw, adjsfculw, xmu, xcosz, &
& adjsfcdsw, adjsfcnsw, adjsfcdlw, xmu, xcosz, &
& adjnirbmu, adjnirdfu, adjvisbmu, adjvisdfu, &
& adjnirbmd, adjnirdfd, adjvisbmd, adjvisdfd

Expand Down Expand Up @@ -352,7 +352,7 @@ subroutine dcyc2t3_run &

! if (lprnt .and. i == ipr) write(0,*)' in dcyc3: dry==',dry(i)
! &,' wet=',wet(i),' icy=',icy(i),' tsfc3=',tsfc3(i,:)
! &,' sfcemis=',sfcemis(i,:),' adjsfculw=',adjsfculw(i,:)
! &,' sfcemis=',sfcemis(i,:)
!

!> - normalize by average value over radiation period for daytime.
Expand Down
8 changes: 0 additions & 8 deletions physics/Interstitials/UFS_SCM_NEPTUNE/dcyc2t3.meta
Original file line number Diff line number Diff line change
Expand Up @@ -524,14 +524,6 @@
type = real
kind = kind_phys
intent = out
[adjsfculw]
standard_name = surface_upwelling_longwave_flux
long_name = surface upwelling longwave flux at current time
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[adjsfculw_lnd]
standard_name = surface_upwelling_longwave_flux_over_land
long_name = surface upwelling longwave flux at current time over land
Expand Down
41 changes: 29 additions & 12 deletions physics/photochem/module_ozphys.F90
Original file line number Diff line number Diff line change
Expand Up @@ -95,13 +95,18 @@ function load_o3prog(this, file, fileID) result (err_message)
integer, intent(in) :: fileID
character(len=*), intent(in) :: file
character(len=128) :: err_message
integer :: i1, i2, i3
integer :: i1, i2, i3, ierr
real(kind=4), dimension(:), allocatable :: lat4, pres4, time4, tempin
real(kind=4) :: blatc4

! initialize error message
err_message = ""

! Get dimensions from data file
open(unit=fileID,file=trim(file), form='unformatted', convert='big_endian')
read (fileID) this%ncf, this%nlat, this%nlev, this%ntime
open(unit=fileID,file=trim(file), form='unformatted', convert='big_endian', iostat=ierr, iomsg=err_message)
if (ierr /= 0 ) return
read (fileID, iostat=ierr, iomsg=err_message) this%ncf, this%nlat, this%nlev, this%ntime
if (ierr /= 0 ) return
rewind(fileID)

allocate (this%lat(this%nlat))
Expand All @@ -111,7 +116,8 @@ function load_o3prog(this, file, fileID) result (err_message)
allocate (this%data(this%nlat,this%nlev,this%ncf,this%ntime))

allocate(lat4(this%nlat), pres4(this%nlev), time4(this%ntime+1))
read (fileID) this%ncf, this%nlat, this%nlev, this%ntime, lat4, pres4, time4
read (fileID, iostat=ierr, iomsg=err_message) this%ncf, this%nlat, this%nlev, this%ntime, lat4, pres4, time4
if (ierr /= 0 ) return

! Store
this%pres(:) = pres4(:)
Expand All @@ -124,7 +130,8 @@ function load_o3prog(this, file, fileID) result (err_message)
do i1=1,this%ntime
do i2=1,this%ncf
do i3=1,this%nlev
read(fileID) tempin
read(fileID, iostat=ierr, iomsg=err_message) tempin
if (ierr /= 0 ) return
this%data(:,i3,i2,i1) = tempin(:)
enddo
enddo
Expand Down Expand Up @@ -526,12 +533,18 @@ function load_o3clim(this, file, fileID) result (err_message)

! Locals
real(kind=4) :: blatc4
integer :: iLev, iLat, imo
integer :: iLev, iLat, imo, ierr
real(kind=4), allocatable :: o3clim4(:,:,:), pstr4(:)
integer, allocatable :: imond(:), ilatt(:,:)

open(unit=fileID,file=trim(file), form='unformatted', convert='big_endian')
read (fileID,end=101) this%nlatc, this%nlevc, this%ntimec, blatc4
! initialize error message
err_message = ""

open(unit=fileID,file=trim(file),form='unformatted',convert='big_endian', iostat=ierr, iomsg=err_message)
if (ierr /= 0 ) return
read (fileID,end=101,iostat=ierr,iomsg=err_message) this%nlatc, this%nlevc, this%ntimec, blatc4
if (ierr /= 0 ) return

101 if (this%nlevc < 10 .or. this%nlevc > 100) then
rewind (fileID)
this%nlevc = 17
Expand All @@ -551,15 +564,18 @@ function load_o3clim(this, file, fileID) result (err_message)
allocate (this%pkstr(this%nlevc), this%pstr(this%nlevc), this%datac(this%nlatc,this%nlevc,12))
if ( this%nlevc == 17 ) then ! For the operational ozone climatology
do iLev = 1, this%nlevc
read (fileID,15) pstr4(iLev)
read (fileID,15,iostat=ierr,iomsg=err_message) pstr4(iLev)
if (ierr /= 0 ) return
15 format(f10.3)
enddo

do imo = 1, 12
do iLat = 1, this%nlatc
read (fileID,16) imond(imo), ilatt(iLat,imo), (o3clim4(iLat,iLev,imo),iLev=1,10)
read (fileID,16,iostat=ierr,iomsg=err_message) imond(imo), ilatt(iLat,imo), (o3clim4(iLat,iLev,imo),iLev=1,10)
if (ierr /= 0 ) return
16 format(i2,i4,10f6.2)
read (fileID,20) (o3clim4(iLat,iLev,imo),iLev=11,this%nlevc)
read (fileID,20,iostat=ierr,iomsg=err_message) (o3clim4(iLat,iLev,imo),iLev=11,this%nlevc)
if (ierr /= 0 ) return
20 format(6x,10f6.2)
enddo
enddo
Expand All @@ -571,7 +587,8 @@ function load_o3clim(this, file, fileID) result (err_message)

do imo = 1, 12
do iLev = 1, this%nlevc
read (fileID) (o3clim4(iLat,iLev,imo),iLat=1,this%nlatc)
read (fileID,iostat=ierr,iomsg=err_message) (o3clim4(iLat,iLev,imo),iLat=1,this%nlatc)
if (ierr /= 0 ) return
enddo
enddo
endif ! end if_this%nlevc_block
Expand Down

0 comments on commit c468c66

Please sign in to comment.