MONC
Functions/Subroutines | Variables
tvdadvection_mod Module Reference

Implements TVD advection for prognostic fields. More...

Functions/Subroutines

type(component_descriptor_type) function, public tvdadvection_get_descriptor ()
 Provides a description of this component for the core to register. More...
 
subroutine field_information_retrieval_callback (current_state, name, field_information)
 Field information retrieval callback, this returns information for a specific components published field. More...
 
subroutine field_value_retrieval_callback (current_state, name, field_value)
 Field value retrieval callback, this returns the value of a specific published field. More...
 
subroutine initialisation_callback (current_state)
 Sets up the stencil_mod (used in interpolation) and allocates data for the flux fields. More...
 
subroutine finalisation_callback (current_state)
 Frees up the memory associated with the advection. More...
 
subroutine timestep_callback (current_state)
 Timestep callback hook which performs the TVD advection for each prognostic field. More...
 
subroutine advect_flow_fields (current_state)
 Will advect the flow fields. More...
 
subroutine advect_q_fields (current_state)
 Advects the Q fields. More...
 
subroutine advect_theta (current_state)
 Advects the theta field if it is active. More...
 
subroutine advect_scalar_field (y_local_index, x_local_index, dt, u, v, w, z_q_field, q_field, source_field, global_grid, local_grid, parallel, halo_column, field_stepping)
 Advects a single scalar field. More...
 
subroutine advect_u (y_local_index, x_local_index, dt, u, v, w, zf, su, global_grid, local_grid, parallel, halo_column, field_stepping)
 Advects the U flow field. More...
 
subroutine advect_v (y_local_index, x_local_index, dt, u, v, w, zf, sv, global_grid, local_grid, parallel, halo_column, field_stepping)
 Advects the V flow field. More...
 
subroutine advect_w (y_local_index, x_local_index, dt, u, v, w, zf, sw, global_grid, local_grid, parallel, halo_column, field_stepping)
 Advects the W flow field. More...
 
subroutine differentiate_face_values (y_flow_index, x_flow_index, u, v, w, y_source_index, x_source_index, source_field, local_grid, global_grid, flux_y_previous, flux_x_previous, tzc1, tzc2, differentiate_top)
 Differentiates face values to update the source field. More...
 
subroutine complete_y_flux_wrap_send_if_required (y_local_index, field, parallel, local_grid)
 Completes the Y flux MPI asynchronous send if required. More...
 
subroutine register_y_flux_wrap_send_if_required (y_local_index, field, parallel, local_grid)
 Registers an asynchronous send for the Y flux if required. More...
 
subroutine complete_y_flux_wrap_recv_if_required (y_local_index, field, parallel, local_grid)
 Completes the Y flux MPI asynchronous recieve if required. If the wrap around process is the same (one process in the y dimension) then just issues a local copy. More...
 
subroutine register_y_flux_wrap_recv_if_required (y_local_index, field, parallel, local_grid)
 Registers an MPI asynchronous receive for the flux if required. More...
 
subroutine save_precomponent_tendencies (current_state, cxn, cyn, txn, tyn)
 Save the 3d tendencies coming into the component. More...
 
subroutine compute_component_tendencies (current_state, cxn, cyn, txn, tyn)
 Computation of component tendencies. More...
 
subroutine set_published_field_value (field_value, real_1d_field, real_2d_field, real_3d_field)
 Sets the published field value from the temporary diagnostic values held by. More...
 
logical function determine_if_advection_here (field)
 Parses a field string (read in from the configuration file) and determines whether this algorithm should be used for advecting that field. More...
 

Variables

type(grid_stencil_type), save star_stencil
 
integer, save u_index =0
 
integer, save v_index =0
 
integer, save w_index =0
 
logical advect_flow
 
logical advect_th
 
logical advect_q
 
real(kind=default_precision), dimension(:), allocatable flux_x
 
real(kind=default_precision), dimension(:), allocatable flux_y
 
real(kind=default_precision), dimension(:), allocatable flux_z
 
real(kind=default_precision), dimension(:), allocatable u_advection
 
real(kind=default_precision), dimension(:), allocatable v_advection
 
real(kind=default_precision), dimension(:), allocatable w_advection
 
real(kind=default_precision), dimension(:), allocatable th_advection
 
real(kind=default_precision), dimension(:,:), allocatable q_advection
 
type(prognostic_field_type), dimension(:), allocatable interpolated_fields
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_u
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_v
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_w
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_th
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_qv
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_ql
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_qi
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_qr
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_qs
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_qg
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_tabs
 
logical l_tend_3d_u
 
logical l_tend_3d_v
 
logical l_tend_3d_w
 
logical l_tend_3d_th
 
logical l_tend_3d_qv
 
logical l_tend_3d_ql
 
logical l_tend_3d_qi
 
logical l_tend_3d_qr
 
logical l_tend_3d_qs
 
logical l_tend_3d_qg
 
logical l_tend_3d_tabs
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_u
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_v
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_w
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_th
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_qv
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_ql
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_qi
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_qr
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_qs
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_qg
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_tabs
 
logical l_tend_pr_tot_u
 
logical l_tend_pr_tot_v
 
logical l_tend_pr_tot_w
 
logical l_tend_pr_tot_th
 
logical l_tend_pr_tot_qv
 
logical l_tend_pr_tot_ql
 
logical l_tend_pr_tot_qi
 
logical l_tend_pr_tot_qr
 
logical l_tend_pr_tot_qs
 
logical l_tend_pr_tot_qg
 
logical l_tend_pr_tot_tabs
 
integer iqv =0
 
integer iql =0
 
integer iqr =0
 
integer iqi =0
 
integer iqs =0
 
integer iqg =0
 
integer diagnostic_generation_frequency
 

Detailed Description

Implements TVD advection for prognostic fields.

Function/Subroutine Documentation

◆ advect_flow_fields()

subroutine tvdadvection_mod::advect_flow_fields ( type(model_state_type), intent(inout)  current_state)
private

Will advect the flow fields.

Parameters
current_stateThe current model state_mod

Definition at line 586 of file tvdadvection.F90.

587  type(model_state_type), intent(inout) :: current_state
588 
589  real(kind=default_precision) :: dtm
590 
591  dtm = current_state%dtm*2.0_default_precision
592  if (current_state%momentum_stepping == forward_stepping) dtm=current_state%dtm
593 
594 #ifdef U_ACTIVE
595  call advect_u(current_state%column_local_y, current_state%column_local_x, dtm, current_state%u, &
596  current_state%v, current_state%w, current_state%zu, current_state%su, current_state%global_grid, &
597  current_state%local_grid, current_state%parallel, current_state%halo_column, current_state%field_stepping)
598  if (is_component_enabled(current_state%options_database, "profile_diagnostics")) then
599  ! NOTE: flux_z is declared at the top of module and then passed into ultflx, through argument
600  ! list in advect_scalar_field.
601  tvd_dgs_terms%adv_u_dgs(:, current_state%column_local_y, current_state%column_local_x) = &
602  flux_z(:)
603  endif
604 #endif
605 
606 #ifdef V_ACTIVE
607  call advect_v(current_state%column_local_y, current_state%column_local_x, dtm, current_state%u, &
608  current_state%v, current_state%w, current_state%zv, current_state%sv, current_state%global_grid, &
609  current_state%local_grid, current_state%parallel, current_state%halo_column, current_state%field_stepping)
610  if (is_component_enabled(current_state%options_database, "profile_diagnostics")) then
611  ! NOTE: flux_z is declared at the top of module and then passed into ultflx, through argument
612  ! list in advect_scalar_field.
613  tvd_dgs_terms%adv_v_dgs(:, current_state%column_local_y, current_state%column_local_x) = &
614  flux_z(:)
615  endif
616 #endif
617 
618 #ifdef W_ACTIVE
619  call advect_w(current_state%column_local_y, current_state%column_local_x, dtm, current_state%u, &
620  current_state%v, current_state%w, current_state%zw, current_state%sw, current_state%global_grid,&
621  current_state%local_grid, current_state%parallel, current_state%halo_column, current_state%field_stepping)
622  if (is_component_enabled(current_state%options_database, "profile_diagnostics")) then
623  ! NOTE: flux_z is declared at the top of module and then passed into ultflx, through argument
624  ! list in advect_scalar_field.
625  tvd_dgs_terms%adv_w_dgs(:, current_state%column_local_y, current_state%column_local_x) = &
626  flux_z(:)
627  endif
628 #endif
Here is the call graph for this function:
Here is the caller graph for this function:

◆ advect_q_fields()

subroutine tvdadvection_mod::advect_q_fields ( type(model_state_type), intent(inout)  current_state)
private

Advects the Q fields.

Parameters
current_stateThe current model state_mod

Definition at line 633 of file tvdadvection.F90.

634  type(model_state_type), intent(inout) :: current_state
635 
636  integer :: i
637  real(kind=default_precision) :: dtm
638 
639  dtm = current_state%dtm*2.0_default_precision
640  if (current_state%scalar_stepping == forward_stepping) dtm=current_state%dtm
641 
642  do i=1,current_state%number_q_fields
643  if (current_state%q(i)%active) then
644  call advect_scalar_field(current_state%column_local_y, current_state%column_local_x, dtm, current_state%u, &
645  current_state%v, current_state%w, current_state%zq(i), current_state%q(i), current_state%sq(i), &
646  current_state%global_grid, current_state%local_grid, current_state%parallel, &
647  current_state%halo_column, current_state%field_stepping)
648  q_advection(:,i)=current_state%sq(i)%data(:, current_state%column_local_y, current_state%column_local_x)
649  if (is_component_enabled(current_state%options_database, "profile_diagnostics")) then
650  ! NOTE: flux_z is declared at the top of module and then passed into ultflx, through argument
651  ! list in advect_scalar_field.
652  tvd_dgs_terms%adv_q_dgs(:, current_state%column_local_y, current_state%column_local_x, i) = &
653  flux_z(:)
654  endif
655 
656  end if
657  end do
Here is the call graph for this function:
Here is the caller graph for this function:

◆ advect_scalar_field()

subroutine tvdadvection_mod::advect_scalar_field ( integer, intent(in)  y_local_index,
integer, intent(in)  x_local_index,
real(kind=default_precision), intent(in)  dt,
type(prognostic_field_type), intent(inout)  u,
type(prognostic_field_type), intent(inout)  v,
type(prognostic_field_type), intent(inout)  w,
type(prognostic_field_type), intent(inout)  z_q_field,
type(prognostic_field_type), intent(inout)  q_field,
type(prognostic_field_type), intent(inout)  source_field,
type(global_grid_type), intent(inout)  global_grid,
type(local_grid_type), intent(inout)  local_grid,
type(parallel_state_type), intent(inout)  parallel,
logical, intent(in)  halo_column,
integer, intent(in)  field_stepping 
)
private

