Skip to content

Commit

Permalink
Remove DIFZM as it is not used
Browse files Browse the repository at this point in the history
  • Loading branch information
cacraigucar committed May 22, 2024
1 parent 812d476 commit 600b8b6
Show file tree
Hide file tree
Showing 3 changed files with 43 additions and 52 deletions.
86 changes: 42 additions & 44 deletions src/physics/cam/clubb_intr.F90
Original file line number Diff line number Diff line change
Expand Up @@ -186,7 +186,7 @@ module clubb_intr
real(r8) :: clubb_bv_efold = unset_r8
real(r8) :: clubb_wpxp_Ri_exp = unset_r8
real(r8) :: clubb_z_displace = unset_r8

integer :: &
clubb_iiPDF_type, & ! Selected option for the two-component normal
! (double Gaussian) PDF type to use for the w, rt,
Expand Down Expand Up @@ -314,7 +314,7 @@ module clubb_intr
clubb_l_mono_flux_lim_um, & ! Flag to turn on monotonic flux limiter for um
clubb_l_mono_flux_lim_vm, & ! Flag to turn on monotonic flux limiter for vm
clubb_l_mono_flux_lim_spikefix, & ! Flag to implement monotonic flux limiter code that
! eliminates spurious drying tendencies at model top
! eliminates spurious drying tendencies at model top
clubb_l_intr_sfc_flux_smooth = .false. ! Add a locally calculated roughness to upwp and vpwp sfc fluxes

! Constant parameters
Expand Down Expand Up @@ -433,7 +433,6 @@ module clubb_intr

integer :: &
dlfzm_idx = -1, & ! ZM detrained convective cloud water mixing ratio.
difzm_idx = -1, & ! ZM detrained convective cloud ice mixing ratio.
dnlfzm_idx = -1, & ! ZM detrained convective cloud water num concen.
dnifzm_idx = -1 ! ZM detrained convective cloud ice num concen.

Expand Down Expand Up @@ -477,7 +476,7 @@ subroutine clubb_register_cam( )
! Register physics buffer fields and constituents !
!------------------------------------------------ !

! Add CLUBB fields to pbuf
! Add CLUBB fields to pbuf
use physics_buffer, only: pbuf_add_field, dtype_r8, dtype_i4, dyn_time_lvls
use subcol_utils, only: subcol_get_scheme

Expand Down Expand Up @@ -844,7 +843,7 @@ subroutine clubb_readnl(nlfile)

!----- Begin Code -----

! Determine if we want clubb_history to be output
! Determine if we want clubb_history to be output
clubb_history = .false. ! Initialize to false
stats_metadata%l_stats = .false. ! Initialize to false
stats_metadata%l_output_rad_files = .false. ! Initialize to false
Expand Down Expand Up @@ -1201,7 +1200,7 @@ subroutine clubb_readnl(nlfile)

! Overwrite defaults if they are true
if (clubb_history) stats_metadata%l_stats = .true.
if (clubb_rad_history) stats_metadata%l_output_rad_files = .true.
if (clubb_rad_history) stats_metadata%l_output_rad_files = .true.
if (clubb_cloudtop_cooling) do_cldcool = .true.
if (clubb_rainevap_turb) do_rainturb = .true.

Expand Down Expand Up @@ -1529,7 +1528,7 @@ subroutine clubb_ini_cam(pbuf2d)
stats_metadata%l_stats_samp = .false.
stats_metadata%l_grads = .false.

! Overwrite defaults if needbe
! Overwrite defaults if needbe
if (stats_metadata%l_stats) stats_metadata%l_stats_samp = .true.

! Define physics buffers indexes
Expand Down Expand Up @@ -1679,7 +1678,7 @@ subroutine clubb_ini_cam(pbuf2d)
clubb_params(ibv_efold) = clubb_bv_efold
clubb_params(iwpxp_Ri_exp) = clubb_wpxp_Ri_exp
clubb_params(iz_displace) = clubb_z_displace

