23   real(kind=
default_precision) :: 
eps, 
repsh, 
thcona, 
thconb, 
thconap1, 
suba, 
subb, 
subc, 
subg, 
subh, 
subr, 
pr_n, 
ric, 
ricinv 
   45     type(model_state_type), 
target, 
intent(inout) :: current_state
 
   48     if (.not. is_component_enabled(current_state%options_database, 
"diffusion")) 
then 
   49       call log_master_log(log_error, 
"Smagorinsky requires the diffusion component to be enabled")
 
   51     if (.not. is_component_enabled(current_state%options_database, 
"viscosity")) 
then 
   52       call log_master_log(log_error, 
"Smagorinsky requires the viscosity component to be enabled")
 
   54     if (.not. current_state%use_viscosity_and_diffusion) 
then  
   55        call log_master_log(log_error, 
"Smagorinsky requires use_viscosity_and_diffusion=.true. or monc will fail")
 
   58     if (.not. is_component_enabled(current_state%options_database, 
"lower_bc")) 
then 
   59        call log_master_log(log_info, 
"LOWERBC is disabled, zero diff and vis_coeff on level 1")
 
   60        current_state%vis_coefficient%data(1,:,:)=0.0_default_precision
 
   61        current_state%diff_coefficient%data(1,:,:)=0.0_default_precision
 
   64     eps=0.01_default_precision
 
   66     thcona=ratio_mol_wts*current_state%thref0
 
   70     subb=options_get_real(current_state%options_database, 
"smag-subb")
 
   71     subc=options_get_real(current_state%options_database, 
"smag-subc")
 
   73     subg=1.2_default_precision
 
   74     subh=0.0_default_precision
 
   75     subr=4.0_default_precision
 
   76     pr_n=0.7_default_precision
 
   78     ric=0.25_default_precision
 
   80     if (current_state%use_viscosity_and_diffusion) 
then 
   81       call init_halo_communication(current_state, get_single_field_per_halo_cell, &
 
   82            current_state%viscosity_halo_swap_state, 2, .true.)
 
   83       call init_halo_communication(current_state, get_single_field_per_halo_cell, &
 
   84            current_state%diffusion_halo_swap_state, 2, .true.)
 
   87     if (.not. current_state%passive_q) 
then  
   88        iqv = get_q_index(standard_q_names%VAPOUR, 
'smagorinsky')
 
   89        current_state%water_vapour_mixing_ratio_index=
iqv 
   91        iql = get_q_index(standard_q_names%CLOUD_LIQUID_MASS, 
'smagorinsky')
 
   92        current_state%liquid_water_mixing_ratio_index=
iql 
  100     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  102     real(kind=default_precision), 
dimension(current_state%local_grid%size(Z_INDEX)) :: richardson_number, ssq
 
  104     if (.not. current_state%halo_column) 
then 
  105       if (.not. current_state%use_viscosity_and_diffusion) 
then 
  106         current_state%vis_coefficient%data(2:,:,:)=0.0_default_precision
 
  107         current_state%diff_coefficient%data(2:,:,:)=0.0_default_precision
 
  108         current_state%cvis=0.0_default_precision
 
  110         if (current_state%field_stepping == forward_stepping) 
then 
  117         call setfri(current_state, richardson_number, ssq)
 
  118         if (is_component_enabled(current_state%options_database, 
"cfltest")) 
then 
  123     if (current_state%last_timestep_column) 