Advects a single scalar field.

Definition at line 685 of file tvdadvection.F90.

687 
688  integer, intent(in) ::y_local_index, x_local_index, field_stepping
689  real(kind=default_precision), intent(in) ::dt ! timestep (s)
690  logical, intent(in) :: halo_column
691  type(prognostic_field_type), intent(inout) :: u, w, v, z_q_field, q_field, source_field
692  type(global_grid_type), intent(inout) :: global_grid
693  type(local_grid_type), intent(inout) :: local_grid
694  type(parallel_state_type), intent(inout) :: parallel
695 
696  if (.not. allocated(q_field%flux_previous_x)) allocate(q_field%flux_previous_x(local_grid%size(z_index), &
697  local_grid%size(y_index)+4))
698  if (.not. allocated(q_field%flux_previous_y)) allocate(q_field%flux_previous_y(local_grid%size(z_index)))
699 
700  call register_y_flux_wrap_recv_if_required(y_local_index, q_field, parallel, local_grid)
701 
702  if (field_stepping == forward_stepping) then
703  call ultflx(y_local_index, x_local_index, u, v, w, y_local_index, x_local_index, q_field, local_grid, &
704  global_grid%configuration, parallel, 0, dt, &
705  flux_y, flux_z, flux_x, q_field%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdz,&
706  global_grid%configuration%vertical%rdzn, global_grid%configuration%vertical%dzn, 2, local_grid%size(z_index))
707  else
708  call ultflx(y_local_index, x_local_index, u, v, w, y_local_index, x_local_index, z_q_field, local_grid, &
709  global_grid%configuration, parallel, 0, dt, &
710  flux_y, flux_z, flux_x, q_field%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdz,&
711  global_grid%configuration%vertical%rdzn, global_grid%configuration%vertical%dzn, 2, local_grid%size(z_index))
712  end if
713 
714  call complete_y_flux_wrap_recv_if_required(y_local_index, q_field, parallel, local_grid)
715 
716  if (.not. halo_column) then
717  call differentiate_face_values(y_local_index, x_local_index, u, v, w, y_local_index, x_local_index, source_field, &
718  local_grid, global_grid, q_field%flux_previous_y, q_field%flux_previous_x(:,y_local_index), &
719  global_grid%configuration%vertical%tzc1, global_grid%configuration%vertical%tzc2, .true.)
720  end if
721 
722  if (y_local_index .lt. local_grid%local_domain_end_index(y_index)) q_field%flux_previous_y(:) = flux_y(:)
723  call register_y_flux_wrap_send_if_required(y_local_index, q_field, parallel, local_grid)
724  call complete_y_flux_wrap_send_if_required(y_local_index, q_field, parallel, local_grid)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ advect_theta()

subroutine tvdadvection_mod::advect_theta ( type(model_state_type), intent(inout)  current_state)
private

Advects the theta field if it is active.

Parameters
current_stateThe current model state_mod

Definition at line 662 of file tvdadvection.F90.

663  type(model_state_type), intent(inout) :: current_state
664 
665  real(kind=default_precision) :: dtm
666 
667  dtm = current_state%dtm*2.0_default_precision
668  if (current_state%scalar_stepping == forward_stepping) dtm=current_state%dtm
669 
670  if (current_state%th%active) then
671  call advect_scalar_field(current_state%column_local_y, current_state%column_local_x, dtm, current_state%u,&
672  current_state%v, current_state%w, current_state%zth, current_state%th, current_state%sth, current_state%global_grid,&
673  current_state%local_grid, current_state%parallel, current_state%halo_column, current_state%field_stepping)
674  th_advection=current_state%sth%data(:, current_state%column_local_y, current_state%column_local_x)
675  if (is_component_enabled(current_state%options_database, "profile_diagnostics")) then
676  ! NOTE: flux_z is declared at the top of module and then passed into ultflx, through argument
677  ! list in advect_scalar_field.
678  tvd_dgs_terms%adv_th_dgs(:, current_state%column_local_y, current_state%column_local_x) = &
679  flux_z(:)
680  endif
681  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ advect_u()

subroutine tvdadvection_mod::advect_u ( integer, intent(in)  y_local_index,
integer, intent(in)  x_local_index,
real(kind=default_precision), intent(in)  dt,
type(prognostic_field_type), intent(inout)  u,
type(prognostic_field_type), intent(inout)  v,
type(prognostic_field_type), intent(inout)  w,
type(prognostic_field_type), intent(inout)  zf,
type(prognostic_field_type), intent(inout)  su,
type(global_grid_type), intent(inout)  global_grid,
type(local_grid_type), intent(inout)  local_grid,
type(parallel_state_type), intent(inout)  parallel,
logical, intent(in)  halo_column,
integer, intent(in)  field_stepping 
)
private

Advects the U flow field.

Definition at line 728 of file tvdadvection.F90.

730 
731  integer, intent(in) :: y_local_index, x_local_index, field_stepping
732  real(kind=default_precision), intent(in) ::dt ! timestep (s)
733  logical, intent(in) :: halo_column
734  type(prognostic_field_type), intent(inout) :: u, w, v, zf, su
735  type(global_grid_type), intent(inout) :: global_grid
736  type(local_grid_type), intent(inout) :: local_grid
737  type(parallel_state_type), intent(inout) :: parallel
738 
739  if (.not. allocated(u%flux_previous_x)) allocate(u%flux_previous_x(local_grid%size(z_index), local_grid%size(y_index)+4))
740  if (.not. allocated(u%flux_previous_y)) allocate(u%flux_previous_y(local_grid%size(z_index)))
741 
742  call register_y_flux_wrap_recv_if_required(y_local_index, u, parallel, local_grid)
743 
744  call interpolate_to_dual(local_grid, u, star_stencil, x_local_index, y_local_index, interpolated_fields, u_index)
745 
746  if (field_stepping == forward_stepping) then
747  call ultflx(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
748  interpolated_fields(w_index), y_local_index, x_local_index, u, local_grid, global_grid%configuration, parallel, 0, &
749  dt, flux_y, flux_z, flux_x, &
750  u%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdz, &
751  global_grid%configuration%vertical%rdzn, global_grid%configuration%vertical%dzn, 2, local_grid%size(z_index))
752  else
753  ! Centred stepping
754  call ultflx(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
755  interpolated_fields(w_index), y_local_index, x_local_index, zf, local_grid, global_grid%configuration, parallel, 0, &
756  dt, flux_y, flux_z, flux_x, &
757  u%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdz, &
758  global_grid%configuration%vertical%rdzn, global_grid%configuration%vertical%dzn, 2, local_grid%size(z_index))
759  end if
760 
761  call complete_y_flux_wrap_recv_if_required(y_local_index, u, parallel, local_grid)
762 
763  if (.not. halo_column) then
764  call differentiate_face_values(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
765  interpolated_fields(w_index), y_local_index, x_local_index, su, local_grid, global_grid, &
766  u%flux_previous_y, u%flux_previous_x(:,y_local_index), &
767  global_grid%configuration%vertical%tzc1, global_grid%configuration%vertical%tzc2, .true.)
768  u_advection=su%data(:, y_local_index, x_local_index)
769  end if
770 
771  if (y_local_index .lt. local_grid%local_domain_end_index(y_index)) u%flux_previous_y(:) = flux_y(:)
772  call register_y_flux_wrap_send_if_required(y_local_index, u, parallel, local_grid)
773  call complete_y_flux_wrap_send_if_required(y_local_index, u, parallel, local_grid)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ advect_v()

subroutine tvdadvection_mod::advect_v ( integer, intent(in)  y_local_index,
integer, intent(in)  x_local_index,
real(kind=default_precision), intent(in)  dt,
type(prognostic_field_type), intent(inout)  u,
type(prognostic_field_type), intent(inout)  v,
type(prognostic_field_type), intent(inout)  w,
type(prognostic_field_type), intent(inout)  zf,
type(prognostic_field_type), intent(inout)  sv,
type(global_grid_type), intent(inout)  global_grid,
type(local_grid_type), intent(inout)  local_grid,
type(parallel_state_type), intent(inout)  parallel,
logical, intent(in)  halo_column,
integer, intent(in)  field_stepping 
)
private

Advects the V flow field.

Definition at line 777 of file tvdadvection.F90.

779 
780  integer, intent(in) ::y_local_index, x_local_index, field_stepping
781  real(kind=default_precision), intent(in) ::dt ! timestep (s)
782  logical, intent(in) :: halo_column
783  type(prognostic_field_type), intent(inout) :: u, w, v, zf, sv
784  type(global_grid_type), intent(inout) :: global_grid
785  type(local_grid_type), intent(inout) :: local_grid
786  type(parallel_state_type), intent(inout) :: parallel
787 
788  if (.not. allocated(v%flux_previous_x)) allocate(v%flux_previous_x(local_grid%size(z_index), local_grid%size(y_index)+4))
789  if (.not. allocated(v%flux_previous_y)) allocate(v%flux_previous_y(local_grid%size(z_index)))
790 
791  call register_y_flux_wrap_recv_if_required(y_local_index, v, parallel, local_grid)
792 
793  call interpolate_to_dual(local_grid, v, star_stencil, x_local_index, y_local_index, interpolated_fields, v_index)
794 
795  if (field_stepping == forward_stepping) then
796  call ultflx(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
797  interpolated_fields(w_index), y_local_index, x_local_index, v, local_grid, global_grid%configuration, parallel, 0, &
798  dt, flux_y, flux_z, flux_x, &
799  v%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdz, &
800  global_grid%configuration%vertical%rdzn, global_grid%configuration%vertical%dzn, 2, local_grid%size(z_index))
801  else
802  ! Centred stepping
803  call ultflx(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
804  interpolated_fields(w_index), y_local_index, x_local_index, zf, local_grid, global_grid%configuration, parallel, 0, &
805  dt, flux_y, flux_z, flux_x, &
806  v%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdz, &
807  global_grid%configuration%vertical%rdzn, global_grid%configuration%vertical%dzn, 2, local_grid%size(z_index))
808  end if
809 
810  call complete_y_flux_wrap_recv_if_required(y_local_index, v, parallel, local_grid)
811 
812  if (.not. halo_column) then
813  call differentiate_face_values(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
814  interpolated_fields(w_index), y_local_index, x_local_index, sv, local_grid, global_grid, &
815  v%flux_previous_y, v%flux_previous_x(:,y_local_index), &
816  global_grid%configuration%vertical%tzc1, global_grid%configuration%vertical%tzc2, .true.)
817  v_advection=sv%data(:, y_local_index, x_local_index)
818  end if
819 
820  if (y_local_index .lt. local_grid%local_domain_end_index(y_index)) v%flux_previous_y(:) = flux_y(:)
821  call register_y_flux_wrap_send_if_required(y_local_index, v, parallel, local_grid)
822  call complete_y_flux_wrap_send_if_required(y_local_index, v, parallel, local_grid)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ advect_w()