! Set up CLUBB core. Note that some of these inputs are overwritten
! when clubb_tend_cam is called. The reason is that heights can change
! at each time step, which is why dummy arrays are read in here for heights
Expand Down Expand Up @@ -2426,7 +2425,6 @@ subroutine clubb_tend_cam( state, ptend_all, pbuf, hdtime, &

! ZM microphysics
real(r8), pointer :: dlfzm(:,:) ! ZM detrained convective cloud water mixing ratio.
real(r8), pointer :: difzm(:,:) ! ZM detrained convective cloud ice mixing ratio.
real(r8), pointer :: dnlfzm(:,:) ! ZM detrained convective cloud water num concen.
real(r8), pointer :: dnifzm(:,:) ! ZM detrained convective cloud ice num concen.

Expand Down Expand Up @@ -2489,9 +2487,9 @@ subroutine clubb_tend_cam( state, ptend_all, pbuf, hdtime, &
character(len=*), parameter :: subr='clubb_tend_cam'
real(r8), parameter :: rad2deg=180.0_r8/pi
real(r8) :: tmp_lon1, tmp_lonN

type(grid) :: gr

type(nu_vertical_res_dep) :: nu_vert_res_dep ! Vertical resolution dependent nu values
real(r8) :: lmin

Expand Down Expand Up @@ -3033,10 +3031,10 @@ subroutine clubb_tend_cam( state, ptend_all, pbuf, hdtime, &

stats_nsamp = nint(stats_metadata%stats_tsamp/dtime)
stats_nout = nint(stats_metadata%stats_tout/dtime)
! Heights need to be set at each timestep. Therefore, recall
! setup_grid and setup_parameters for this.

! Heights need to be set at each timestep. Therefore, recall
! setup_grid and setup_parameters for this.

! Set-up CLUBB core at each CLUBB call because heights can change
! Important note: do not make any calls that use CLUBB grid-height
! operators (such as zt2zm_api, etc.) until AFTER the
Expand Down Expand Up @@ -3333,7 +3331,7 @@ subroutine clubb_tend_cam( state, ptend_all, pbuf, hdtime, &


do t=1,nadv ! do needed number of "sub" timesteps for each CAM step

! Increment the statistics then begin stats timestep
if (stats_metadata%l_stats) then
call stats_begin_timestep_api( t, stats_nsamp, stats_nout, &
Expand Down Expand Up @@ -3808,7 +3806,7 @@ subroutine clubb_tend_cam( state, ptend_all, pbuf, hdtime, &

rtm_integral_ltend(:) = rtm_integral_ltend(:)/gravit
rtm_integral_vtend(:) = rtm_integral_vtend(:)/gravit

if (clubb_do_adv) then
if (macmic_it == cld_macmic_num_steps) then

Expand Down Expand Up @@ -4370,8 +4368,8 @@ subroutine clubb_tend_cam( state, ptend_all, pbuf, hdtime, &
end if

! Output CLUBB history here
if (stats_metadata%l_stats) then
if (stats_metadata%l_stats) then

do j=1,stats_zt(1)%num_output_fields

temp1 = trim(stats_zt(1)%file%grid_avg_var(j)%name)
Expand All @@ -4390,7 +4388,7 @@ subroutine clubb_tend_cam( state, ptend_all, pbuf, hdtime, &
call outfld(trim(sub),out_zm(:,:,j), pcols, lchnk)
enddo

if (stats_metadata%l_output_rad_files) then
if (stats_metadata%l_output_rad_files) then
do j=1,stats_rad_zt(1)%num_output_fields
call outfld(trim(stats_rad_zt(1)%file%grid_avg_var(j)%name), out_radzt(:,:,j), pcols, lchnk)
enddo
Expand Down Expand Up @@ -4758,8 +4756,8 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
! Initialize zt (mass points)

i = 1
do while ( ichar(clubb_vars_zt(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_zt(i)) /= 0 .and. &
do while ( ichar(clubb_vars_zt(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_zt(i)) /= 0 .and. &
i <= nvarmax_zt )
i = i + 1
enddo
Expand Down Expand Up @@ -4802,8 +4800,8 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
! Initialize zm (momentum points)

i = 1
do while ( ichar(clubb_vars_zm(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_zm(i)) /= 0 .and. &
do while ( ichar(clubb_vars_zm(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_zm(i)) /= 0 .and. &
i <= nvarmax_zm )
i = i + 1
end do
Expand Down Expand Up @@ -4839,10 +4837,10 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
! Initialize rad_zt (radiation points)

if (stats_metadata%l_output_rad_files) then

i = 1
do while ( ichar(clubb_vars_rad_zt(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_rad_zt(i)) /= 0 .and. &
do while ( ichar(clubb_vars_rad_zt(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_rad_zt(i)) /= 0 .and. &
i <= nvarmax_rad_zt )
i = i + 1
end do
Expand Down Expand Up @@ -4876,10 +4874,10 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
stats_metadata, stats_rad_zt(j) )

! Initialize rad_zm (radiation points)

i = 1
do while ( ichar(clubb_vars_rad_zm(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_rad_zm(i)) /= 0 .and. &
do while ( ichar(clubb_vars_rad_zm(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_rad_zm(i)) /= 0 .and. &
i <= nvarmax_rad_zm )
i = i + 1
end do
Expand Down Expand Up @@ -4908,7 +4906,7 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &

allocate( stats_rad_zm(j)%file%grid_avg_var( stats_rad_zm(j)%num_output_fields ) )
allocate( stats_rad_zm(j)%file%z( stats_rad_zm(j)%kk ) )

call stats_init_rad_zm_api( clubb_vars_rad_zm, &
l_error, &
stats_metadata, stats_rad_zm(j) )
Expand All @@ -4918,8 +4916,8 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
! Initialize sfc (surface point)

i = 1
do while ( ichar(clubb_vars_sfc(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_sfc(i)) /= 0 .and. &
do while ( ichar(clubb_vars_sfc(i)(1:1)) /= 0 .and. &
len_trim(clubb_vars_sfc(i)) /= 0 .and. &
i <= nvarmax_sfc )
i = i + 1
end do
Expand Down Expand Up @@ -4961,30 +4959,30 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
endif

! Now call add fields

do i = 1, stats_zt(1)%num_output_fields

temp1 = trim(stats_zt(1)%file%grid_avg_var(i)%name)
sub = temp1
if (len(temp1) > max_fieldname_len) sub = temp1(1:max_fieldname_len)

call addfld( trim(sub), (/ 'ilev' /), 'A', &
trim(stats_zt(1)%file%grid_avg_var(i)%units), &
trim(stats_zt(1)%file%grid_avg_var(i)%description) )
enddo

do i = 1, stats_zm(1)%num_output_fields

temp1 = trim(stats_zm(1)%file%grid_avg_var(i)%name)
sub = temp1
if (len(temp1) > max_fieldname_len) sub = temp1(1:max_fieldname_len)

call addfld( trim(sub), (/ 'ilev' /), 'A', &
trim(stats_zm(1)%file%grid_avg_var(i)%units), &
trim(stats_zm(1)%file%grid_avg_var(i)%description) )
enddo

if (stats_metadata%l_output_rad_files) then
if (stats_metadata%l_output_rad_files) then

do i = 1, stats_rad_zt(1)%num_output_fields
temp1 = trim(stats_rad_zt(1)%file%grid_avg_var(i)%name)
Expand All @@ -4994,7 +4992,7 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
trim(stats_rad_zt(1)%file%grid_avg_var(i)%units), &
trim(stats_rad_zt(1)%file%grid_avg_var(i)%description) )
enddo

do i = 1, stats_rad_zm(1)%num_output_fields
temp1 = trim(stats_rad_zm(1)%file%grid_avg_var(i)%name)
sub = temp1
Expand All @@ -5004,7 +5002,7 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
trim(stats_rad_zm(1)%file%grid_avg_var(i)%description) )
enddo
endif

do i = 1, stats_sfc(1)%num_output_fields
temp1 = trim(stats_sfc(1)%file%grid_avg_var(i)%name)
sub = temp1
Expand All @@ -5013,7 +5011,7 @@ subroutine stats_init_clubb( l_stats_in, stats_tsamp_in, stats_tout_in, &
trim(stats_sfc(1)%file%grid_avg_var(i)%units), &
trim(stats_sfc(1)%file%grid_avg_var(i)%description) )
enddo


return

Expand Down Expand Up @@ -5102,7 +5100,7 @@ subroutine stats_end_timestep_clubb(thecol, stats_zt, stats_zm, stats_rad_zt, st
enddo
enddo

if (stats_metadata%l_output_rad_files) then
if (stats_metadata%l_output_rad_files) then
do i = 1, stats_rad_zt%num_output_fields
do k = 1, stats_rad_zt%kk
out_radzt(thecol,pverp-k+1,i) = stats_rad_zt%accum_field_values(1,1,k,i)
Expand Down
2 changes: 0 additions & 2 deletions src/physics/cam/macrop_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,6 @@ module macrop_driver

integer :: &
dlfzm_idx = -1, & ! ZM detrained convective cloud water mixing ratio.
difzm_idx = -1, & ! ZM detrained convective cloud ice mixing ratio.
dnlfzm_idx = -1, & ! ZM detrained convective cloud water num concen.
dnifzm_idx = -1 ! ZM detrained convective cloud ice num concen.

Expand Down Expand Up @@ -486,7 +485,6 @@ subroutine macrop_driver_tend( &

! ZM microphysics
real(r8), pointer :: dlfzm(:,:) ! ZM detrained convective cloud water mixing ratio.
real(r8), pointer :: difzm(:,:) ! ZM detrained convective cloud ice mixing ratio.
real(r8), pointer :: dnlfzm(:,:) ! ZM detrained convective cloud water num concen.
real(r8), pointer :: dnifzm(:,:) ! ZM detrained convective cloud ice num concen.

Expand Down
7 changes: 1 addition & 6 deletions src/physics/cam/zm_conv_intr.F90
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,6 @@ module zm_conv_intr
ixorg, &
dp_cldice_idx, &
dlfzm_idx, & ! detrained convective cloud water mixing ratio.
difzm_idx, & ! detrained convective cloud ice mixing ratio.
prec_dp_idx, &
snow_dp_idx, &
mconzm_idx ! convective mass flux
Expand Down Expand Up @@ -149,8 +148,6 @@ subroutine zm_conv_register
! detrained convective cloud water mixing ratio.
call pbuf_add_field('DLFZM', 'physpkg', dtype_r8, (/pcols,pver/), dlfzm_idx)
! detrained convective cloud ice mixing ratio.
call pbuf_add_field('DIFZM', 'physpkg', dtype_r8, (/pcols,pver/), difzm_idx)
! convective mass fluxes
call pbuf_add_field('CMFMC_DP', 'physpkg', dtype_r8, (/pcols,pverp/), mconzm_idx)

!CACNOTE - Is zm_org really a constituent or was it just a handy structure to use for an allocatable which persists in the run?
Expand Down Expand Up @@ -442,7 +439,7 @@ subroutine zm_conv_tend(pblh ,mcon ,cme , &
real(r8), pointer, dimension(:,:) :: dp_cldliq
real(r8), pointer, dimension(:,:) :: dp_cldice
real(r8), pointer :: dlf(:,:) ! detrained convective cloud water mixing ratio.
real(r8), pointer :: dif(:,:) ! detrained convective cloud ice mixing ratio.
real(r8) :: dif(pcols,pver) ! detrained convective cloud ice mixing ratio.
real(r8), pointer :: lambdadpcu(:,:) ! slope of cloud liquid size distr
real(r8), pointer :: mudpcu(:,:) ! width parameter of droplet size distr
real(r8), pointer :: mconzm(:,:) !convective mass fluxes
Expand Down Expand Up @@ -536,10 +533,8 @@ subroutine zm_conv_tend(pblh ,mcon ,cme , &
call pbuf_get_field(pbuf, zm_ideep_idx, ideep)

call pbuf_get_field(pbuf, dlfzm_idx, dlf)
call pbuf_get_field(pbuf, difzm_idx, dif)
call pbuf_get_field(pbuf, mconzm_idx, mconzm)

!
! Begin with Zhang-McFarlane (1996) convection parameterization
!
call t_startf ('zm_convr_run')
Expand Down

0 comments on commit 600b8b6

Please sign in to comment.