then 
  125       call initiate_nonblocking_halo_swap(current_state, current_state%diffusion_halo_swap_state, &
 
  127       call initiate_nonblocking_halo_swap(current_state, current_state%viscosity_halo_swap_state, &
 
  135     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  137     call finalise_halo_communication(current_state%viscosity_halo_swap_state)
 
  138     call finalise_halo_communication(current_state%diffusion_halo_swap_state)
 
  144     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  148     if (mod(current_state%timestep, current_state%cfl_frequency) == 1 .or. &
 
  149          current_state%timestep-current_state%start_timestep .le. current_state%cfl_frequency) 
then 
  150       do k=2, current_state%local_grid%size(z_index)-1
 
  151         current_state%cvis=max(current_state%cvis, max(current_state%vis_coefficient%data(k, current_state%column_local_y, &
 
  152              current_state%column_local_x),current_state%diff_coefficient%data(k, current_state%column_local_y, &
 
  153              current_state%column_local_x))*(current_state%global_grid%configuration%vertical%rdzn(k+1)**2+&
 
  154              current_state%global_grid%configuration%horizontal%cx2+current_state%global_grid%configuration%horizontal%cy2))
 
  164   subroutine setfri(current_state, richardson_number, ssq)
 
  165     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  166     real(kind=default_precision), 
dimension(:), 
intent(in) :: richardson_number, ssq
 
  169     real(kind=default_precision) :: rifac, sctmp
 
  171     do k=2,current_state%local_grid%size(z_index)-1
 
  172       if (richardson_number(k) .le. 0.0_default_precision) 
then 
  173         current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=&
 
  174              sqrt(1.0_default_precision-
subc*richardson_number(k))
 
  175         current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=&
 
  176              suba*sqrt(1.-
subb*richardson_number(k))        
 
  177       else if ((richardson_number(k) .gt. 0.0_default_precision) .and. (richardson_number(k) .lt. 
ric)) 
then 
  178         rifac=(1.-richardson_number(k)*
ricinv)**4
 
  179         current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=&
 
  180              rifac*(1.-
subh*richardson_number(k))
 
  181         current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=&
 
  182              rifac*
suba*(1.-
subg*richardson_number(k))       
 
  184         current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=0.0_default_precision
 
  185         current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=0.0_default_precision
 
  187       sctmp=current_state%global_grid%configuration%vertical%rneutml_sq(k)*sqrt(ssq(k))
 
  188       current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=&
 
  189            current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)*sctmp
 
  190       current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)=&
 
  191            current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x)*sctmp     
 
  194     current_state%vis_coefficient%data(current_state%local_grid%size(z_index), &
 
  195          current_state%column_local_y, current_state%column_local_x)= 0.0_default_precision
 
  196     current_state%diff_coefficient%data(current_state%local_grid%size(z_index), &
 
  197          current_state%column_local_y, current_state%column_local_x)= 0.0_default_precision
 
  205     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  206     real(kind=default_precision), 
dimension(:), 
intent(in) :: ssq
 
  207     type(prognostic_field_type), 
intent(inout) :: th
 
  208     type(prognostic_field_type), 
dimension(:), 
intent(inout) :: q
 
  213     if (.not. current_state%passive_th) 
then 
  214       if (.not. current_state%passive_q) 
then 
  221         do k=2, current_state%local_grid%size(z_index)-1
 
  223                current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x) -&
 
  224                current_state%th%data(k, current_state%column_local_y, current_state%column_local_x))* &
 
  225                current_state%global_grid%configuration%vertical%rdzn(k+1)*&
 
  226                current_state%global_grid%configuration%vertical%buoy_co(k) / ssq(k) 
 
  240     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  241     real(kind=default_precision), 
dimension(:), 
intent(in) :: ssq
 
  242     type(prognostic_field_type), 
intent(inout) :: th
 
  243     type(prognostic_field_type), 
dimension(:), 
intent(inout) :: q
 
  244     real(kind=default_precision), 
dimension(current_state%local_grid%size(Z_INDEX)) :: 
moist_ri_2 
  247     real(kind=default_precision) :: tmpinv, scltmp, qt_k, qt_kp1, thlpr_k, thlpr_kp1, qlli, qlui, &
 
  248          thvli, thvui, thlpr_un, thlpr_ln, qtun, qtln, thvln, thvun, qlln, qlun
 
  250     do k=2,current_state%local_grid%size(z_index)-1
 
  251       tmpinv = 1.0_default_precision/ssq(k)
 
  252       scltmp=current_state%global_grid%configuration%vertical%rdzn(k+1)*&
 
  253            current_state%global_grid%configuration%vertical%buoy_co(k)
 
  254       if (current_state%use_anelastic_equations) 