subroutine tvdadvection_mod::advect_w ( integer, intent(in)  y_local_index,
integer, intent(in)  x_local_index,
real(kind=default_precision), intent(in)  dt,
type(prognostic_field_type), intent(inout)  u,
type(prognostic_field_type), intent(inout)  v,
type(prognostic_field_type), intent(inout)  w,
type(prognostic_field_type), intent(inout)  zf,
type(prognostic_field_type), intent(inout)  sw,
type(global_grid_type), intent(inout)  global_grid,
type(local_grid_type), intent(inout)  local_grid,
type(parallel_state_type), intent(inout)  parallel,
logical, intent(in)  halo_column,
integer, intent(in)  field_stepping 
)
private

Advects the W flow field.

Definition at line 826 of file tvdadvection.F90.

828 
829  integer, intent(in) ::y_local_index, x_local_index, field_stepping
830  real(kind=default_precision), intent(in) ::dt ! timestep (s)
831  logical, intent(in) :: halo_column
832  type(prognostic_field_type), intent(inout) :: u, w, v, zf, sw
833  type(global_grid_type), intent(inout) :: global_grid
834  type(local_grid_type), intent(inout) :: local_grid
835  type(parallel_state_type), intent(inout) :: parallel
836 
837  if (.not. allocated(w%flux_previous_x)) allocate(w%flux_previous_x(local_grid%size(z_index), local_grid%size(y_index)+4))
838  if (.not. allocated(w%flux_previous_y)) allocate(w%flux_previous_y(local_grid%size(z_index)))
839 
840  call register_y_flux_wrap_recv_if_required(y_local_index, w, parallel, local_grid)
841 
842  call interpolate_to_dual(local_grid, w, star_stencil, x_local_index, y_local_index, interpolated_fields, w_index)
843 
844  if (field_stepping == forward_stepping) then
845  call ultflx(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
846  interpolated_fields(w_index), y_local_index, x_local_index, w, local_grid, global_grid%configuration, parallel, 1, &
847  dt, flux_y, flux_z, flux_x,&
848  w%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdzn, &
849  global_grid%configuration%vertical%rdz, global_grid%configuration%vertical%dz, 1, local_grid%size(z_index)-1)
850  else
851  ! Centred stepping
852  call ultflx(1, 1, interpolated_fields(u_index), interpolated_fields(v_index), &
853  interpolated_fields(w_index), y_local_index, x_local_index, zf, local_grid, global_grid%configuration, parallel, 1, &
854  dt, flux_y, flux_z, flux_x,&
855  w%flux_previous_x(:,y_local_index), global_grid%configuration%vertical%rdzn, &
856  global_grid%configuration%vertical%rdz, global_grid%configuration%vertical%dz, 1, local_grid%size(z_index)-1)
857  end if
858 
859  call complete_y_flux_wrap_recv_if_required(y_local_index, w, parallel, local_grid)
860 
861  if (.not. halo_column) then
862  call differentiate_face_values(1, 1, interpolated_fields(u_index), interpolated_fields(v_index),&
863  interpolated_fields(w_index), y_local_index, x_local_index, sw, local_grid, global_grid, &
864  w%flux_previous_y, w%flux_previous_x(:,y_local_index),&
865  global_grid%configuration%vertical%tzd1, global_grid%configuration%vertical%tzd2, .false.)
866  w_advection=sw%data(:, y_local_index, x_local_index)
867  end if
868  if (y_local_index .lt. local_grid%local_domain_end_index(y_index)) w%flux_previous_y(:) = flux_y(:)
869  call register_y_flux_wrap_send_if_required(y_local_index, w, parallel, local_grid)
870  call complete_y_flux_wrap_send_if_required(y_local_index, w, parallel, local_grid)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ complete_y_flux_wrap_recv_if_required()

subroutine tvdadvection_mod::complete_y_flux_wrap_recv_if_required ( integer, intent(in)  y_local_index,
type(prognostic_field_type), intent(inout)  field,
type(parallel_state_type), intent(inout)  parallel,
type(local_grid_type), intent(inout)  local_grid 
)
private

Completes the Y flux MPI asynchronous recieve if required. If the wrap around process is the same (one process in the y dimension) then just issues a local copy.

Parameters
y_local_indexThe local index in Y
fieldThe prognostic field
parallelParallel system description
local_gridThe local grid description

Definition at line 977 of file tvdadvection.F90.

978  integer, intent(in) :: y_local_index
979  type(prognostic_field_type), intent(inout) :: field
980  type(parallel_state_type), intent(inout) :: parallel
981  type(local_grid_type), intent(inout) :: local_grid
982 
983  integer :: ierr
984 
985  if (y_local_index == local_grid%local_domain_end_index(y_index) .and. parallel%my_coords(y_index) == &
986  parallel%dim_sizes(y_index)-1) then
987  if (field%async_flux_handle .ne. mpi_request_null) then
988  call mpi_wait(field%async_flux_handle, mpi_status_ignore, ierr)
989  end if
990  flux_y(:) = field%flux_y_buffer(:)
991  end if
Here is the caller graph for this function:

◆ complete_y_flux_wrap_send_if_required()

subroutine tvdadvection_mod::complete_y_flux_wrap_send_if_required ( integer, intent(in)  y_local_index,
type(prognostic_field_type), intent(inout)  field,
type(parallel_state_type), intent(inout)  parallel,
type(local_grid_type), intent(inout)  local_grid 
)
private

Completes the Y flux MPI asynchronous send if required.

Parameters
y_local_indexThe local index in Y
fieldThe prognostic field
parallelParallel system description
local_gridThe local grid description

Definition at line 930 of file tvdadvection.F90.

931  integer, intent(in) :: y_local_index
932  type(prognostic_field_type), intent(inout) :: field
933  type(parallel_state_type), intent(inout) :: parallel
934  type(local_grid_type), intent(inout) :: local_grid
935 
936  integer :: ierr
937 
938  if (y_local_index == local_grid%local_domain_end_index(y_index) .and. parallel%my_coords(y_index) == 0 .and. &
939  field%async_flux_handle .ne. mpi_request_null) then
940  call mpi_wait(field%async_flux_handle, mpi_status_ignore, ierr)
941  end if
Here is the caller graph for this function:

◆ compute_component_tendencies()

subroutine tvdadvection_mod::compute_component_tendencies ( type(model_state_type), intent(inout), target  current_state,
integer, intent(in)  cxn,
integer, intent(in)  cyn,
integer, intent(in)  txn,
integer, intent(in)  tyn 
)
private

Computation of component tendencies.

Parameters
current_stateCurrent model state
cxnThe current slice, x, index
cynThe current column, y, index.
txntarget_x_index
tyntarget_y_index

Definition at line 1075 of file tvdadvection.F90.

1076  type(model_state_type), target, intent(inout) :: current_state
1077  integer, intent(in) :: cxn, cyn, txn, tyn
1078 
1079  ! Calculate change in tendency due to component
1080  if (l_tend_3d_u) then
1081  tend_3d_u(:,tyn,txn)=current_state%su%data(:,cyn,cxn) - tend_3d_u(:,tyn,txn)
1082  endif
1083  if (l_tend_3d_v) then
1084  tend_3d_v(:,tyn,txn)=current_state%sv%data(:,cyn,cxn) - tend_3d_v(:,tyn,txn)
1085  endif
1086  if (l_tend_3d_w) then
1087  tend_3d_w(:,tyn,txn)=current_state%sw%data(:,cyn,cxn) - tend_3d_w(:,tyn,txn)
1088  endif
1089  if (l_tend_3d_th) then
1090  tend_3d_th(:,tyn,txn)=current_state%sth%data(:,cyn,cxn) - tend_3d_th(:,tyn,txn)
1091  endif
1092  if (l_tend_3d_qv) then
1093  tend_3d_qv(:,tyn,txn)=current_state%sq(iqv)%data(:,cyn,cxn) - tend_3d_qv(:,tyn,txn)
1094  endif
1095  if (l_tend_3d_ql) then
1096  tend_3d_ql(:,tyn,txn)=current_state%sq(iql)%data(:,cyn,cxn) - tend_3d_ql(:,tyn,txn)
1097  endif
1098  if (l_tend_3d_qi) then
1099  tend_3d_qi(:,tyn,txn)=current_state%sq(iqi)%data(:,cyn,cxn) - tend_3d_qi(:,tyn,txn)
1100  endif
1101  if (l_tend_3d_qr) then
1102  tend_3d_qr(:,tyn,txn)=current_state%sq(iqr)%data(:,cyn,cxn) - tend_3d_qr(:,tyn,txn)
1103  endif
1104  if (l_tend_3d_qs) then
1105  tend_3d_qs(:,tyn,txn)=current_state%sq(iqs)%data(:,cyn,cxn) - tend_3d_qs(:,tyn,txn)
1106  endif
1107  if (l_tend_3d_qg) then
1108  tend_3d_qg(:,tyn,txn)=current_state%sq(iqg)%data(:,cyn,cxn) - tend_3d_qg(:,tyn,txn)
1109  endif
1110  if (l_tend_3d_tabs) then
1111  tend_3d_tabs(:,tyn,txn)= &
1112  current_state%sth%data(:,cyn,cxn) * current_state%global_grid%configuration%vertical%rprefrcp(:) &
1113  - tend_3d_tabs(:,tyn,txn)
1114  endif
1115 
1116  ! Add local tendency fields to the profile total
1117  if (l_tend_pr_tot_u) then
1118  tend_pr_tot_u(:)=tend_pr_tot_u(:) + tend_3d_u(:,tyn,txn)
1119  endif
1120  if (l_tend_pr_tot_v) then
1121  tend_pr_tot_v(:)=tend_pr_tot_v(:) + tend_3d_v(:,tyn,txn)
1122  endif
1123  if (l_tend_pr_tot_w) then
1124  tend_pr_tot_w(:)=tend_pr_tot_w(:) + tend_3d_w(:,tyn,txn)
1125  endif
1126  if (l_tend_pr_tot_th) then
1127  tend_pr_tot_th(:)=tend_pr_tot_th(:) + tend_3d_th(:,tyn,txn)
1128  endif
1129  if (l_tend_pr_tot_qv) then
1130  tend_pr_tot_qv(:)=tend_pr_tot_qv(:) + tend_3d_qv(:,tyn,txn)
1131  endif
1132  if (l_tend_pr_tot_ql) then
1133  tend_pr_tot_ql(:)=tend_pr_tot_ql(:) + tend_3d_ql(:,tyn,txn)
1134  endif
1135  if (l_tend_pr_tot_qi) then
1136  tend_pr_tot_qi(:)=tend_pr_tot_qi(:) + tend_3d_qi(:,tyn,txn)
1137  endif
1138  if (l_tend_pr_tot_qr) then
1139  tend_pr_tot_qr(:)=tend_pr_tot_qr(:) + tend_3d_qr(:,tyn,txn)
1140  endif
1141  if (l_tend_pr_tot_qs) then
1142  tend_pr_tot_qs(:)=tend_pr_tot_qs(:) + tend_3d_qs(:,tyn,txn)
1143  endif
1144  if (l_tend_pr_tot_qg) then
1145  tend_pr_tot_qg(:)=tend_pr_tot_qg(:) + tend_3d_qg(:,tyn,txn)
1146  endif
1147  if (l_tend_pr_tot_tabs) then
1148  tend_pr_tot_tabs(:)=tend_pr_tot_tabs(:) + tend_3d_tabs(:,tyn,txn)
1149  endif
1150 
Here is the caller graph for this function:

