90 type(model_state_type),
target,
intent(inout) :: current_state
94 allocate(current_state%global_grid%configuration%vertical%savolubar(current_state%local_grid%size(z_index)))
97 allocate(current_state%global_grid%configuration%vertical%savolvbar(current_state%local_grid%size(z_index)))
100 allocate(
resetq_min(current_state%number_q_fields))
101 cfl_is_enabled=is_component_enabled(current_state%options_database,
"cfltest")
107 l_qdiag = (.not. current_state%passive_q .and. current_state%number_q_fields .gt. 0)
129 allocate(
tend_3d_th(current_state%local_grid%size(z_index), &
130 current_state%local_grid%size(y_index), &
131 current_state%local_grid%size(x_index) ) )
134 iqv=get_q_index(standard_q_names%VAPOUR,
'stepfields')
135 allocate(
tend_3d_qv(current_state%local_grid%size(z_index), &
136 current_state%local_grid%size(y_index), &
137 current_state%local_grid%size(x_index) ) )
140 iql=get_q_index(standard_q_names%CLOUD_LIQUID_MASS,
'stepfields')
141 allocate(
tend_3d_ql(current_state%local_grid%size(z_index), &
142 current_state%local_grid%size(y_index), &
143 current_state%local_grid%size(x_index) ) )
146 iqi=get_q_index(standard_q_names%ICE_MASS,
'stepfields')
147 allocate(
tend_3d_qi(current_state%local_grid%size(z_index), &
148 current_state%local_grid%size(y_index), &
149 current_state%local_grid%size(x_index) ) )
152 iqr=get_q_index(standard_q_names%RAIN_MASS,
'stepfields')
153 allocate(
tend_3d_qr(current_state%local_grid%size(z_index), &
154 current_state%local_grid%size(y_index), &
155 current_state%local_grid%size(x_index) ) )
158 iqs=get_q_index(standard_q_names%SNOW_MASS,
'stepfields')
159 allocate(
tend_3d_qs(current_state%local_grid%size(z_index), &
160 current_state%local_grid%size(y_index), &
161 current_state%local_grid%size(x_index) ) )
164 iqg=get_q_index(standard_q_names%GRAUPEL_MASS,
'stepfields')
165 allocate(
tend_3d_qg(current_state%local_grid%size(z_index), &
166 current_state%local_grid%size(y_index), &
167 current_state%local_grid%size(x_index) ) )
170 allocate(
tend_3d_tabs(current_state%local_grid%size(z_index), &
171 current_state%local_grid%size(y_index), &
172 current_state%local_grid%size(x_index) ) )
177 allocate(
tend_pr_tot_th(current_state%local_grid%size(z_index)) )
180 allocate(
tend_pr_tot_qv(current_state%local_grid%size(z_index)) )
183 allocate(
tend_pr_tot_ql(current_state%local_grid%size(z_index)) )
186 allocate(
tend_pr_tot_qi(current_state%local_grid%size(z_index)) )
189 allocate(
tend_pr_tot_qr(current_state%local_grid%size(z_index)) )
192 allocate(
tend_pr_tot_qs(current_state%local_grid%size(z_index)) )
195 allocate(
tend_pr_tot_qg(current_state%local_grid%size(z_index)) )
210 type(model_state_type),
target,
intent(inout) :: current_state
237 type(model_state_type),
target,
intent(inout) :: current_state
240 integer :: current_x_index, current_y_index, target_x_index, target_y_index
242 current_x_index=current_state%column_local_x
243 current_y_index=current_state%column_local_y
244 target_y_index=current_y_index-current_state%local_grid%halo_size(y_index)
245 target_x_index=current_x_index-current_state%local_grid%halo_size(x_index)
248 if (
cfl_is_enabled .and. current_state%first_timestep_column)
then
249 if (mod(current_state%timestep, current_state%cfl_frequency) == 1 .or. &
250 current_state%timestep-current_state%start_timestep .le. current_state%cfl_frequency)
then
258 if (.not. current_state%halo_column)
then
266 do iq=1,current_state%number_q_fields
267 if (current_state%first_timestep_column)
then
268 resetq_min(iq)=minval(current_state%zq(iq)%data(:,current_state%column_local_y, current_state%column_local_x))
271 minval(current_state%zq(iq)%data(:,current_state%column_local_y, current_state%column_local_x)))
274 current_state%column_local_x-2, current_state%column_local_y-1, current_state%zq(iq), current_state%local_grid)
280 if (current_state%first_timestep_column)
then
316 type(model_state_type),
target,
intent(inout) :: current_state
318 integer :: x_prev, y_prev, i, k
319 real(kind=default_precision) :: c1, c2
321 x_prev = current_state%column_local_x-2
322 y_prev = current_state%column_local_y-1
324 c1 = 1.0_default_precision - 2.0_default_precision*current_state%tsmth
325 c2 = current_state%tsmth
328 current_state%global_grid%configuration%vertical%savolubar=current_state%global_grid%configuration%vertical%olzubar
329 call step_single_field(current_state%column_local_x, current_state%column_local_y, &
330 x_prev, y_prev, current_state%u, current_state%zu, current_state%su, current_state%local_grid, .true., &
331 current_state%field_stepping, current_state%dtm, current_state%ugal, c1, c2, .false., current_state%savu)
334 current_state%global_grid%configuration%vertical%savolvbar=current_state%global_grid%configuration%vertical%olzvbar
335 call step_single_field(current_state%column_local_x, current_state%column_local_y, &
336 x_prev, y_prev, current_state%v, current_state%zv, current_state%sv, current_state%local_grid, .true., &
337 current_state%field_stepping, current_state%dtm, current_state%vgal, c1, c2, .false., current_state%savv)
340 call step_single_field(current_state%column_local_x, current_state%column_local_y, &
341 x_prev, y_prev, current_state%w, current_state%zw, current_state%sw, current_state%local_grid, .false., &
342 current_state%field_stepping, current_state%dtm, real(0., kind=default_precision), c1, c2, .false., current_state%savw)
344 if (current_state%th%active)
then
345 call step_single_field(current_state%column_local_x, current_state%column_local_y, &
346 x_prev, y_prev, current_state%th, current_state%zth, current_state%sth, current_state%local_grid, .false., &
347 current_state%field_stepping, current_state%dtm, real(0., kind=default_precision), c1, c2, &
348 current_state%field_stepping == centred_stepping)
350 do i=1,current_state%number_q_fields
351 if (current_state%q(i)%active)
then
352 call step_single_field(current_state%column_local_x, current_state%column_local_y, x_prev, y_prev, &
353 current_state%q(i), current_state%zq(i), current_state%sq(i), current_state%local_grid, .false., &
354 current_state%field_stepping, current_state%dtm, real(0., kind=default_precision), c1, c2, &
355 current_state%field_stepping == centred_stepping)
366 type(model_state_type),
target,
intent(inout) :: current_state
367 integer,
intent(in) :: local_x, local_y
371 do k=2, current_state%local_grid%local_domain_end_index(z_index)
373 current_state%local_zumax = max(current_state%local_zumax, current_state%zu%data(k,local_y,local_x))
374 current_state%local_zumin = min(current_state%local_zumin, current_state%zu%data(k,local_y,local_x))
377 current_state%local_zvmax = max(current_state%local_zvmax, current_state%zv%data(k,local_y,local_x))
378 current_state%local_zvmin = min(current_state%local_zvmin, current_state%zv%data(k,local_y,local_x))
381 if (k .lt. current_state%local_grid%local_domain_end_index(z_index))
then
382 current_state%abswmax(k) = max(current_state%abswmax(k), abs(current_state%zw%data(k,local_y,local_x)))
391 type(model_state_type),
intent(inout),
target :: current_state
394 current_state%local_zumin=rlargep
395 current_state%local_zumax=-rlargep
396 current_state%local_zvmin=rlargep
397 current_state%local_zvmax=-rlargep
398 current_state%abswmax=-rlargep
410 integer,
intent(in) :: x_local_index, y_local_index, x_prev, y_prev
411 type(local_grid_type),
intent(inout) :: local_grid
412 type(prognostic_field_type),
intent(inout) :: field
414 if (x_prev .ge. local_grid%local_domain_start_index(x_index))
then
417 if (x_local_index == local_grid%local_domain_end_index(x_index))
then
418 if (x_local_index .gt. 1)
then
433 integer,
intent(in) :: y_local_index, x_prev, y_prev
434 type(local_grid_type),
intent(inout) :: local_grid
435 type(prognostic_field_type),
intent(inout) :: field
437 if (y_prev .ge. local_grid%local_domain_start_index(y_index))
then
438 where (field%data(:, y_prev, x_prev) < 0.0_default_precision)
439 field%data(:, y_prev, x_prev)=0.0_default_precision
442 if (y_local_index == local_grid%local_domain_end_index(y_index))
then
443 where (field%data(:, y_local_index, x_prev) < 0.0_default_precision)
444 field%data(:, y_local_index, x_prev)=0.0_default_precision
466 subroutine step_single_field(x_local_index, y_local_index, x_prev, y_prev, field, zfield, sfield, local_grid,&
467 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing, sav)
468 integer,
intent(in) :: x_local_index, y_local_index, x_prev, y_prev, direction
469 real(kind=default_precision),
intent(in) :: dtm, gal
470 logical,
intent(in) :: flow_field, do_timesmoothing
471 type(local_grid_type),
intent(inout) :: local_grid
472 type(prognostic_field_type),
intent(inout) :: field, zfield, sfield
473 real(kind=default_precision),
intent(in) :: c1, c2
474 type(prognostic_field_type),
optional,
intent(inout) :: sav
476 if (x_prev .ge. local_grid%local_domain_start_index(x_index))
then
477 if (
present(sav))
then
479 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing, sav)
482 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing)
486 if (x_local_index == local_grid%local_domain_end_index(x_index))
then
488 if (x_local_index .gt. 1)
then
489 if (
present(sav))
then
490 call step_column_in_slice(y_local_index, x_local_index-1, y_prev, field, zfield, sfield, local_grid, &
491 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing, sav)
493 call step_column_in_slice(y_local_index, x_local_index-1, y_prev, field, zfield, sfield, local_grid, &
494 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing)
497 if (
present(sav))
then
498 call step_column_in_slice(y_local_index, x_local_index, y_prev, field, zfield, sfield, local_grid, &
499 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing, sav)
501 call step_column_in_slice(y_local_index, x_local_index, y_prev, field, zfield, sfield, local_grid, &
502 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing)
516 type(prognostic_field_type),
intent(inout) :: field, zfield
517 type(local_grid_type),
intent(inout) :: local_grid
518 integer,
intent(in) :: x_index, y_index
519 real(kind=default_precision),
intent(in) :: c1, c2
523 do k=1,local_grid%size(z_index)
524 field%data(k, y_index, x_index)=c1*field%data(k, y_index, x_index)+c2*zfield%data(k, y_index, x_index)
547 flow_field, direction, dtm, gal, c1, c2, do_timesmoothing, sav)
548 integer,
intent(in) :: y_local_index, x_prev, y_prev, direction
549 real(kind=default_precision),
intent(in) :: dtm, gal
550 logical,
intent(in) :: flow_field, do_timesmoothing
551 type(local_grid_type),
intent(inout) :: local_grid
552 type(prognostic_field_type),
intent(inout) :: field, zfield, sfield
553 real(kind=default_precision),
intent(in) :: c1, c2
554 type(prognostic_field_type),
optional,
intent(inout) :: sav
556 if (y_prev .ge. local_grid%local_domain_start_index(y_index))
then
557 if (do_timesmoothing)
then
560 if (
present(sav))
then
561 call step_field(x_prev, y_prev, field, zfield, sfield, local_grid, flow_field, direction, dtm, gal, sav)
563 call step_field(x_prev, y_prev, field, zfield, sfield, local_grid, flow_field, direction, dtm, gal)
567 if (y_local_index == local_grid%local_domain_end_index(y_index))
then
568 if (do_timesmoothing)
then
571 if (
present(sav))
then
572 call step_field(x_prev, y_local_index, field, zfield, sfield, local_grid, flow_field, direction, dtm, gal, sav)
574 call step_field(x_prev, y_local_index, field, zfield, sfield, local_grid, flow_field, direction, dtm, gal)
590 subroutine step_field(x_local_index, y_local_index, field, zfield, sfield, local_grid, flow_field, direction, dtm, gal, sav)
591 integer,
intent(in) :: x_local_index, y_local_index, direction
592 real(kind=default_precision),
intent(in) :: dtm, gal
593 logical,
intent(in) :: flow_field
594 type(local_grid_type),
intent(inout) :: local_grid
595 type(prognostic_field_type),
intent(inout) :: field, zfield, sfield
596 type(prognostic_field_type),
optional,
intent(inout) :: sav
599 real(kind=default_precision) :: actual_gal, dtm_x2
601 dtm_x2 = 2.0_default_precision * dtm
603 actual_gal = merge(gal, real(0.0_default_precision, kind=default_precision), flow_field)
605 sfield%data(1,y_local_index, x_local_index)=0.0_default_precision
607 do k=1,local_grid%size(z_index)
609 if (
present(sav) .and. direction .eq. centred_stepping) &
610 sav%data(k,y_local_index, x_local_index) = zfield%data(k, y_local_index, x_local_index) + actual_gal
611 if (flow_field) field%data(k, y_local_index, x_local_index) = actual_gal + field%data(k, y_local_index, x_local_index)
612 if (direction == forward_stepping)
then
613 zfield%data(k, y_local_index, x_local_index) = field%data(k, y_local_index, x_local_index) + dtm * &
614 sfield%data(k, y_local_index, x_local_index)
616 zfield%data(k, y_local_index, x_local_index) = actual_gal+zfield%data(k, y_local_index, x_local_index)+dtm_x2*&
617 sfield%data(k, y_local_index, x_local_index)
629 type(model_state_type),
target,
intent(inout) :: current_state
630 integer,
intent(in) :: cxn, cyn, txn, tyn
634 tend_3d_th(:,tyn,txn)=current_state%sth%data(:,cyn,cxn)
656 current_state%sth%data(:,cyn,cxn) * current_state%global_grid%configuration%vertical%rprefrcp(:)
694 type(model_state_type),
target,
intent(inout) :: current_state
695 character(len=*),
intent(in) :: name
696 type(component_field_information_type),
intent(out) :: field_information
700 strcomp=index(name,
"_total_3d_local")
701 if (strcomp .ne. 0)
then
702 field_information%field_type=component_array_field_type
703 field_information%number_dimensions=3
704 field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
705 field_information%dimension_sizes(2)=current_state%local_grid%size(y_index)
706 field_information%dimension_sizes(3)=current_state%local_grid%size(x_index)
707 field_information%data_type=component_double_data_type
709 if (name .eq.
"tend_th_total_3d_local")
then
711 else if (name .eq.
"tend_qv_total_3d_local")
then
713 else if (name .eq.
"tend_ql_total_3d_local")
then
715 else if (name .eq.
"tend_qi_total_3d_local")
then
717 else if (name .eq.
"tend_qr_total_3d_local")
then
719 else if (name .eq.
"tend_qs_total_3d_local")
then
721 else if (name .eq.
"tend_qg_total_3d_local")
then
723 else if (name .eq.
"tend_tabs_total_3d_local")
then
726 field_information%enabled=.true.
732 strcomp=index(name,
"_total_profile_total_local")
733 if (strcomp .ne. 0)
then
734 field_information%field_type=component_array_field_type
735 field_information%number_dimensions=1
736 field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
737 field_information%data_type=component_double_data_type
739 if (name .eq.
"tend_th_total_profile_total_local")
then
741 else if (name .eq.
"tend_qv_total_profile_total_local")
then
743 else if (name .eq.
"tend_ql_total_profile_total_local")
then
745 else if (name .eq.
"tend_qi_total_profile_total_local")
then
747 else if (name .eq.
"tend_qr_total_profile_total_local")
then
749 else if (name .eq.
"tend_qs_total_profile_total_local")
then
751 else if (name .eq.
"tend_qg_total_profile_total_local")
then
753 else if (name .eq.
"tend_tabs_total_profile_total_local")
then
756 field_information%enabled=.true.
769 type(model_state_type),
target,
intent(inout) :: current_state
770 character(len=*),
intent(in) :: name
771 type(component_field_value_type),
intent(out) :: field_value
774 if (name .eq.
"tend_th_total_3d_local" .and.
allocated(
tend_3d_th))
then
776 else if (name .eq.
"tend_qv_total_3d_local" .and.
allocated(
tend_3d_qv))
then
778 else if (name .eq.
"tend_ql_total_3d_local" .and.
allocated(
tend_3d_ql))
then
780 else if (name .eq.
"tend_qi_total_3d_local" .and.
allocated(
tend_3d_qi))
then
782 else if (name .eq.
"tend_qr_total_3d_local" .and.
allocated(
tend_3d_qr))
then
784 else if (name .eq.
"tend_qs_total_3d_local" .and.
allocated(
tend_3d_qs))
then
786 else if (name .eq.
"tend_qg_total_3d_local" .and.
allocated(
tend_3d_qg))
then
788 else if (name .eq.
"tend_tabs_total_3d_local" .and.
allocated(
tend_3d_tabs))
then
792 else if (name .eq.
"tend_th_total_profile_total_local" .and.
allocated(
tend_pr_tot_th))
then
794 else if (name .eq.
"tend_qv_total_profile_total_local" .and.
allocated(
tend_pr_tot_qv))
then
796 else if (name .eq.
"tend_ql_total_profile_total_local" .and.
allocated(
tend_pr_tot_ql))
then
798 else if (name .eq.
"tend_qi_total_profile_total_local" .and.
allocated(
tend_pr_tot_qi))
then
800 else if (name .eq.
"tend_qr_total_profile_total_local" .and.
allocated(
tend_pr_tot_qr))
then
802 else if (name .eq.
"tend_qs_total_profile_total_local" .and.
allocated(
tend_pr_tot_qs))
then
804 else if (name .eq.
"tend_qg_total_profile_total_local" .and.
allocated(
tend_pr_tot_qg))
then
806 else if (name .eq.
"tend_tabs_total_profile_total_local" .and.
allocated(
tend_pr_tot_tabs))
then
818 type(component_field_value_type),
intent(inout) :: field_value
819 real(kind=default_precision),
dimension(:),
optional :: real_1d_field
820 real(kind=default_precision),
dimension(:,:),
optional :: real_2d_field
821 real(kind=default_precision),
dimension(:,:,:),
optional :: real_3d_field
823 if (
present(real_1d_field))
then
824 allocate(field_value%real_1d_array(
size(real_1d_field)), source=real_1d_field)
825 else if (
present(real_2d_field))
then
826 allocate(field_value%real_2d_array(
size(real_2d_field, 1),
size(real_2d_field, 2)), source=real_2d_field)
827 else if (
present(real_3d_field))
then
828 allocate(field_value%real_3d_array(
size(real_3d_field, 1),
size(real_3d_field, 2),
size(real_3d_field, 3)), &
829 source=real_3d_field)