then 
  255         thcona=ratio_mol_wts*current_state%global_grid%configuration%vertical%thref(k)
 
  256         thconb=0.5_default_precision*(ratio_mol_wts-1.0_default_precision)*&
 
  257              (current_state%global_grid%configuration%vertical%thref(k)+&
 
  258              current_state%global_grid%configuration%vertical%thref(k+1))
 
  259         thconap1=ratio_mol_wts*current_state%global_grid%configuration%vertical%thref(k+1)
 
  262       qt_k = q(current_state%water_vapour_mixing_ratio_index)%data(&
 
  263            k, current_state%column_local_y, current_state%column_local_x)+&
 
  264            q(current_state%liquid_water_mixing_ratio_index)%data(k, current_state%column_local_y, current_state%column_local_x)
 
  265       qt_kp1 = q(current_state%water_vapour_mixing_ratio_index)%data(&
 
  266            k+1, current_state%column_local_y, current_state%column_local_x)+&
 
  267            q(current_state%liquid_water_mixing_ratio_index)%data(k+1, current_state%column_local_y, current_state%column_local_x)
 
  268       thlpr_k = th%data(k, current_state%column_local_y, current_state%column_local_x) -&
 
  269            rlvap_over_cp*q(current_state%liquid_water_mixing_ratio_index)%data(&
 
  270            k, current_state%column_local_y, current_state%column_local_x)*&
 
  271            current_state%global_grid%configuration%vertical%prefrcp(k)
 
  273       thlpr_kp1 = th%data(k+1, current_state%column_local_y, current_state%column_local_x) - &
 
  274            rlvap_over_cp*q(current_state%liquid_water_mixing_ratio_index)%data(&
 
  275            k+1, current_state%column_local_y, current_state%column_local_x)*&
 
  276            current_state%global_grid%configuration%vertical%prefrcp(k)
 
  280       qlli = max(0.0_default_precision, (qt_k-(current_state%global_grid%configuration%vertical%qsat(k) +&
 
  281            current_state%global_grid%configuration%vertical%dqsatdt(k)*&
 
  282            (current_state%global_grid%configuration%vertical%rprefrcp(k)*thlpr_k-&
 
  283            current_state%global_grid%configuration%vertical%tstarpr(k))))*&
 
  284            current_state%global_grid%configuration%vertical%qsatfac(k))
 
  285       qlui = max(0.0_default_precision, (qt_kp1-(current_state%global_grid%configuration%vertical%qsat(k) +&
 
  286            current_state%global_grid%configuration%vertical%dqsatdt(k)*&
 
  287            (current_state%global_grid%configuration%vertical%rprefrcp(k)*(thlpr_kp1+&
 
  288            current_state%global_grid%configuration%vertical%thref(k+1))-&
 
  289            current_state%global_grid%configuration%vertical%tstarpr(k)-&
 
  290            current_state%global_grid%configuration%vertical%tref(k))))*&
 
  291            current_state%global_grid%configuration%vertical%qsatfac(k))
 
  292       thvli = thlpr_k+current_state%global_grid%configuration%vertical%thref(k) +&
 
  293            ( rlvap_over_cp*current_state%global_grid%configuration%vertical%prefrcp(k)-
thcona ) * qlli                         
 
  294       thvui = thlpr_kp1+current_state%global_grid%configuration%vertical%thref(k+1) +&
 
  295            ( rlvap_over_cp*current_state%global_grid%configuration%vertical%prefrcp(k)-
thconap1 ) * qlui                       
 
  301       thlpr_un = thlpr_kp1 - 
eps*(thlpr_kp1 - thlpr_k + current_state%global_grid%configuration%vertical%dthref(k))
 
  302       thlpr_ln = thlpr_k   + 
eps*(thlpr_kp1 - thlpr_k + current_state%global_grid%configuration%vertical%dthref(k))
 
  303       qtun     = qt_kp1    - 
eps*(qt_kp1 - qt_k) 
 
  304       qtln     = qt_k      + 
eps*(qt_kp1 - qt_k)
 
  306       qlln = max(0.0_default_precision,( qtln - ( current_state%global_grid%configuration%vertical%qsat(k) +&
 
  307            current_state%global_grid%configuration%vertical%dqsatdt(k)*&
 
  308            (current_state%global_grid%configuration%vertical%rprefrcp(k)*&
 
  309            thlpr_ln-current_state%global_grid%configuration%vertical%tstarpr(k)))&
 
  310            )*current_state%global_grid%configuration%vertical%qsatfac(k))
 
  311       qlun = max(0.0_default_precision,( qtun - ( current_state%global_grid%configuration%vertical%qsat(k) + &
 
  312            current_state%global_grid%configuration%vertical%dqsatdt(k)*&
 
  313            (current_state%global_grid%configuration%vertical%rprefrcp(k)*&
 
  314            (thlpr_un+current_state%global_grid%configuration%vertical%thref(k+1))-&
 
  315            current_state%global_grid%configuration%vertical%tstarpr(k)-current_state%global_grid%configuration%vertical%tref(k)))&
 
  316            )*current_state%global_grid%configuration%vertical%qsatfac(k))
 
  317       thvln = thlpr_ln+current_state%global_grid%configuration%vertical%thref(k) +&
 
  318            ( rlvap_over_cp*current_state%global_grid%configuration%vertical%prefrcp(k)-
thcona) * qlln
 
  319       thvun = thlpr_un+current_state%global_grid%configuration%vertical%thref(k+1) +&
 
  320            ( rlvap_over_cp*current_state%global_grid%configuration%vertical%prefrcp(k)-
thconap1) * qlun
 
  335     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  336     real(kind=default_precision), 