◆ determine_if_advection_here()

logical function tvdadvection_mod::determine_if_advection_here ( character(len=*), intent(in)  field)
private

Parses a field string (read in from the configuration file) and determines whether this algorithm should be used for advecting that field.

Parameters
fieldThe string configuration of field advection
Returns
Whether or not the field is advected here

Definition at line 1181 of file tvdadvection.F90.

1182  character(len=*), intent(in) :: field
1183 
1184  if (len_trim(field) .ne. 0) then
1185  if (trim(field) .eq. "tvd" .or. trim(field) .eq. "any") then
1186  determine_if_advection_here=.true.
1187  else
1188  determine_if_advection_here=.false.
1189  end if
1190  else
1191  determine_if_advection_here=.true.
1192  end if
Here is the caller graph for this function:

◆ differentiate_face_values()

subroutine tvdadvection_mod::differentiate_face_values ( integer, intent(in)  y_flow_index,
integer, intent(in)  x_flow_index,
type(prognostic_field_type), intent(inout)  u,
type(prognostic_field_type), intent(inout)  v,
type(prognostic_field_type), intent(inout)  w,
integer, intent(in)  y_source_index,
integer, intent(in)  x_source_index,
type(prognostic_field_type), intent(inout)  source_field,
type(local_grid_type), intent(inout)  local_grid,
type(global_grid_type), intent(inout)  global_grid,
real(kind=default_precision), dimension(:), intent(in)  flux_y_previous,
real(kind=default_precision), dimension(:), intent(in)  flux_x_previous,
real(kind=default_precision), dimension(*), intent(in)  tzc1,
real(kind=default_precision), dimension(*), intent(in)  tzc2,
logical, intent(in)  differentiate_top 
)
private

Differentiates face values to update the source field.

Definition at line 874 of file tvdadvection.F90.

876 
877  integer, intent(in) :: y_flow_index, x_flow_index, y_source_index, x_source_index
878  logical, intent(in) :: differentiate_top
879  real(kind=default_precision), intent(in), dimension(*) :: tzc1, tzc2
880  type(prognostic_field_type), intent(inout) :: u, w, v
881  type(prognostic_field_type), intent(inout) :: source_field
882  type(global_grid_type), intent(inout) :: global_grid
883  type(local_grid_type), intent(inout) :: local_grid
884  real(kind=default_precision), intent(in), dimension(:) :: flux_y_previous, flux_x_previous
885 
886  integer :: k
887 
888  do k=2,local_grid%size(z_index)-1
889 #ifdef V_ACTIVE
890  source_field%data(k, y_source_index, x_source_index)=source_field%data(k, y_source_index, x_source_index)+&
891  (v%data(k, y_flow_index-1, x_flow_index)* flux_y_previous(k) - v%data(k, y_flow_index, x_flow_index)*flux_y(k))*&
892  global_grid%configuration%horizontal%cy
893 #endif
894 #ifdef W_ACTIVE
895  source_field%data(k, y_source_index, x_source_index)=source_field%data(k, y_source_index, x_source_index)+&
896  4.0_default_precision*(w%data(k-1, y_flow_index, x_flow_index)* flux_z(k)*tzc1(k) - &
897  w%data(k, y_flow_index, x_flow_index)*flux_z(k+1)*tzc2(k))
898 #endif
899 #ifdef U_ACTIVE
900  source_field%data(k, y_source_index, x_source_index)=source_field%data(k, y_source_index, x_source_index)+&
901  (u%data(k, y_flow_index, x_flow_index-1)* flux_x(k) - u%data(k, y_flow_index, x_flow_index)*flux_x_previous(k))*&
902  global_grid%configuration%horizontal%cx
903 #endif
904  end do
905  if (differentiate_top) then
906  k=local_grid%size(z_index)
907  source_field%data(k, y_source_index, x_source_index)=0.0_default_precision
908 #ifdef V_ACTIVE
909  source_field%data(k, y_source_index, x_source_index)=source_field%data(k, y_source_index, x_source_index)+&
910  (v%data(k, y_flow_index-1, x_flow_index)* flux_y_previous(k) - v%data(k, y_flow_index, x_flow_index)*flux_y(k))*&
911  global_grid%configuration%horizontal%cy
912 #endif
913 #ifdef W_ACTIVE
914  source_field%data(k, y_source_index, x_source_index)=source_field%data(k, y_source_index, x_source_index)+&
915  4.0_default_precision*tzc1(k)* w%data(k-1, y_flow_index, x_flow_index)*flux_z(k)
916 #endif
917 #ifdef U_ACTIVE
918  source_field%data(k, y_source_index, x_source_index)=source_field%data(k, y_source_index, x_source_index)+&
919  (u%data(k, y_flow_index, x_flow_index-1)* flux_x(k) -u%data(k, y_flow_index, x_flow_index)*flux_x_previous(k))*&
920  global_grid%configuration%horizontal%cx
921 #endif
922  end if
Here is the caller graph for this function:

◆ field_information_retrieval_callback()

subroutine tvdadvection_mod::field_information_retrieval_callback ( type(model_state_type), intent(inout), target  current_state,
character(len=*), intent(in)  name,
type(component_field_information_type), intent(out)  field_information 
)
private

Field information retrieval callback, this returns information for a specific components published field.

Parameters
current_stateCurrent model state
nameThe name of the field to retrieve information for
field_informationPopulated with information about the field

Definition at line 108 of file tvdadvection.F90.

109  type(model_state_type), target, intent(inout) :: current_state
110  character(len=*), intent(in) :: name
111  type(component_field_information_type), intent(out) :: field_information
112  integer :: strcomp
113 
114  ! Field description is the same regardless of the specific field being retrieved
115  field_information%field_type=component_array_field_type
116  field_information%data_type=component_double_data_type
117  if (name .eq. "q_advection") then
118  field_information%number_dimensions=2
119  else
120  field_information%number_dimensions=1
121  end if
122  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
123  if (name .eq. "q_advection") field_information%dimension_sizes(2)=current_state%number_q_fields
124  field_information%enabled=.true.
125 
126  ! Field information for 3d
127  strcomp=index(name, "tvdadvection_3d_local")
128  if (strcomp .ne. 0) then
129  field_information%field_type=component_array_field_type
130  field_information%number_dimensions=3
131  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
132  field_information%dimension_sizes(2)=current_state%local_grid%size(y_index)
133  field_information%dimension_sizes(3)=current_state%local_grid%size(x_index)
134  field_information%data_type=component_double_data_type
135 
136  if (name .eq. "tend_u_tvdadvection_3d_local") then
137  field_information%enabled=l_tend_3d_u
138  else if (name .eq. "tend_v_tvdadvection_3d_local") then
139  field_information%enabled=l_tend_3d_v
140  else if (name .eq. "tend_w_tvdadvection_3d_local") then
141  field_information%enabled=l_tend_3d_w
142  else if (name .eq. "tend_th_tvdadvection_3d_local") then
143  field_information%enabled=l_tend_3d_th
144  else if (name .eq. "tend_qv_tvdadvection_3d_local") then
145  field_information%enabled=l_tend_3d_qv
146  else if (name .eq. "tend_ql_tvdadvection_3d_local") then
147  field_information%enabled=l_tend_3d_ql
148  else if (name .eq. "tend_qi_tvdadvection_3d_local") then
149  field_information%enabled=l_tend_3d_qi
150  else if (name .eq. "tend_qr_tvdadvection_3d_local") then
151  field_information%enabled=l_tend_3d_qr
152  else if (name .eq. "tend_qs_tvdadvection_3d_local") then
153  field_information%enabled=l_tend_3d_qs
154  else if (name .eq. "tend_qg_tvdadvection_3d_local") then
155  field_information%enabled=l_tend_3d_qg
156  else if (name .eq. "tend_tabs_tvdadvection_3d_local") then
157  field_information%enabled=l_tend_3d_tabs
158  else
159  field_information%enabled=.true.
160  end if
161 
162  end if !end 3d check
163 
164  ! Field information for profiles
165  strcomp=index(name, "tvdadvection_profile_total_local")
166  if (strcomp .ne. 0) then
167  field_information%field_type=component_array_field_type
168  field_information%number_dimensions=1
169  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
170  field_information%data_type=component_double_data_type
171 
172  if (name .eq. "tend_u_tvdadvection_profile_total_local") then
173  field_information%enabled=l_tend_pr_tot_u
174  else if (name .eq. "tend_v_tvdadvection_profile_total_local") then
175  field_information%enabled=l_tend_pr_tot_v
176  else if (name .eq. "tend_w_tvdadvection_profile_total_local") then
177  field_information%enabled=l_tend_pr_tot_w
178  else if (name .eq. "tend_th_tvdadvection_profile_total_local") then
179  field_information%enabled=l_tend_pr_tot_th
180  else if (name .eq. "tend_qv_tvdadvection_profile_total_local") then
181  field_information%enabled=l_tend_pr_tot_qv
182  else if (name .eq. "tend_ql_tvdadvection_profile_total_local") then
183  field_information%enabled=l_tend_pr_tot_ql
184  else if (name .eq. "tend_qi_tvdadvection_profile_total_local") then
185  field_information%enabled=l_tend_pr_tot_qi
186  else if (name .eq. "tend_qr_tvdadvection_profile_total_local") then
187  field_information%enabled=l_tend_pr_tot_qr
188  else if (name .eq. "tend_qs_tvdadvection_profile_total_local") then
189  field_information%enabled=l_tend_pr_tot_qs
190  else if (name .eq. "tend_qg_tvdadvection_profile_total_local") then
191  field_information%enabled=l_tend_pr_tot_qg
192  else if (name .eq. "tend_tabs_tvdadvection_profile_total_local") then
193  field_information%enabled=l_tend_pr_tot_tabs
194  else
195  field_information%enabled=.true.
196  end if
197 
198  end if !end profile check
199 
Here is the caller graph for this function:

