Skip to content
Draft
3 changes: 2 additions & 1 deletion test/capgen_test/temp_set.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ MODULE temp_set
!! \htmlinclude arg_table_temp_set_run.html
!!
SUBROUTINE temp_set_run(ncol, lev, timestep, temp_level, temp_diag, temp, ps, &
to_promote, promote_pcnst, slev_lbound, soil_levs, var_array, errmsg, errflg)
to_promote, promote_pcnst, slev_lbound, soil_levs, var_array, cld_frac, errmsg, errflg)
!----------------------------------------------------------------
IMPLICIT NONE
!----------------------------------------------------------------
Expand All @@ -36,6 +36,7 @@ SUBROUTINE temp_set_run(ncol, lev, timestep, temp_level, temp_diag, temp, ps, &
real(kind_phys), intent(out) :: promote_pcnst(:)
character(len=512), intent(out) :: errmsg
integer, intent(out) :: errflg
real(kind_phys), intent(in), optional :: cld_frac(:,:)
!----------------------------------------------------------------
integer :: ilev

Expand Down
9 changes: 9 additions & 0 deletions test/capgen_test/temp_set.meta
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,15 @@
type = real
kind = kind_phys
intent = inout
[ cld_frac ]
standard_name = cloud_fraction
long_name = cloud fraction
type = real
kind = kind_phys
units = Pa
dimensions = (horizontal_loop_extent, vertical_layer_dimension)
intent = in
optional = True
[ errmsg ]
standard_name = ccpp_error_message
long_name = Error message for error handling in CCPP
Expand Down
12 changes: 8 additions & 4 deletions test/capgen_test/test_capgen_host_integration.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ program test
character(len=cs), target :: test_parts1(2) = (/ 'physics1 ', &
'physics2 ' /)
character(len=cs), target :: test_parts2(1) = (/ 'data_prep ' /)
character(len=cm), target :: test_invars1(10) = (/ &
character(len=cm), target :: test_invars1(12) = (/ &
'potential_temperature ', &
'potential_temperature_at_interface ', &
'coefficients_for_interpolation ', &
Expand All @@ -16,7 +16,9 @@ program test
'soil_levels ', &
'temperature_at_diagnostic_levels ', &
'time_step_for_physics ', &
'array_variable_for_testing ' /)
'array_variable_for_testing ', &
'cloud_fraction ', &
'do_cloud_fraction_adjustment '/)
character(len=cm), target :: test_outvars1(10) = (/ &
'potential_temperature ', &
'potential_temperature_at_interface ', &
Expand All @@ -28,7 +30,7 @@ program test
'ccpp_error_code ', &
'ccpp_error_message ', &
'array_variable_for_testing ' /)
character(len=cm), target :: test_reqvars1(12) = (/ &
character(len=cm), target :: test_reqvars1(14) = (/ &
'potential_temperature ', &
'potential_temperature_at_interface ', &
'coefficients_for_interpolation ', &
Expand All @@ -40,7 +42,9 @@ program test
'temperature_at_diagnostic_levels ', &
'ccpp_error_code ', &
'ccpp_error_message ', &
'array_variable_for_testing ' /)
'array_variable_for_testing ', &
'cloud_fraction ', &
'do_cloud_fraction_adjustment '/)

character(len=cm), target :: test_invars2(3) = (/ &
'model_times ', &
Expand Down
3 changes: 2 additions & 1 deletion test/capgen_test/test_host_data.F90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ module test_host_data
real(kind_phys), dimension(:,:), allocatable :: &
u, & ! zonal wind (m/s)
v, & ! meridional wind (m/s)
pmid ! midpoint pressure (Pa)
pmid, & ! midpoint pressure (Pa)
cld_frac ! cloud fraction (1)
real(kind_phys), dimension(:,:,:),allocatable :: &
q ! constituent mixing ratio (kg/kg moist or dry air depending on type)
end type physics_state
Expand Down
8 changes: 8 additions & 0 deletions test/capgen_test/test_host_data.meta
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,14 @@
kind = kind_phys
units = Pa
dimensions = (horizontal_dimension, vertical_layer_dimension)
[ cld_frac ]
standard_name = cloud_fraction
long_name = cloud fraction
type = real
kind = kind_phys
units = Pa
dimensions = (horizontal_dimension, vertical_layer_dimension)
active = (do_cloud_fraction_adjustment)
[ soil_levs ]
standard_name = soil_levels
long_name = soil levels
Expand Down
3 changes: 2 additions & 1 deletion test/capgen_test/test_host_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,8 @@ module test_host_mod
integer, parameter :: num_time_steps = 2
real(kind_phys), parameter :: tolerance = 1.0e-13_kind_phys
real(kind_phys) :: tint_save(ncols, pverP)

logical, parameter :: cfrac_adj = .false.

public :: init_data
public :: compare_data
public :: check_model_times
Expand Down
6 changes: 6 additions & 0 deletions test/capgen_test/test_host_mod.meta
Original file line number Diff line number Diff line change
Expand Up @@ -131,3 +131,9 @@
units = none
dimensions = (horizontal_dimension,2,4,6)
type = real | kind = kind_phys
[ cfrac_adj ]
standard_name = do_cloud_fraction_adjustment
long_name = control for cloud fraction adjustment
units = none
dimensions = ()
type = logical