dimension(:), 
intent(in) :: ssq
 
  337     type(prognostic_field_type), 
intent(inout) :: th
 
  338     type(prognostic_field_type), 
dimension(:), 
intent(inout) :: q
 
  339     real(kind=default_precision), 
dimension(current_state%local_grid%size(Z_INDEX)) :: 
moist_ri_1 
  342     real(kind=default_precision) :: liquid_water_at_kp1, temperature_at_kp1, dtlref, tmpinv, &
 
  343          liquid_water_static_energy_temperature, total_water_substance, total_water_substance_p1, scltmp, qloading
 
  346     do k=2, current_state%local_grid%size(z_index)
 
  347       liquid_water_static_energy_temperature = &
 
  348            th%data(k, current_state%column_local_y, current_state%column_local_x)*&
 
  349            current_state%global_grid%configuration%vertical%rprefrcp(k) - rlvap_over_cp*&
 
  350            q(current_state%liquid_water_mixing_ratio_index)%data(k, current_state%column_local_y, current_state%column_local_x)
 
  352         total_water_substance = q(current_state%water_vapour_mixing_ratio_index)%data(&
 
  353              k, current_state%column_local_y, current_state%column_local_x) + &
 
  354              q(current_state%liquid_water_mixing_ratio_index)%data(k, current_state%column_local_y, current_state%column_local_x)
 
  356         total_water_substance=total_water_substance_p1
 
  358       total_water_substance_p1 = q(current_state%water_vapour_mixing_ratio_index)%data(&
 
  359            k+1, current_state%column_local_y, current_state%column_local_x) + &
 
  360            q(current_state%liquid_water_mixing_ratio_index)%data(k+1, current_state%column_local_y, current_state%column_local_x)
 
  361       if (k .le. current_state%local_grid%size(z_index)-1) 
then 
  362         tmpinv = 1.0_default_precision/ssq(k)
 
  363         dtlref = current_state%global_grid%configuration%vertical%tref(k+1)-&
 
  364              current_state%global_grid%configuration%vertical%tref(k)+(g/cp)*&
 
  365              current_state%global_grid%configuration%vertical%dzn(k+1)
 
  366         temperature_at_kp1=current_state%global_grid%configuration%vertical%tstarpr(k+1)+&
 
  367              current_state%global_grid%configuration%vertical%tref(k+1)+&
 
  368              (liquid_water_static_energy_temperature+rlvap_over_cp*(total_water_substance-&
 
  369              current_state%global_grid%configuration%vertical%qsat(k+1)) - &
 
  370              dtlref - current_state%global_grid%configuration%vertical%tstarpr(k+1) )*&
 
  371              current_state%global_grid%configuration%vertical%qsatfac(k+1)
 
  372         liquid_water_at_kp1=total_water_substance -( current_state%global_grid%configuration%vertical%qsat(k+1)+&
 
  373              current_state%global_grid%configuration%vertical%dqsatdt(k+1)*(temperature_at_kp1- &
 
  374              current_state%global_grid%configuration%vertical%tstarpr(k+1)-&
 
  375              current_state%global_grid%configuration%vertical%tref(k+1)) )
 
  376         if (liquid_water_at_kp1 .le. 0.0_default_precision) 
then 
  377           liquid_water_at_kp1=0.0_default_precision
 
  378           temperature_at_kp1=current_state%global_grid%configuration%vertical%tref(k+1)+&
 
  379                (liquid_water_static_energy_temperature-dtlref)
 
  381         scltmp=current_state%global_grid%configuration%vertical%rdzn(k+1)*&
 
  382              current_state%global_grid%configuration%vertical%buoy_co(k)
 
  386         qloading = current_state%cq(current_state%water_vapour_mixing_ratio_index)*&
 
  387              (total_water_substance_p1-total_water_substance)-ratio_mol_wts*&
 
  388              (q(current_state%liquid_water_mixing_ratio_index)%data(&
 
  389              k+1, current_state%column_local_y, current_state%column_local_x)-liquid_water_at_kp1)
 
  395         moist_ri_1(k) = ((th%data(k+1, current_state%column_local_y, current_state%column_local_x)+&
 
  396              current_state%global_grid%configuration%vertical%thref(k+1) - temperature_at_kp1*&
 
  397              current_state%global_grid%configuration%vertical%prefrcp(k+1))&
 
  398              +current_state%global_grid%configuration%vertical%thref(k+1)*qloading)*scltmp*tmpinv
 
  411     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  412     type(prognostic_field_type), 