◆ field_value_retrieval_callback()

subroutine tvdadvection_mod::field_value_retrieval_callback ( type(model_state_type), intent(inout), target  current_state,
character(len=*), intent(in)  name,
type(component_field_value_type), intent(out)  field_value 
)
private

Field value retrieval callback, this returns the value of a specific published field.

Parameters
current_stateCurrent model state
nameThe name of the field to retrieve the value for
field_valuePopulated with the value of the field

Definition at line 207 of file tvdadvection.F90.

208  type(model_state_type), target, intent(inout) :: current_state
209  character(len=*), intent(in) :: name
210  type(component_field_value_type), intent(out) :: field_value
211 
212  if (name .eq. "u_advection") then
213  allocate(field_value%real_1d_array(size(u_advection)), source=u_advection)
214  else if (name .eq. "v_advection") then
215  allocate(field_value%real_1d_array(size(v_advection)), source=v_advection)
216  else if (name .eq. "w_advection") then
217  allocate(field_value%real_1d_array(size(w_advection)), source=w_advection)
218  else if (name .eq. "th_advection") then
219  allocate(field_value%real_1d_array(size(th_advection)), source=th_advection)
220  else if (name .eq. "q_advection") then
221  allocate(field_value%real_2d_array(size(q_advection, 1), size(q_advection, 2)), source=q_advection)
222  end if
223 
224  ! 3d Tendency Fields
225  if (name .eq. "tend_u_tvdadvection_3d_local" .and. allocated(tend_3d_u)) then
226  call set_published_field_value(field_value, real_3d_field=tend_3d_u)
227  else if (name .eq. "tend_v_tvdadvection_3d_local" .and. allocated(tend_3d_v)) then
228  call set_published_field_value(field_value, real_3d_field=tend_3d_v)
229  else if (name .eq. "tend_w_tvdadvection_3d_local" .and. allocated(tend_3d_w)) then
230  call set_published_field_value(field_value, real_3d_field=tend_3d_w)
231  else if (name .eq. "tend_th_tvdadvection_3d_local" .and. allocated(tend_3d_th)) then
232  call set_published_field_value(field_value, real_3d_field=tend_3d_th)
233  else if (name .eq. "tend_qv_tvdadvection_3d_local" .and. allocated(tend_3d_qv)) then
234  call set_published_field_value(field_value, real_3d_field=tend_3d_qv)
235  else if (name .eq. "tend_ql_tvdadvection_3d_local" .and. allocated(tend_3d_ql)) then
236  call set_published_field_value(field_value, real_3d_field=tend_3d_ql)
237  else if (name .eq. "tend_qi_tvdadvection_3d_local" .and. allocated(tend_3d_qi)) then
238  call set_published_field_value(field_value, real_3d_field=tend_3d_qi)
239  else if (name .eq. "tend_qr_tvdadvection_3d_local" .and. allocated(tend_3d_qr)) then
240  call set_published_field_value(field_value, real_3d_field=tend_3d_qr)
241  else if (name .eq. "tend_qs_tvdadvection_3d_local" .and. allocated(tend_3d_qs)) then
242  call set_published_field_value(field_value, real_3d_field=tend_3d_qs)
243  else if (name .eq. "tend_qg_tvdadvection_3d_local" .and. allocated(tend_3d_qg)) then
244  call set_published_field_value(field_value, real_3d_field=tend_3d_qg)
245  else if (name .eq. "tend_tabs_tvdadvection_3d_local" .and. allocated(tend_3d_tabs)) then
246  call set_published_field_value(field_value, real_3d_field=tend_3d_tabs)
247 
248  ! Profile Tendency Fields
249  else if (name .eq. "tend_u_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_u)) then
250  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_u)
251  else if (name .eq. "tend_v_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_v)) then
252  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_v)
253  else if (name .eq. "tend_w_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_w)) then
254  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_w)
255  else if (name .eq. "tend_th_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_th)) then
256  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_th)
257  else if (name .eq. "tend_qv_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_qv)) then
258  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_qv)
259  else if (name .eq. "tend_ql_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_ql)) then
260  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_ql)
261  else if (name .eq. "tend_qi_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_qi)) then
262  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_qi)
263  else if (name .eq. "tend_qr_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_qr)) then
264  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_qr)
265  else if (name .eq. "tend_qs_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_qs)) then
266  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_qs)
267  else if (name .eq. "tend_qg_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_qg)) then
268  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_qg)
269  else if (name .eq. "tend_tabs_tvdadvection_profile_total_local" .and. allocated(tend_pr_tot_tabs)) then
270  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_tabs)
271  end if
272 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ finalisation_callback()

subroutine tvdadvection_mod::finalisation_callback ( type(model_state_type), intent(inout), target  current_state)
private

Frees up the memory associated with the advection.

Parameters
current_stateThe current model state

Definition at line 472 of file tvdadvection.F90.

473  type(model_state_type), target, intent(inout) :: current_state
474 
475  call free_stencil(star_stencil)
476  if (allocated(flux_x)) deallocate(flux_x)
477  if (allocated(flux_y)) deallocate(flux_y)
478  if (allocated(flux_z)) deallocate(flux_z)
479  if (allocated(interpolated_fields)) deallocate(interpolated_fields)
480  if (allocated(u_advection)) deallocate(u_advection)
481  if (allocated(v_advection)) deallocate(v_advection)
482  if (allocated(w_advection)) deallocate(w_advection)
483  if (allocated(th_advection)) deallocate(th_advection)
484  if (allocated(q_advection)) deallocate(q_advection)
485 
486  if (allocated(tend_3d_u)) deallocate(tend_3d_u)
487  if (allocated(tend_3d_v)) deallocate(tend_3d_v)
488  if (allocated(tend_3d_w)) deallocate(tend_3d_w)
489  if (allocated(tend_3d_th)) deallocate(tend_3d_th)
490  if (allocated(tend_3d_qv)) deallocate(tend_3d_qv)
491  if (allocated(tend_3d_ql)) deallocate(tend_3d_ql)
492  if (allocated(tend_3d_qi)) deallocate(tend_3d_qi)
493  if (allocated(tend_3d_qr)) deallocate(tend_3d_qr)
494  if (allocated(tend_3d_qs)) deallocate(tend_3d_qs)
495  if (allocated(tend_3d_qg)) deallocate(tend_3d_qg)
496  if (allocated(tend_3d_tabs)) deallocate(tend_3d_tabs)
497 
498  if (allocated(tend_pr_tot_u)) deallocate(tend_pr_tot_u)
499  if (allocated(tend_pr_tot_v)) deallocate(tend_pr_tot_v)
500  if (allocated(tend_pr_tot_w)) deallocate(tend_pr_tot_w)
501  if (allocated(tend_pr_tot_th)) deallocate(tend_pr_tot_th)
502  if (allocated(tend_pr_tot_qv)) deallocate(tend_pr_tot_qv)
503  if (allocated(tend_pr_tot_ql)) deallocate(tend_pr_tot_ql)
504  if (allocated(tend_pr_tot_qi)) deallocate(tend_pr_tot_qi)
505  if (allocated(tend_pr_tot_qr)) deallocate(tend_pr_tot_qr)
506  if (allocated(tend_pr_tot_qs)) deallocate(tend_pr_tot_qs)
507  if (allocated(tend_pr_tot_qg)) deallocate(tend_pr_tot_qg)
508  if (allocated(tend_pr_tot_tabs)) deallocate(tend_pr_tot_tabs)
509 
Here is the caller graph for this function:

◆ initialisation_callback()

subroutine tvdadvection_mod::initialisation_callback ( type(model_state_type), intent(inout), target  current_state)
private

Sets up the stencil_mod (used in interpolation) and allocates data for the flux fields.

Parameters
current_stateThe current model state_mod

Definition at line 277 of file tvdadvection.F90.

278  type(model_state_type), target, intent(inout) :: current_state
279  logical :: l_qdiag
280 
281  type(prognostic_field_ptr_type), dimension(3) :: fields
282  integer, dimension(3, 2) :: sizes
283  integer :: num_fields
284  logical :: xdim, ydim
285 
286  xdim=.false.
287  ydim=.false.
288  num_fields=0
289 #ifdef U_ACTIVE
290  xdim=.true.
291  num_fields = num_fields + 1
292  fields(num_fields)%ptr => current_state%u
293  sizes(num_fields,:) = (/ 2, 2 /) ! need um2 therefore -2 (applies to all interpolations)
294  u_index = num_fields
295 #endif
296 
297 #ifdef V_ACTIVE
298  ydim=.true.
299  num_fields = num_fields + 1
300  fields(num_fields)%ptr => current_state%v
301  sizes(num_fields,:) = (/ 1, 1 /)
302  v_index=num_fields
303 #endif
304 
305 #ifdef W_ACTIVE
306  num_fields = num_fields + 1
307  fields(num_fields)%ptr => current_state%w
308  sizes(num_fields,:) = (/ 1, 1 /)
309  w_index=num_fields
310 #endif
311  ! Allocate from 0, as any inactive dimensions will issue 0 to the ultimate flux which ignores the field
312  allocate(interpolated_fields(0:num_fields))
313 #ifdef U_ACTIVE
314  allocate(interpolated_fields(u_index)%data(current_state%global_grid%size(z_index), -1:3, -1:3))
315  interpolated_fields(u_index)%active=.true.
316 #endif
317 #ifdef V_ACTIVE
318  allocate(interpolated_fields(v_index)%data(current_state%global_grid%size(z_index), 0:2, 0:2))
319  interpolated_fields(v_index)%active=.true.
320 #endif
321 #ifdef W_ACTIVE
322  allocate(interpolated_fields(w_index)%data(current_state%global_grid%size(z_index), 0:2, 0:2))
323  interpolated_fields(w_index)%active=.true.
324 #endif
325 
326  star_stencil = create_stencil(current_state%local_grid, fields, num_fields, 3, sizes, xdim, ydim)
327  allocate(flux_y(current_state%global_grid%size(z_index)))
328  allocate(flux_z(current_state%global_grid%size(z_index)))
329  allocate(flux_x(current_state%global_grid%size(z_index)))
330  allocate(u_advection(current_state%global_grid%size(z_index)), v_advection(current_state%global_grid%size(z_index)), &
331  w_advection(current_state%global_grid%size(z_index)), th_advection(current_state%global_grid%size(z_index)), &
332  q_advection(current_state%global_grid%size(z_index), current_state%number_q_fields))
333 
334  advect_flow=determine_if_advection_here(options_get_string(current_state%options_database, "advection_flow_fields"))
335  advect_th=determine_if_advection_here(options_get_string(current_state%options_database, "advection_theta_field"))
336  advect_q=determine_if_advection_here(options_get_string(current_state%options_database, "advection_q_fields"))
337 
338  ! Set tendency diagnostic logicals based on availability
339  ! Need to use 3d tendencies to compute the profiles, so they will be allocated
340  ! in the case where profiles are available
341  l_qdiag = (.not. current_state%passive_q .and. current_state%number_q_fields .gt. 0) .and. advect_q
342 
343  l_tend_pr_tot_u = current_state%u%active .and. advect_flow
344  l_tend_pr_tot_v = current_state%v%active .and. advect_flow
345  l_tend_pr_tot_w = current_state%w%active .and. advect_flow
346  l_tend_pr_tot_th = current_state%th%active .and. advect_th
347  l_tend_pr_tot_qv = l_qdiag .and. current_state%number_q_fields .ge. 1
348  l_tend_pr_tot_ql = l_qdiag .and. current_state%number_q_fields .ge. 2
349  l_tend_pr_tot_qi = l_qdiag .and. current_state%number_q_fields .ge. 11
350  l_tend_pr_tot_qr = l_qdiag .and. current_state%number_q_fields .ge. 11
351  l_tend_pr_tot_qs = l_qdiag .and. current_state%number_q_fields .ge. 11
352  l_tend_pr_tot_qg = l_qdiag .and. current_state%number_q_fields .ge. 11
353  l_tend_pr_tot_tabs = l_tend_pr_tot_th
354 
355  l_tend_3d_u = (current_state%u%active .and. advect_flow) .or. l_tend_pr_tot_u
356  l_tend_3d_v = (current_state%v%active .and. advect_flow) .or. l_tend_pr_tot_v
357  l_tend_3d_w = (current_state%w%active .and. advect_flow) .or. l_tend_pr_tot_w
358  l_tend_3d_th = (current_state%th%active .and. advect_th) .or. l_tend_pr_tot_th
359  l_tend_3d_qv = (l_qdiag .and. current_state%number_q_fields .ge. 1) .or. l_tend_pr_tot_qv
360  l_tend_3d_ql = (l_qdiag .and. current_state%number_q_fields .ge. 2) .or. l_tend_pr_tot_ql
361  l_tend_3d_qi = (l_qdiag .and. current_state%number_q_fields .ge. 11) .or. l_tend_pr_tot_qi
362  l_tend_3d_qr = (l_qdiag .and. current_state%number_q_fields .ge. 11) .or. l_tend_pr_tot_qr
363  l_tend_3d_qs = (l_qdiag .and. current_state%number_q_fields .ge. 11) .or. l_tend_pr_tot_qs
364  l_tend_3d_qg = (l_qdiag .and. current_state%number_q_fields .ge. 11) .or. l_tend_pr_tot_qg
365  l_tend_3d_tabs = l_tend_3d_th
366 
367 
368  ! Allocate 3d tendency fields upon availability
369  if (l_tend_3d_u) then
370  allocate( tend_3d_u(current_state%local_grid%size(z_index), &
371  current_state%local_grid%size(y_index), &
372  current_state%local_grid%size(x_index) ) )
373  endif
374  if (l_tend_3d_v) then
375  allocate( tend_3d_v(current_state%local_grid%size(z_index), &
376  current_state%local_grid%size(y_index), &
377  current_state%local_grid%size(x_index) ) )
378  endif
379  if (l_tend_3d_w) then
380  allocate( tend_3d_w(current_state%local_grid%size(z_index), &
381  current_state%local_grid%size(y_index), &
382  current_state%local_grid%size(x_index) ) )
383  endif
384  if (l_tend_3d_th) then
385  allocate( tend_3d_th(current_state%local_grid%size(z_index), &
386  current_state%local_grid%size(y_index), &
387  current_state%local_grid%size(x_index) ) )
388  endif
389  if (l_tend_3d_qv) then
390  iqv=get_q_index(standard_q_names%VAPOUR, 'tvd_advection')
391  allocate( tend_3d_qv(current_state%local_grid%size(z_index), &
392  current_state%local_grid%size(y_index), &
393  current_state%local_grid%size(x_index) ) )
394  endif
395  if (l_tend_3d_ql) then
396  iql=get_q_index(standard_q_names%CLOUD_LIQUID_MASS, 'tvd_advection')
397  allocate( tend_3d_ql(current_state%local_grid%size(z_index), &
398  current_state%local_grid%size(y_index), &
399  current_state%local_grid%size(x_index) ) )
400  endif
401  if (l_tend_3d_qi) then
402  iqi=get_q_index(standard_q_names%ICE_MASS, 'tvd_advection')
403  allocate( tend_3d_qi(current_state%local_grid%size(z_index), &
404  current_state%local_grid%size(y_index), &
405  current_state%local_grid%size(x_index) ) )
406  endif
407  if (l_tend_3d_qr) then
408  iqr=get_q_index(standard_q_names%RAIN_MASS, 'tvd_advection')
409  allocate( tend_3d_qr(current_state%local_grid%size(z_index), &
410  current_state%local_grid%size(y_index), &
411  current_state%local_grid%size(x_index) ) )
412  endif
413  if (l_tend_3d_qs) then
414  iqs=get_q_index(standard_q_names%SNOW_MASS, 'tvd_advection')
415  allocate( tend_3d_qs(current_state%local_grid%size(z_index), &
416  current_state%local_grid%size(y_index), &
417  current_state%local_grid%size(x_index) ) )
418  endif
419  if (l_tend_3d_qg) then
420  iqg=get_q_index(standard_q_names%GRAUPEL_MASS, 'tvd_advection')
421  allocate( tend_3d_qg(current_state%local_grid%size(z_index), &
422  current_state%local_grid%size(y_index), &
423  current_state%local_grid%size(x_index) ) )
424  endif
425  if (l_tend_3d_tabs) then
426  allocate( tend_3d_tabs(current_state%local_grid%size(z_index), &
427  current_state%local_grid%size(y_index), &
428  current_state%local_grid%size(x_index) ) )
429  endif
430  ! Allocate profile tendency fields upon availability
431  if (l_tend_pr_tot_u) then
432  allocate( tend_pr_tot_u(current_state%local_grid%size(z_index)) )
433  endif
434  if (l_tend_pr_tot_v) then
435  allocate( tend_pr_tot_v(current_state%local_grid%size(z_index)) )
436  endif
437  if (l_tend_pr_tot_w) then
438  allocate( tend_pr_tot_w(current_state%local_grid%size(z_index)) )
439  endif
440  if (l_tend_pr_tot_th) then
441  allocate( tend_pr_tot_th(current_state%local_grid%size(z_index)) )
442  endif
443  if (l_tend_pr_tot_qv) then
444  allocate( tend_pr_tot_qv(current_state%local_grid%size(z_index)) )
445  endif
446  if (l_tend_pr_tot_ql) then
447  allocate( tend_pr_tot_ql(current_state%local_grid%size(z_index)) )
448  endif
449  if (l_tend_pr_tot_qi) then
450  allocate( tend_pr_tot_qi(current_state%local_grid%size(z_index)) )
451  endif
452  if (l_tend_pr_tot_qr) then
453  allocate( tend_pr_tot_qr(current_state%local_grid%size(z_index)) )
454  endif
455  if (l_tend_pr_tot_qs) then
456  allocate( tend_pr_tot_qs(current_state%local_grid%size(z_index)) )
457  endif
458  if (l_tend_pr_tot_qg) then
459  allocate( tend_pr_tot_qg(current_state%local_grid%size(z_index)) )
460  endif
461  if (l_tend_pr_tot_tabs) then
462  allocate( tend_pr_tot_tabs(current_state%local_grid%size(z_index)) )
463  endif
464 
465  ! Save the sampling_frequency to force diagnostic calculation on select time steps
466  diagnostic_generation_frequency=options_get_integer(current_state%options_database,"sampling_frequency")
467 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ register_y_flux_wrap_recv_if_required()

subroutine tvdadvection_mod::register_y_flux_wrap_recv_if_required ( integer, intent(in)  y_local_index,
type(prognostic_field_type), intent(inout)  field,
type(parallel_state_type), intent(inout)  parallel,
type(local_grid_type), intent(inout)  local_grid 
)
private

Registers an MPI asynchronous receive for the flux if required.

This is registered at the start and we have until the last column in Y until it must be completed. No communication is registered if this is a local operation

Parameters
y_local_indexThe local index in Y
fieldThe prognostic field
parallelParallel system description
local_gridThe local grid description

Definition at line 1002 of file tvdadvection.F90.

1003  integer, intent(in) :: y_local_index
1004  type(prognostic_field_type), intent(inout) :: field
1005  type(parallel_state_type), intent(inout) :: parallel
1006  type(local_grid_type), intent(inout) :: local_grid
1007 
1008  integer :: ierr
1009 
1010  if (y_local_index == local_grid%local_domain_start_index(y_index) .and. parallel%my_coords(y_index) == &
1011  parallel%dim_sizes(y_index)-1) then
1012  if (parallel%my_rank .ne. local_grid%neighbours(y_index,3)) then
1013  if (.not. allocated(field%flux_y_buffer)) allocate(field%flux_y_buffer(local_grid%size(z_index)))
1014  call mpi_irecv(field%flux_y_buffer, local_grid%size(z_index), precision_type, local_grid%neighbours(y_index,3), 0, &
1015  parallel%neighbour_comm, field%async_flux_handle, ierr)
1016  end if
1017  end if
Here is the caller graph for this function:

◆ register_y_flux_wrap_send_if_required()

subroutine tvdadvection_mod::register_y_flux_wrap_send_if_required ( integer, intent(in)  y_local_index,
type(prognostic_field_type), intent(inout)  field,
type(parallel_state_type), intent(inout)  parallel,
type(local_grid_type), intent(inout)  local_grid 
)
private