intent(inout) :: u, v, w
 
  416     real(kind=default_precision) :: ssq11, ssq22, ssq33, ssq13, ssq23, ssq12
 
  418     do k=2,current_state%local_grid%size(z_index)-1   
 
  420       ssq11=current_state%global_grid%configuration%horizontal%cx2*(&
 
  421            (u%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  422            u%data(k+1, current_state%column_local_y, current_state%column_local_x-1))**2+&
 
  423            (u%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  424            u%data(k, current_state%column_local_y, current_state%column_local_x-1))**2)
 
  426       ssq11=0.0_default_precision
 
  429       ssq22=current_state%global_grid%configuration%horizontal%cy2*(&
 
  430            (v%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  431            v%data(k+1, current_state%column_local_y-1, current_state%column_local_x))**2+&
 
  432            (v%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  433            v%data(k, current_state%column_local_y-1, current_state%column_local_x))**2)
 
  435       ssq22=0.0_default_precision
 
  438       ssq33=((w%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  439            w%data(k-1, current_state%column_local_y, current_state%column_local_x))*&
 
  440            current_state%global_grid%configuration%vertical%rdz(k))**2 +&
 
  441            ((w%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  442            w%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  443            current_state%global_grid%configuration%vertical%rdz(k+1))**2
 
  445       ssq33=0.0_default_precision
 
  447 #if defined(U_ACTIVE) && defined(W_ACTIVE) 
  449       ssq13=(((u%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  450            u%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  451            current_state%global_grid%configuration%vertical%rdzn(k+1)+&
 
  452            (w%data(k, current_state%column_local_y, current_state%column_local_x+1)-&
 
  453            w%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  454            current_state%global_grid%configuration%horizontal%cx)**2+&
 
  455            ((u%data(k+1, current_state%column_local_y, current_state%column_local_x-1)-&
 
  456            u%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  457            current_state%global_grid%configuration%vertical%rdzn(k+1)+&
 
  458            (w%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  459            w%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  460            current_state%global_grid%configuration%horizontal%cx)**2)*0.5_default_precision
 
  461 #elif defined(U_ACTIVE) && !defined(W_ACTIVE) 
  462       ssq13=(((u%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  463            u%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  464            current_state%global_grid%configuration%vertical%rdzn(k+1))**2+&
 
  465            ((u%data(k+1, current_state%column_local_y, current_state%column_local_x-1)-&
 
  466            u%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  467            current_state%global_grid%configuration%vertical%rdzn(k+1))**2)*0.5_default_precision
 
  468 #elif !defined(U_ACTIVE) && defined(W_ACTIVE) 
  469       ssq13=(((w%data(k, current_state%column_local_y, current_state%column_local_x+1)-&
 
  470            w%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  471            current_state%global_grid%configuration%horizontal%cx)**2+&
 
  472            ((w%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  473            w%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  474            current_state%global_grid%configuration%horizontal%cx)**2)*0.5_default_precision
 
  476       ssq13=0.0_default_precision
 
  478 #if defined(W_ACTIVE) && defined(V_ACTIVE) 
  480       ssq23=(((w%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  481            w%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  482            current_state%global_grid%configuration%horizontal%cy+&
 
  483            (v%data(k+1, current_state%column_local_y-1, current_state%column_local_x)-&
 
  484            v%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  485            current_state%global_grid%configuration%vertical%rdzn(k+1))**2+&
 
  486            ((w%data(k, current_state%column_local_y+1, current_state%column_local_x)-&
 
  487            w%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  488            current_state%global_grid%configuration%horizontal%cy+&
 
  489            (v%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  490            v%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  491            current_state%global_grid%configuration%vertical%rdzn(k+1))**2)*0.5_default_precision
 
  492 #elif defined(W_ACTIVE) && !defined(V_ACTIVE) 
  493       ssq23=(((w%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  494            w%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  495            current_state%global_grid%configuration%horizontal%cy)**2+&
 
  496            ((w%data(k, current_state%column_local_y+1, current_state%column_local_x)-&
 
  497            w%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  498            current_state%global_grid%configuration%horizontal%cy)**2)*0.5_default_precision
 
  499 #elif !defined(W_ACTIVE) && defined(V_ACTIVE) 
  500       ssq23=(((v%data(k+1, current_state%column_local_y-1, current_state%column_local_x)-&
 
  501            v%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  502            current_state%global_grid%configuration%vertical%rdzn(k+1))**2+&
 
  503            ((v%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  504            v%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  505            current_state%global_grid%configuration%vertical%rdzn(k+1))**2)*0.5_default_precision
 
  507       ssq23=0.0_default_precision
 
  510 #if defined(U_ACTIVE) && defined(V_ACTIVE) 
  512       ssq12=(((((u%data(k, current_state%column_local_y, current_state%column_local_x-1)-&
 
  513            u%data(k, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  514            current_state%global_grid%configuration%horizontal%cy+&
 
  515            (v%data(k, current_state%column_local_y-1, current_state%column_local_x)-&
 
  516            v%data(k, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  517            current_state%global_grid%configuration%horizontal%cx)**2 +&
 
  518            ((u%data(k, current_state%column_local_y+1, current_state%column_local_x-1)-&
 
  519            u%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  520            current_state%global_grid%configuration%horizontal%cy+&
 
  521            (v%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  522            v%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  523            current_state%global_grid%configuration%horizontal%cx)**2) +(&
 
  524            ((u%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  525            u%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  526            current_state%global_grid%configuration%horizontal%cy+&
 
  527            (v%data(k, current_state%column_local_y-1, current_state%column_local_x+1)-&
 
  528            v%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  529            current_state%global_grid%configuration%horizontal%cx)**2 +&
 
  530            ((u%data(k, current_state%column_local_y+1, current_state%column_local_x)-&
 
  531            u%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  532            current_state%global_grid%configuration%horizontal%cy+&
 
  533            (v%data(k, current_state%column_local_y, current_state%column_local_x+1)-&
 
  534            v%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  535            current_state%global_grid%configuration%horizontal%cx)**2))+((&
 
  536            ((u%data(k+1, current_state%column_local_y, current_state%column_local_x-1)-&
 
  537            u%data(k+1, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  538            current_state%global_grid%configuration%horizontal%cy+&
 
  539            (v%data(k+1, current_state%column_local_y-1, current_state%column_local_x)-&
 
  540            v%data(k+1, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  541            current_state%global_grid%configuration%horizontal%cx)**2+&
 
  542            ((u%data(k+1, current_state%column_local_y+1, current_state%column_local_x-1)-&
 
  543            u%data(k+1, current_state%column_local_y, current_state%column_local_x-1))*&
 
  544            current_state%global_grid%configuration%horizontal%cy+&
 
  545            (v%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  546            v%data(k+1, current_state%column_local_y, current_state%column_local_x-1))*&
 
  547            current_state%global_grid%configuration%horizontal%cx)**2)+(&
 
  548            ((u%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  549            u%data(k+1, current_state%column_local_y-1, current_state%column_local_x))*&
 
  550            current_state%global_grid%configuration%horizontal%cy+&
 
  551            (v%data(k+1, current_state%column_local_y-1, current_state%column_local_x+1)-&
 
  552            v%data(k+1, current_state%column_local_y-1, current_state%column_local_x))*&
 
  553            current_state%global_grid%configuration%horizontal%cx)**2+&
 
  554            ((u%data(k+1, current_state%column_local_y+1, current_state%column_local_x)-&
 
  555            u%data(k+1, current_state%column_local_y, current_state%column_local_x))*&
 
  556            current_state%global_grid%configuration%horizontal%cy+&
 
  557            (v%data(k+1, current_state%column_local_y, current_state%column_local_x+1)-&
 
  558            v%data(k+1, current_state%column_local_y, current_state%column_local_x))*&
 
  559            current_state%global_grid%configuration%horizontal%cx)**2)))*0.125_default_precision
 
  561 #elif defined(U_ACTIVE) && !defined(V_ACTIVE) 
  563       ssq12=(((((u%data(k, current_state%column_local_y, current_state%column_local_x-1)-&
 
  564            u%data(k, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  565            current_state%global_grid%configuration%horizontal%cy)**2 +&
 
  566            ((u%data(k, current_state%column_local_y+1, current_state%column_local_x-1)-&
 
  567            u%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  568            current_state%global_grid%configuration%horizontal%cy)**2) +(&
 
  569            ((u%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  570            u%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  571            current_state%global_grid%configuration%horizontal%cy)**2 +&
 
  572            ((u%data(k, current_state%column_local_y+1, current_state%column_local_x)-&
 
  573            u%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  574            current_state%global_grid%configuration%horizontal%cy)**2))+((&
 
  575            ((u%data(k+1, current_state%column_local_y, current_state%column_local_x-1)-&
 
  576            u%data(k+1, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  577            current_state%global_grid%configuration%horizontal%cy)**2+&
 
  578            ((u%data(k+1, current_state%column_local_y+1, current_state%column_local_x-1)-&
 
  579            u%data(k+1, current_state%column_local_y, current_state%column_local_x-1))*&
 
  580            current_state%global_grid%configuration%horizontal%cy)**2)+(&
 
  581            ((u%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  582            u%data(k+1, current_state%column_local_y-1, current_state%column_local_x))*&
 
  583            current_state%global_grid%configuration%horizontal%cy)**2+&
 
  584            ((u%data(k+1, current_state%column_local_y+1, current_state%column_local_x)-&
 
  585            u%data(k+1, current_state%column_local_y, current_state%column_local_x))*&
 
  586            current_state%global_grid%configuration%horizontal%cy)**2)))*0.125_default_precision
 
  588 #elif !defined(U_ACTIVE) && defined(V_ACTIVE) 
  590       ssq12=(((((v%data(k, current_state%column_local_y-1, current_state%column_local_x)-&
 
  591            v%data(k, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  592            current_state%global_grid%configuration%horizontal%cx)**2 +&
 
  593            ((v%data(k, current_state%column_local_y, current_state%column_local_x)-&
 
  594            v%data(k, current_state%column_local_y, current_state%column_local_x-1))*&
 
  595            current_state%global_grid%configuration%horizontal%cx)**2) +&
 
  596            (((v%data(k, current_state%column_local_y-1, current_state%column_local_x+1)-&
 
  597            v%data(k, current_state%column_local_y-1, current_state%column_local_x))*&
 
  598            current_state%global_grid%configuration%horizontal%cx)**2 +&
 
  599            ((v%data(k, current_state%column_local_y, current_state%column_local_x+1)-&
 
  600            v%data(k, current_state%column_local_y, current_state%column_local_x))*&
 
  601            current_state%global_grid%configuration%horizontal%cx)**2))+((&
 
  602            ((v%data(k+1, current_state%column_local_y-1, current_state%column_local_x)-&
 
  603            v%data(k+1, current_state%column_local_y-1, current_state%column_local_x-1))*&
 
  604            current_state%global_grid%configuration%horizontal%cx)**2+&
 
  605            ((v%data(k+1, current_state%column_local_y, current_state%column_local_x)-&
 
  606            v%data(k+1, current_state%column_local_y, current_state%column_local_x-1))*&
 
  607            current_state%global_grid%configuration%horizontal%cx)**2)+(&
 
  608            ((v%data(k+1, current_state%column_local_y-1, current_state%column_local_x+1)-&
 
  609            v%data(k+1, current_state%column_local_y-1, current_state%column_local_x))*&
 
  610            current_state%global_grid%configuration%horizontal%cx)**2+&
 
  611            ((v%data(k+1, current_state%column_local_y, current_state%column_local_x+1)-&
 
  612            v%data(k+1, current_state%column_local_y, current_state%column_local_x))*&
 
  613            current_state%global_grid%configuration%horizontal%cx)**2)))*0.125_default_precision
 
  615       ssq12=0.0_default_precision
 
  625     type(model_state_type), 
target, 
intent(inout) :: current_state
 
  626     type(prognostic_field_type), 
intent(inout) :: th
 
  631     do k=2,current_state%local_grid%size(z_index)-1
 
  633         current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x) * ( &
 
  634           (current_state%global_grid%configuration%vertical%rdzn(k+1) * &
 
  635             (current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x) - &
 
  636              current_state%th%data(k, current_state%column_local_y, current_state%column_local_x) - &
 
  637              current_state%global_grid%configuration%vertical%dthref(k) ) ) ** 2 + &
 
  638           0.25 * current_state%global_grid%configuration%horizontal%cx2 * &
 
  639             ( (current_state%th%data(k, current_state%column_local_y, current_state%column_local_x+1) - &
 
  640                current_state%th%data(k, current_state%column_local_y, current_state%column_local_x) ) ** 2 + &
 
  641               (current_state%th%data(k, current_state%column_local_y, current_state%column_local_x) - &
 
  642                current_state%th%data(k, current_state%column_local_y, current_state%column_local_x-1) ) ** 2 + &
 
  643               (current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x+1) - &
 
  644                current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x) ) **2 + &
 
  645               (current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x) - &
 
  646                current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x-1) ) ** 2 ) + &
 
  647           0.25 * current_state%global_grid%configuration%horizontal%cy2 * &
 
  648             ( (current_state%th%data(k, current_state%column_local_y+1, current_state%column_local_x) - &
 
  649                current_state%th%data(k, current_state%column_local_y, current_state%column_local_x) ) ** 2 + &
 
  650               (current_state%th%data(k, current_state%column_local_y, current_state%column_local_x) - &
 
  651                current_state%th%data(k, current_state%column_local_y-1, current_state%column_local_x) ) ** 2 + &
 
  652               (current_state%th%data(k+1, current_state%column_local_y+1, current_state%column_local_x) - &
 
  653                current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x) ) **2 + &
 
  654               (current_state%th%data(k+1, current_state%column_local_y, current_state%column_local_x) - &
 
  655                current_state%th%data(k+1, current_state%column_local_y-1, current_state%column_local_x) ) ** 2 ) )
 
  671        pid_location, current_page, source_data)
 
  672     type(model_state_type), 
intent(inout) :: current_state
 
  673     integer, 
intent(in) :: dim, pid_location, source_index
 
  674     integer, 
intent(inout) :: current_page(:)
 
  675     type(neighbour_description_type), 
intent(inout) :: neighbour_description
 
  676     type(field_data_wrapper_type), 
dimension(:), 
intent(in), 
optional :: source_data
 
  678     call copy_field_to_buffer(current_state%local_grid, neighbour_description%send_halo_buffer, &
 
  679          current_state%vis_coefficient%data, dim, source_index, current_page(pid_location))
 
  681     current_page(pid_location)=current_page(pid_location)+1
 
  694        pid_location, current_page, source_data)
 
  695     type(model_state_type), 
intent(inout) :: current_state
 
  696     integer, 
intent(in) :: corner_loc, pid_location, x_source_index, y_source_index
 
  697     integer, 
intent(inout) :: current_page(:)
 
  698     type(neighbour_description_type), 
intent(inout) :: neighbour_description
 
  699     type(field_data_wrapper_type), 
dimension(:), 
intent(in), 
optional :: source_data
 
  701     call copy_corner_to_buffer(current_state%local_grid, neighbour_description%send_corner_buffer, &
 
  702          current_state%vis_coefficient%data, corner_loc, x_source_index, y_source_index, current_page(pid_location))
 
  704     current_page(pid_location)=current_page(pid_location)+1
 
  716        pid_location, current_page, source_data)
 
  717     type(model_state_type), 
intent(inout) :: current_state
 
  718     integer, 
intent(in) :: dim, pid_location, source_index
 
  719     integer, 
intent(inout) :: current_page(:)
 
  720     type(neighbour_description_type), 
intent(inout) :: neighbour_description
 
  721     type(field_data_wrapper_type), 
dimension(:), 
intent(in), 
optional :: source_data
 
  723     call copy_field_to_buffer(current_state%local_grid, neighbour_description%send_halo_buffer, &
 
  724          current_state%diff_coefficient%data, dim, source_index, current_page(pid_location))
 
  726     current_page(pid_location)=current_page(pid_location)+1
 
  739        pid_location, current_page, source_data)
 
  740     type(model_state_type), 
intent(inout) :: current_state
 
  741     integer, 
intent(in) :: corner_loc, pid_location, x_source_index, y_source_index
 
  742     integer, 
intent(inout) :: current_page(:)
 
  743     type(neighbour_description_type), 
intent(inout) :: neighbour_description
 
  744     type(field_data_wrapper_type), 
dimension(:), 
intent(in), 
optional :: source_data
 
  746     call copy_corner_to_buffer(current_state%local_grid, neighbour_description%send_corner_buffer, &
 
  747          current_state%diff_coefficient%data, corner_loc, x_source_index, y_source_index, current_page(pid_location))
 
  749     current_page(pid_location)=current_page(pid_location)+1