Registers an asynchronous send for the Y flux if required.

This is done after the second y is computed and we have until the entire Y dimension is completed until the communication must be complete. If the wrap around process is the same (one process in Y dimension) then just issues a local copy to the buffer.

Parameters
y_local_indexThe local index in Y
fieldThe prognostic field
parallelParallel system description
local_gridThe local grid description

Definition at line 953 of file tvdadvection.F90.

954  integer, intent(in) :: y_local_index
955  type(prognostic_field_type), intent(inout) :: field
956  type(parallel_state_type), intent(inout) :: parallel
957  type(local_grid_type), intent(inout) :: local_grid
958 
959  integer :: ierr
960 
961  if (y_local_index == local_grid%local_domain_start_index(y_index)-1 .and. parallel%my_coords(y_index) == 0) then
962  if (.not. allocated(field%flux_y_buffer)) allocate(field%flux_y_buffer(local_grid%size(z_index)))
963  field%flux_y_buffer(:) = flux_y(:)
964  if (parallel%my_rank .ne. local_grid%neighbours(y_index,1)) then
965  call mpi_isend(field%flux_y_buffer, local_grid%size(z_index), precision_type, local_grid%neighbours(y_index,1), 0, &
966  parallel%neighbour_comm, field%async_flux_handle, ierr)
967  end if
968  end if
Here is the caller graph for this function:

◆ save_precomponent_tendencies()

subroutine tvdadvection_mod::save_precomponent_tendencies ( type(model_state_type), intent(in), target  current_state,
integer, intent(in)  cxn,
integer, intent(in)  cyn,
integer, intent(in)  txn,
integer, intent(in)  tyn 
)
private

Save the 3d tendencies coming into the component.

Parameters
current_stateCurrent model state
cxnThe current slice, x, index
cynThe current column, y, index.
txntarget_x_index
tyntarget_y_index

Definition at line 1027 of file tvdadvection.F90.

1028  type(model_state_type), target, intent(in) :: current_state
1029  integer, intent(in) :: cxn, cyn, txn, tyn
1030 
1031  ! Save 3d tendency fields upon request (of 3d or profiles) and availability
1032  if (l_tend_3d_u) then
1033  tend_3d_u(:,tyn,txn)=current_state%su%data(:,cyn,cxn)
1034  endif
1035  if (l_tend_3d_v) then
1036  tend_3d_v(:,tyn,txn)=current_state%sv%data(:,cyn,cxn)
1037  endif
1038  if (l_tend_3d_w) then
1039  tend_3d_w(:,tyn,txn)=current_state%sw%data(:,cyn,cxn)
1040  endif
1041  if (l_tend_3d_th) then
1042  tend_3d_th(:,tyn,txn)=current_state%sth%data(:,cyn,cxn)
1043  endif
1044  if (l_tend_3d_qv) then
1045  tend_3d_qv(:,tyn,txn)=current_state%sq(iqv)%data(:,cyn,cxn)
1046  endif
1047  if (l_tend_3d_ql) then
1048  tend_3d_ql(:,tyn,txn)=current_state%sq(iql)%data(:,cyn,cxn)
1049  endif
1050  if (l_tend_3d_qi) then
1051  tend_3d_qi(:,tyn,txn)=current_state%sq(iqi)%data(:,cyn,cxn)
1052  endif
1053  if (l_tend_3d_qr) then
1054  tend_3d_qr(:,tyn,txn)=current_state%sq(iqr)%data(:,cyn,cxn)
1055  endif
1056  if (l_tend_3d_qs) then
1057  tend_3d_qs(:,tyn,txn)=current_state%sq(iqs)%data(:,cyn,cxn)
1058  endif
1059  if (l_tend_3d_qg) then
1060  tend_3d_qg(:,tyn,txn)=current_state%sq(iqg)%data(:,cyn,cxn)
1061  endif
1062  if (l_tend_3d_tabs) then
1063  tend_3d_tabs(:,tyn,txn)=current_state%sth%data(:,cyn,cxn) * current_state%global_grid%configuration%vertical%rprefrcp(:)
1064  endif
1065 
Here is the caller graph for this function:

◆ set_published_field_value()

subroutine tvdadvection_mod::set_published_field_value ( type(component_field_value_type), intent(inout)  field_value,
real(kind=default_precision), dimension(:), optional  real_1d_field,
real(kind=default_precision), dimension(:,:), optional  real_2d_field,
real(kind=default_precision), dimension(:,:,:), optional  real_3d_field 
)
private

Sets the published field value from the temporary diagnostic values held by.

Definition at line 1159 of file tvdadvection.F90.

1160  type(component_field_value_type), intent(inout) :: field_value
1161  real(kind=default_precision), dimension(:), optional :: real_1d_field
1162  real(kind=default_precision), dimension(:,:), optional :: real_2d_field
1163  real(kind=default_precision), dimension(:,:,:), optional :: real_3d_field
1164 
1165 
1166  if (present(real_1d_field)) then
1167  allocate(field_value%real_1d_array(size(real_1d_field)),source=real_1d_field)
1168  else if (present(real_2d_field)) then
1169  allocate(field_value%real_2d_array(size(real_2d_field, 1),size(real_2d_field, 2)), source=real_2d_field)
1170  else if (present(real_3d_field)) then
1171  allocate(field_value%real_3d_array(size(real_3d_field, 1),size(real_3d_field, 2), size(real_3d_field, 3)), &
1172  source=real_3d_field)
1173  end if
Here is the caller graph for this function:

◆ timestep_callback()

subroutine tvdadvection_mod::timestep_callback ( type(model_state_type), intent(inout), target  current_state)
private

Timestep callback hook which performs the TVD advection for each prognostic field.

Parameters
current_stateThe current model state_mod

Definition at line 514 of file tvdadvection.F90.

515  type(model_state_type), target, intent(inout) :: current_state
516  integer :: current_x_index, current_y_index, target_x_index, target_y_index
517 
518  current_x_index=current_state%column_local_x
519  current_y_index=current_state%column_local_y
520  target_y_index=current_y_index-current_state%local_grid%halo_size(y_index)
521  target_x_index=current_x_index-current_state%local_grid%halo_size(x_index)
522 
523  ! Zero profile tendency totals on first instance in the sum
524  if (current_state%first_timestep_column) then
525  if (l_tend_pr_tot_u) then
526  tend_pr_tot_u(:)= 0.0_default_precision
527  endif
528  if (l_tend_pr_tot_v) then
529  tend_pr_tot_v(:)= 0.0_default_precision
530  endif
531  if (l_tend_pr_tot_w) then
532  tend_pr_tot_w(:)= 0.0_default_precision
533  endif
534  if (l_tend_pr_tot_th) then
535  tend_pr_tot_th(:)=0.0_default_precision
536  endif
537  if (l_tend_pr_tot_qv) then
538  tend_pr_tot_qv(:)=0.0_default_precision
539  endif
540  if (l_tend_pr_tot_ql) then
541  tend_pr_tot_ql(:)=0.0_default_precision
542  endif
543  if (l_tend_pr_tot_qi) then
544  tend_pr_tot_qi(:)=0.0_default_precision
545  endif
546  if (l_tend_pr_tot_qr) then
547  tend_pr_tot_qr(:)=0.0_default_precision
548  endif
549  if (l_tend_pr_tot_qs) then
550  tend_pr_tot_qs(:)=0.0_default_precision
551  endif
552  if (l_tend_pr_tot_qg) then
553  tend_pr_tot_qg(:)=0.0_default_precision
554  endif
555  if (l_tend_pr_tot_tabs) then
556  tend_pr_tot_tabs(:)=0.0_default_precision
557  endif
558  endif ! zero totals
559 
560 
561  if (current_state%halo_column) then
562  if (.not. ((current_state%column_local_y == current_state%local_grid%halo_size(y_index) .and. &
563  current_state%column_local_x .le. current_state%local_grid%local_domain_end_index(x_index) .and. &
564  current_state%column_local_x .ge. current_state%local_grid%local_domain_start_index(x_index)-1) .or. &
565  (current_state%column_local_x == current_state%local_grid%halo_size(x_index) .and. &
566  current_state%column_local_y .ge. current_state%local_grid%local_domain_start_index(y_index) &
567  .and. current_state%column_local_y .le. current_state%local_grid%local_domain_end_index(y_index)) )) return
568  end if
569 
570  if (mod(current_state%timestep, diagnostic_generation_frequency) == 0 .and. (.not. current_state%halo_column) ) then
571  call save_precomponent_tendencies(current_state, current_x_index, current_y_index, target_x_index, target_y_index)
572  end if
573 
574  if (advect_flow) call advect_flow_fields(current_state)
575  if (advect_th) call advect_theta(current_state)
576  if (advect_q) call advect_q_fields(current_state)
577 
578  if (mod(current_state%timestep, diagnostic_generation_frequency) == 0 .and. (.not. current_state%halo_column) ) then
579  call compute_component_tendencies(current_state, current_x_index, current_y_index, target_x_index, target_y_index)
580  end if
581 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ tvdadvection_get_descriptor()

type(component_descriptor_type) function, public tvdadvection_mod::tvdadvection_get_descriptor

Provides a description of this component for the core to register.

Returns
The descriptor containing registration information for this component

Definition at line 62 of file tvdadvection.F90.

63  tvdadvection_get_descriptor%name="tvd_advection"
64  tvdadvection_get_descriptor%version=0.1
65  tvdadvection_get_descriptor%initialisation=>initialisation_callback
66  tvdadvection_get_descriptor%timestep=>timestep_callback
67  tvdadvection_get_descriptor%finalisation=>finalisation_callback
68 
69  tvdadvection_get_descriptor%field_value_retrieval=>field_value_retrieval_callback
70  tvdadvection_get_descriptor%field_information_retrieval=>field_information_retrieval_callback
71  allocate(tvdadvection_get_descriptor%published_fields(5+11+11))
72  tvdadvection_get_descriptor%published_fields(1)="u_advection"
73  tvdadvection_get_descriptor%published_fields(2)="v_advection"
74  tvdadvection_get_descriptor%published_fields(3)="w_advection"
75  tvdadvection_get_descriptor%published_fields(4)="th_advection"
76  tvdadvection_get_descriptor%published_fields(5)="q_advection"
77 
78  tvdadvection_get_descriptor%published_fields(5+1)="tend_u_tvdadvection_3d_local"
79  tvdadvection_get_descriptor%published_fields(5+2)="tend_v_tvdadvection_3d_local"
80  tvdadvection_get_descriptor%published_fields(5+3)="tend_w_tvdadvection_3d_local"
81  tvdadvection_get_descriptor%published_fields(5+4)="tend_th_tvdadvection_3d_local"
82  tvdadvection_get_descriptor%published_fields(5+5)="tend_qv_tvdadvection_3d_local"
83  tvdadvection_get_descriptor%published_fields(5+6)="tend_ql_tvdadvection_3d_local"
84  tvdadvection_get_descriptor%published_fields(5+7)="tend_qi_tvdadvection_3d_local"
85  tvdadvection_get_descriptor%published_fields(5+8)="tend_qr_tvdadvection_3d_local"
86  tvdadvection_get_descriptor%published_fields(5+9)="tend_qs_tvdadvection_3d_local"
87  tvdadvection_get_descriptor%published_fields(5+10)="tend_qg_tvdadvection_3d_local"
88  tvdadvection_get_descriptor%published_fields(5+11)="tend_tabs_tvdadvection_3d_local"
89 
90  tvdadvection_get_descriptor%published_fields(5+11+1)="tend_u_tvdadvection_profile_total_local"
91  tvdadvection_get_descriptor%published_fields(5+11+2)="tend_v_tvdadvection_profile_total_local"
92  tvdadvection_get_descriptor%published_fields(5+11+3)="tend_w_tvdadvection_profile_total_local"
93  tvdadvection_get_descriptor%published_fields(5+11+4)="tend_th_tvdadvection_profile_total_local"
94  tvdadvection_get_descriptor%published_fields(5+11+5)="tend_qv_tvdadvection_profile_total_local"
95  tvdadvection_get_descriptor%published_fields(5+11+6)="tend_ql_tvdadvection_profile_total_local"
96  tvdadvection_get_descriptor%published_fields(5+11+7)="tend_qi_tvdadvection_profile_total_local"
97  tvdadvection_get_descriptor%published_fields(5+11+8)="tend_qr_tvdadvection_profile_total_local"
98  tvdadvection_get_descriptor%published_fields(5+11+9)="tend_qs_tvdadvection_profile_total_local"
99  tvdadvection_get_descriptor%published_fields(5+11+10)="tend_qg_tvdadvection_profile_total_local"
100  tvdadvection_get_descriptor%published_fields(5+11+11)="tend_tabs_tvdadvection_profile_total_local"
101 
Here is the call graph for this function:

Variable Documentation

◆ advect_flow

logical tvdadvection_mod::advect_flow
private

Definition at line 28 of file tvdadvection.F90.

28  logical :: advect_flow, advect_th, advect_q

◆ advect_q

logical tvdadvection_mod::advect_q
private

Definition at line 28 of file tvdadvection.F90.

◆ advect_th

logical tvdadvection_mod::advect_th
private

Definition at line 28 of file tvdadvection.F90.

◆ diagnostic_generation_frequency

integer tvdadvection_mod::diagnostic_generation_frequency
private

Definition at line 54 of file tvdadvection.F90.

54  integer :: diagnostic_generation_frequency

◆ flux_x

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::flux_x
private

Definition at line 29 of file tvdadvection.F90.

29  real(kind=default_precision), dimension(:), allocatable :: flux_x, flux_y, flux_z, u_advection, v_advection, &
30  w_advection, th_advection

◆ flux_y

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::flux_y
private

Definition at line 29 of file tvdadvection.F90.

◆ flux_z

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::flux_z
private

Definition at line 29 of file tvdadvection.F90.

◆ interpolated_fields

type(prognostic_field_type), dimension(:), allocatable tvdadvection_mod::interpolated_fields
private

Definition at line 33 of file tvdadvection.F90.

33  type(prognostic_field_type), dimension(:), allocatable :: interpolated_fields

◆ iqg

integer tvdadvection_mod::iqg =0
private

Definition at line 53 of file tvdadvection.F90.

◆ iqi

integer tvdadvection_mod::iqi =0
private

Definition at line 53 of file tvdadvection.F90.

◆ iql

integer tvdadvection_mod::iql =0
private

Definition at line 53 of file tvdadvection.F90.

◆ iqr

integer tvdadvection_mod::iqr =0
private

Definition at line 53 of file tvdadvection.F90.

◆ iqs

integer tvdadvection_mod::iqs =0
private

Definition at line 53 of file tvdadvection.F90.

◆ iqv

integer tvdadvection_mod::iqv =0
private

Definition at line 53 of file tvdadvection.F90.

53  integer :: iqv=0, iql=0, iqr=0, iqi=0, iqs=0, iqg=0

◆ l_tend_3d_qg

logical tvdadvection_mod::l_tend_3d_qg
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_qi

logical tvdadvection_mod::l_tend_3d_qi
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_ql

logical tvdadvection_mod::l_tend_3d_ql
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_qr

logical tvdadvection_mod::l_tend_3d_qr
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_qs

logical tvdadvection_mod::l_tend_3d_qs
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_qv

logical tvdadvection_mod::l_tend_3d_qv
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_tabs

logical tvdadvection_mod::l_tend_3d_tabs
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_th

logical tvdadvection_mod::l_tend_3d_th
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_u

logical tvdadvection_mod::l_tend_3d_u
private

Definition at line 41 of file tvdadvection.F90.

41  logical :: l_tend_3d_u, l_tend_3d_v, l_tend_3d_w, l_tend_3d_th,l_tend_3d_qv, &
42  l_tend_3d_ql,l_tend_3d_qi,l_tend_3d_qr,l_tend_3d_qs,l_tend_3d_qg, &
43  l_tend_3d_tabs

◆ l_tend_3d_v

logical tvdadvection_mod::l_tend_3d_v
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_3d_w

logical tvdadvection_mod::l_tend_3d_w
private

Definition at line 41 of file tvdadvection.F90.

◆ l_tend_pr_tot_qg

logical tvdadvection_mod::l_tend_pr_tot_qg
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_qi

logical tvdadvection_mod::l_tend_pr_tot_qi
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_ql

logical tvdadvection_mod::l_tend_pr_tot_ql
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_qr

logical tvdadvection_mod::l_tend_pr_tot_qr
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_qs

logical tvdadvection_mod::l_tend_pr_tot_qs
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_qv

logical tvdadvection_mod::l_tend_pr_tot_qv
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_tabs

logical tvdadvection_mod::l_tend_pr_tot_tabs
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_th

logical tvdadvection_mod::l_tend_pr_tot_th
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_u

logical tvdadvection_mod::l_tend_pr_tot_u
private

Definition at line 49 of file tvdadvection.F90.

49  logical :: l_tend_pr_tot_u, l_tend_pr_tot_v, l_tend_pr_tot_w,l_tend_pr_tot_th,l_tend_pr_tot_qv, &
50  l_tend_pr_tot_ql,l_tend_pr_tot_qi,l_tend_pr_tot_qr,l_tend_pr_tot_qs,l_tend_pr_tot_qg, &
51  l_tend_pr_tot_tabs

◆ l_tend_pr_tot_v

logical tvdadvection_mod::l_tend_pr_tot_v
private

Definition at line 49 of file tvdadvection.F90.

◆ l_tend_pr_tot_w

logical tvdadvection_mod::l_tend_pr_tot_w
private

Definition at line 49 of file tvdadvection.F90.

◆ q_advection

real(kind=default_precision), dimension(:,:), allocatable tvdadvection_mod::q_advection
private

Definition at line 31 of file tvdadvection.F90.

31  real(kind=default_precision), dimension(:,:), allocatable :: q_advection

◆ star_stencil

type(grid_stencil_type), save tvdadvection_mod::star_stencil
private

Definition at line 26 of file tvdadvection.F90.

26  type(grid_stencil_type), save :: star_stencil

◆ tend_3d_qg

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_qg
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_qi

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_qi
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_ql

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_ql
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_qr

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_qr
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_qs

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_qs
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_qv

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_qv
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_tabs

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_tabs
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_th

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_th
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_u

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_u
private

Definition at line 37 of file tvdadvection.F90.

37  real(kind=default_precision), dimension(:,:,:), allocatable :: &
38  tend_3d_u, tend_3d_v, tend_3d_w, tend_3d_th,tend_3d_qv, &
39  tend_3d_ql,tend_3d_qi,tend_3d_qr,tend_3d_qs,tend_3d_qg, &
40  tend_3d_tabs

◆ tend_3d_v

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_v
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_3d_w

real(kind=default_precision), dimension(:,:,:), allocatable tvdadvection_mod::tend_3d_w
private

Definition at line 37 of file tvdadvection.F90.

◆ tend_pr_tot_qg

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_qg
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_qi

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_qi
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_ql

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_ql
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_qr

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_qr
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_qs

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_qs
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_qv

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_qv
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_tabs

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_tabs
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_th

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_th
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_u

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_u
private

Definition at line 45 of file tvdadvection.F90.

45  real(kind=default_precision), dimension(:), allocatable :: &
46  tend_pr_tot_u, tend_pr_tot_v, tend_pr_tot_w,tend_pr_tot_th,tend_pr_tot_qv, &
47  tend_pr_tot_ql,tend_pr_tot_qi,tend_pr_tot_qr,tend_pr_tot_qs,tend_pr_tot_qg, &
48  tend_pr_tot_tabs

◆ tend_pr_tot_v

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_v
private

Definition at line 45 of file tvdadvection.F90.

◆ tend_pr_tot_w

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::tend_pr_tot_w
private

Definition at line 45 of file tvdadvection.F90.

◆ th_advection

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::th_advection
private

Definition at line 29 of file tvdadvection.F90.

◆ u_advection

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::u_advection
private

Definition at line 29 of file tvdadvection.F90.

◆ u_index

integer, save tvdadvection_mod::u_index =0
private

Definition at line 27 of file tvdadvection.F90.

27  integer, save :: u_index=0, v_index=0, w_index=0

◆ v_advection

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::v_advection
private

Definition at line 29 of file tvdadvection.F90.

◆ v_index

integer, save tvdadvection_mod::v_index =0
private

Definition at line 27 of file tvdadvection.F90.

◆ w_advection

real(kind=default_precision), dimension(:), allocatable tvdadvection_mod::w_advection
private

Definition at line 29 of file tvdadvection.F90.

◆ w_index

integer, save tvdadvection_mod::w_index =0
private

Definition at line 27 of file tvdadvection.F90.

grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
optionsdatabase_mod::options_get_integer
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
Definition: optionsdatabase.F90:217
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
optionsdatabase_mod::options_get_string
character(len=string_length) function, public options_get_string(options_database, key, index)
Retrieves a string value from the database that matches the provided key.
Definition: optionsdatabase.F90:280
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17