Ignore:
Timestamp:
Nov 21, 2018 1:21:24 PM (5 years ago)
Author:
suehring
Message:

variable description added some routines

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/advec_ws.f90

    r3467 r3547  
    2525! -----------------
    2626! $Id$
     27! variables documented
     28!
     29! 3467 2018-10-30 19:05:21Z suehring
    2730! Implementation of a new aerosol module salsa.
    2831!
     
    11941197       IMPLICIT NONE
    11951198
    1196        CHARACTER (LEN = *), INTENT(IN) ::  sk_char !<
     1199       CHARACTER (LEN = *), INTENT(IN) ::  sk_char !< string identifier, used for assign fluxes to the correct dimension in the analysis array
    11971200       
    1198        INTEGER(iwp) ::  i     !<
    1199        INTEGER(iwp) ::  ibit0 !<
    1200        INTEGER(iwp) ::  ibit1 !<
    1201        INTEGER(iwp) ::  ibit2 !<
    1202        INTEGER(iwp) ::  ibit3 !<
    1203        INTEGER(iwp) ::  ibit4 !<
    1204        INTEGER(iwp) ::  ibit5 !<
    1205        INTEGER(iwp) ::  ibit6 !<
    1206        INTEGER(iwp) ::  ibit7 !<
    1207        INTEGER(iwp) ::  ibit8 !<
    1208        INTEGER(iwp) ::  i_omp !<
    1209        INTEGER(iwp) ::  j     !<
    1210        INTEGER(iwp) ::  k     !<
    1211        INTEGER(iwp) ::  k_mm  !<
    1212        INTEGER(iwp) ::  k_pp  !<
    1213        INTEGER(iwp) ::  k_ppp !<
    1214        INTEGER(iwp) ::  tn    !<
     1201       INTEGER(iwp) ::  i     !< grid index along x-direction
     1202       INTEGER(iwp) ::  ibit0 !< flag indicating 1st-order scheme along x-direction
     1203       INTEGER(iwp) ::  ibit1 !< flag indicating 3rd-order scheme along x-direction
     1204       INTEGER(iwp) ::  ibit2 !< flag indicating 5th-order scheme along x-direction
     1205       INTEGER(iwp) ::  ibit3 !< flag indicating 1st-order scheme along y-direction
     1206       INTEGER(iwp) ::  ibit4 !< flag indicating 3rd-order scheme along y-direction
     1207       INTEGER(iwp) ::  ibit5 !< flag indicating 5th-order scheme along y-direction
     1208       INTEGER(iwp) ::  ibit6 !< flag indicating 1st-order scheme along z-direction
     1209       INTEGER(iwp) ::  ibit7 !< flag indicating 3rd-order scheme along z-direction
     1210       INTEGER(iwp) ::  ibit8 !< flag indicating 5th-order scheme along z-direction
     1211       INTEGER(iwp) ::  i_omp !< leftmost index on subdomain, or in case of OpenMP, on thread
     1212       INTEGER(iwp) ::  j     !< grid index along y-direction
     1213       INTEGER(iwp) ::  k     !< grid index along z-direction
     1214       INTEGER(iwp) ::  k_mm  !< k-2 index in disretization, can be modified to avoid segmentation faults
     1215       INTEGER(iwp) ::  k_pp  !< k+2 index in disretization, can be modified to avoid segmentation faults
     1216       INTEGER(iwp) ::  k_ppp !< k+3 index in disretization, can be modified to avoid segmentation faults
     1217       INTEGER(iwp) ::  tn    !< number of OpenMP thread
    12151218       
    1216        REAL(wp)     ::  diss_d !<
    1217        REAL(wp)     ::  div    !<
    1218        REAL(wp)     ::  flux_d !<
    1219        REAL(wp)     ::  u_comp !<
    1220        REAL(wp)     ::  v_comp !<
     1219       REAL(wp)     ::  diss_d !< artificial dissipation term at grid box bottom
     1220       REAL(wp)     ::  div    !< diverence on scalar grid
     1221       REAL(wp)     ::  flux_d !< 6th-order flux at grid box bottom
     1222       REAL(wp)     ::  u_comp !< advection velocity along x-direction
     1223       REAL(wp)     ::  v_comp !< advection velocity along y-direction
    12211224       
    12221225#if defined( __nopointer )
    1223        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
     1226       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !< advected scalar
    12241227#else
    1225        REAL(wp), DIMENSION(:,:,:), POINTER    ::  sk     !<
     1228       REAL(wp), DIMENSION(:,:,:), POINTER    ::  sk     !< advected scalar
    12261229#endif
    1227        REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_n !<
    1228        REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_r !<
    1229        REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_t !<
    1230        REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_n !<
    1231        REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_r !<
    1232        REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_t !<
     1230       REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     1231       REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_r !< discretized artificial dissipation at rightward-side of the grid box
     1232       REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_t !< discretized artificial dissipation at top of the grid box
     1233       REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     1234       REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     1235       REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_t !< discretized 6th-order flux at top of the grid box
    12331236       
    1234        REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  swap_diss_y_local !<
    1235        REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  swap_flux_y_local !<
     1237       REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  swap_diss_y_local !< discretized artificial dissipation at southward-side of the grid box
     1238       REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  swap_flux_y_local !< discretized 6th-order flux at northward-side of the grid box
    12361239       
    1237        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  swap_diss_x_local !<
    1238        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  swap_flux_x_local !<
     1240       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  swap_diss_x_local !< discretized artificial dissipation at leftward-side of the grid box
     1241       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  swap_flux_x_local !< discretized 6th-order flux at leftward-side of the grid box
    12391242       
    12401243
     
    17731776       IMPLICIT NONE
    17741777
    1775        INTEGER(iwp) ::  i      !<
    1776        INTEGER(iwp) ::  ibit9  !<
    1777        INTEGER(iwp) ::  ibit10 !<
    1778        INTEGER(iwp) ::  ibit11 !<
    1779        INTEGER(iwp) ::  ibit12 !<
    1780        INTEGER(iwp) ::  ibit13 !<
    1781        INTEGER(iwp) ::  ibit14 !<
    1782        INTEGER(iwp) ::  ibit15 !<
    1783        INTEGER(iwp) ::  ibit16 !<
    1784        INTEGER(iwp) ::  ibit17 !<
    1785        INTEGER(iwp) ::  i_omp  !<
    1786        INTEGER(iwp) ::  j      !<
    1787        INTEGER(iwp) ::  k      !<
    1788        INTEGER(iwp) ::  k_mm   !<
    1789        INTEGER(iwp) ::  k_pp   !<
    1790        INTEGER(iwp) ::  k_ppp  !<
    1791        INTEGER(iwp) ::  tn     !<
     1778       INTEGER(iwp) ::  i      !< grid index along x-direction
     1779       INTEGER(iwp) ::  ibit9  !< flag indicating 1st-order scheme along x-direction
     1780       INTEGER(iwp) ::  ibit10 !< flag indicating 3rd-order scheme along x-direction
     1781       INTEGER(iwp) ::  ibit11 !< flag indicating 5th-order scheme along x-direction
     1782       INTEGER(iwp) ::  ibit12 !< flag indicating 1st-order scheme along y-direction
     1783       INTEGER(iwp) ::  ibit13 !< flag indicating 3rd-order scheme along y-direction
     1784       INTEGER(iwp) ::  ibit14 !< flag indicating 5th-order scheme along y-direction
     1785       INTEGER(iwp) ::  ibit15 !< flag indicating 1st-order scheme along z-direction
     1786       INTEGER(iwp) ::  ibit16 !< flag indicating 3rd-order scheme along z-direction
     1787       INTEGER(iwp) ::  ibit17 !< flag indicating 5th-order scheme along z-direction
     1788       INTEGER(iwp) ::  i_omp  !< leftmost index on subdomain, or in case of OpenMP, on thread
     1789       INTEGER(iwp) ::  j      !< grid index along y-direction
     1790       INTEGER(iwp) ::  k      !< grid index along z-direction
     1791       INTEGER(iwp) ::  k_mm   !< k-2 index in disretization, can be modified to avoid segmentation faults
     1792       INTEGER(iwp) ::  k_pp   !< k+2 index in disretization, can be modified to avoid segmentation faults
     1793       INTEGER(iwp) ::  k_ppp  !< k+3 index in disretization, can be modified to avoid segmentation faults
     1794       INTEGER(iwp) ::  tn     !< number of OpenMP thread
    17921795       
    1793        REAL(wp)    ::  diss_d   !<
    1794        REAL(wp)    ::  div      !<
    1795        REAL(wp)    ::  flux_d   !<
    1796        REAL(wp)    ::  gu       !<
    1797        REAL(wp)    ::  gv       !<
    1798        REAL(wp)    ::  u_comp_l !<
     1796       REAL(wp)    ::  diss_d   !< artificial dissipation term at grid box bottom
     1797       REAL(wp)    ::  div      !< diverence on u-grid
     1798       REAL(wp)    ::  flux_d   !< 6th-order flux at grid box bottom
     1799       REAL(wp)    ::  gu       !< Galilei-transformation velocity along x
     1800       REAL(wp)    ::  gv       !< Galilei-transformation velocity along y
     1801       REAL(wp)    ::  u_comp_l !< advection velocity along x at leftmost grid point on subdomain
    17991802       
    1800        REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_n !<
    1801        REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_r !<
    1802        REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_t !<
    1803        REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_n !<
    1804        REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_r !<
    1805        REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_t !<
    1806        REAL(wp), DIMENSION(nzb:nzt+1) ::  u_comp !<
    1807        REAL(wp), DIMENSION(nzb:nzt+1) ::  v_comp !<
    1808        REAL(wp), DIMENSION(nzb:nzt+1) ::  w_comp !<
     1803       REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     1804       REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_r !< discretized artificial dissipation at rightward-side of the grid box
     1805       REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_t !< discretized artificial dissipation at top of the grid box
     1806       REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     1807       REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     1808       REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_t !< discretized 6th-order flux at top of the grid box
     1809       REAL(wp), DIMENSION(nzb:nzt+1) ::  u_comp !< advection velocity along x
     1810       REAL(wp), DIMENSION(nzb:nzt+1) ::  v_comp !< advection velocity along y
     1811       REAL(wp), DIMENSION(nzb:nzt+1) ::  w_comp !< advection velocity along z
    18091812
    18101813       gu = 2.0_wp * u_gtrans
     
    22682271       IMPLICIT NONE
    22692272
    2270        INTEGER(iwp)  ::  i      !<
    2271        INTEGER(iwp)  ::  ibit18 !<
    2272        INTEGER(iwp)  ::  ibit19 !<
    2273        INTEGER(iwp)  ::  ibit20 !<
    2274        INTEGER(iwp)  ::  ibit21 !<
    2275        INTEGER(iwp)  ::  ibit22 !<
    2276        INTEGER(iwp)  ::  ibit23 !<
    2277        INTEGER(iwp)  ::  ibit24 !<
    2278        INTEGER(iwp)  ::  ibit25 !<
    2279        INTEGER(iwp)  ::  ibit26 !<
    2280        INTEGER(iwp)  ::  i_omp  !<
    2281        INTEGER(iwp)  ::  j      !<
    2282        INTEGER(iwp)  ::  k      !<
    2283        INTEGER(iwp)  ::  k_mm   !<
    2284        INTEGER(iwp)  ::  k_pp   !<
    2285        INTEGER(iwp)  ::  k_ppp  !<
    2286        INTEGER(iwp)  ::  tn     !<
     2273       INTEGER(iwp)  ::  i      !< grid index along x-direction
     2274       INTEGER(iwp)  ::  ibit18 !< flag indicating 1st-order scheme along x-direction
     2275       INTEGER(iwp)  ::  ibit19 !< flag indicating 3rd-order scheme along x-direction
     2276       INTEGER(iwp)  ::  ibit20 !< flag indicating 5th-order scheme along x-direction
     2277       INTEGER(iwp)  ::  ibit21 !< flag indicating 1st-order scheme along y-direction
     2278       INTEGER(iwp)  ::  ibit22 !< flag indicating 3rd-order scheme along y-direction
     2279       INTEGER(iwp)  ::  ibit23 !< flag indicating 3rd-order scheme along y-direction
     2280       INTEGER(iwp)  ::  ibit24 !< flag indicating 1st-order scheme along z-direction
     2281       INTEGER(iwp)  ::  ibit25 !< flag indicating 3rd-order scheme along z-direction
     2282       INTEGER(iwp)  ::  ibit26 !< flag indicating 3rd-order scheme along z-direction
     2283       INTEGER(iwp)  ::  i_omp  !< leftmost index on subdomain, or in case of OpenMP, on thread
     2284       INTEGER(iwp)  ::  j      !< grid index along y-direction
     2285       INTEGER(iwp)  ::  k      !< grid index along z-direction
     2286       INTEGER(iwp)  ::  k_mm   !< k-2 index in disretization, can be modified to avoid segmentation faults
     2287       INTEGER(iwp)  ::  k_pp   !< k+2 index in disretization, can be modified to avoid segmentation faults
     2288       INTEGER(iwp)  ::  k_ppp  !< k+3 index in disretization, can be modified to avoid segmentation faults
     2289       INTEGER(iwp)  ::  tn     !< number of OpenMP thread
    22872290       
    2288        REAL(wp)     ::  diss_d   !<
    2289        REAL(wp)     ::  div      !<
    2290        REAL(wp)     ::  flux_d   !<
    2291        REAL(wp)     ::  gu       !<
    2292        REAL(wp)     ::  gv       !<
    2293        REAL(wp)     ::  v_comp_l !<
     2291       REAL(wp)     ::  diss_d   !< artificial dissipation term at grid box bottom
     2292       REAL(wp)     ::  div      !< divergence on v-grid
     2293       REAL(wp)     ::  flux_d   !< 6th-order flux at grid box bottom
     2294       REAL(wp)     ::  gu       !< Galilei-transformation velocity along x
     2295       REAL(wp)     ::  gv       !< Galilei-transformation velocity along y
     2296       REAL(wp)     ::  v_comp_l !< advection velocity along y on leftmost grid point on subdomain
    22942297       
    2295        REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_n !<
    2296        REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_r !<
    2297        REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_t !<
    2298        REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_n !<
    2299        REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_r !<
    2300        REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_t !<
    2301        REAL(wp), DIMENSION(nzb:nzt+1)  ::  u_comp !<
    2302        REAL(wp), DIMENSION(nzb:nzt+1)  ::  v_comp !<
    2303        REAL(wp), DIMENSION(nzb:nzt+1)  ::  w_comp !<
     2298       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     2299       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_r !< discretized artificial dissipation at rightward-side of the grid box
     2300       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_t !< discretized artificial dissipation at top of the grid box
     2301       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     2302       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     2303       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_t !< discretized 6th-order flux at top of the grid box
     2304       REAL(wp), DIMENSION(nzb:nzt+1)  ::  u_comp !< advection velocity along x
     2305       REAL(wp), DIMENSION(nzb:nzt+1)  ::  v_comp !< advection velocity along y
     2306       REAL(wp), DIMENSION(nzb:nzt+1)  ::  w_comp !< advection velocity along z
    23042307
    23052308       gu = 2.0_wp * u_gtrans
     
    27702773       IMPLICIT NONE
    27712774
    2772        INTEGER(iwp) ::  i      !<
    2773        INTEGER(iwp) ::  ibit27 !<
    2774        INTEGER(iwp) ::  ibit28 !<
    2775        INTEGER(iwp) ::  ibit29 !<
    2776        INTEGER(iwp) ::  ibit30 !<
    2777        INTEGER(iwp) ::  ibit31 !<
    2778        INTEGER(iwp) ::  ibit32 !<
    2779        INTEGER(iwp) ::  ibit33 !<
    2780        INTEGER(iwp) ::  ibit34 !<
    2781        INTEGER(iwp) ::  ibit35 !<
    2782        INTEGER(iwp) ::  i_omp  !<
    2783        INTEGER(iwp) ::  j      !<
    2784        INTEGER(iwp) ::  k      !<
    2785        INTEGER(iwp) ::  k_mm   !<
    2786        INTEGER(iwp) ::  k_pp   !<
    2787        INTEGER(iwp) ::  k_ppp  !<
    2788        INTEGER(iwp) ::  tn     !<
     2775       INTEGER(iwp) ::  i      !< grid index along x-direction
     2776       INTEGER(iwp) ::  ibit27 !< flag indicating 1st-order scheme along x-direction
     2777       INTEGER(iwp) ::  ibit28 !< flag indicating 3rd-order scheme along x-direction
     2778       INTEGER(iwp) ::  ibit29 !< flag indicating 5th-order scheme along x-direction
     2779       INTEGER(iwp) ::  ibit30 !< flag indicating 1st-order scheme along y-direction
     2780       INTEGER(iwp) ::  ibit31 !< flag indicating 3rd-order scheme along y-direction
     2781       INTEGER(iwp) ::  ibit32 !< flag indicating 5th-order scheme along y-direction
     2782       INTEGER(iwp) ::  ibit33 !< flag indicating 1st-order scheme along z-direction
     2783       INTEGER(iwp) ::  ibit34 !< flag indicating 3rd-order scheme along z-direction
     2784       INTEGER(iwp) ::  ibit35 !< flag indicating 5th-order scheme along z-direction
     2785       INTEGER(iwp) ::  i_omp  !< leftmost index on subdomain, or in case of OpenMP, on thread
     2786       INTEGER(iwp) ::  j      !< grid index along y-direction
     2787       INTEGER(iwp) ::  k      !< grid index along z-direction
     2788       INTEGER(iwp) ::  k_mm   !< k-2 index in disretization, can be modified to avoid segmentation faults
     2789       INTEGER(iwp) ::  k_pp   !< k+2 index in disretization, can be modified to avoid segmentation faults
     2790       INTEGER(iwp) ::  k_ppp  !< k+3 index in disretization, can be modified to avoid segmentation faults
     2791       INTEGER(iwp) ::  tn     !< number of OpenMP thread
    27892792       
    2790        REAL(wp)    ::  diss_d  !<
    2791        REAL(wp)    ::  div     !<
    2792        REAL(wp)    ::  flux_d  !<
    2793        REAL(wp)    ::  gu      !<
    2794        REAL(wp)    ::  gv      !<
     2793       REAL(wp)    ::  diss_d  !< discretized artificial dissipation at top of the grid box
     2794       REAL(wp)    ::  div     !< divergence on w-grid
     2795       REAL(wp)    ::  flux_d  !< discretized 6th-order flux at top of the grid box
     2796       REAL(wp)    ::  gu      !< Galilei-transformation velocity along x
     2797       REAL(wp)    ::  gv      !< Galilei-transformation velocity along y
    27952798       
    2796        REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_n !<
    2797        REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_r !<
    2798        REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_t !<
    2799        REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_n !<
    2800        REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_r !<
    2801        REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_t !<
    2802        REAL(wp), DIMENSION(nzb:nzt+1)  ::  u_comp !<
    2803        REAL(wp), DIMENSION(nzb:nzt+1)  ::  v_comp !<
    2804        REAL(wp), DIMENSION(nzb:nzt+1)  ::  w_comp !<
     2799       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     2800       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_r !< discretized artificial dissipation at rightward-side of the grid box
     2801       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_t !< discretized artificial dissipation at top of the grid box
     2802       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     2803       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     2804       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_t !< discretized 6th-order flux at top of the grid box
     2805       REAL(wp), DIMENSION(nzb:nzt+1)  ::  u_comp !< advection velocity along x
     2806       REAL(wp), DIMENSION(nzb:nzt+1)  ::  v_comp !< advection velocity along y
     2807       REAL(wp), DIMENSION(nzb:nzt+1)  ::  w_comp !< advection velocity along z
    28052808
    28062809       gu = 2.0_wp * u_gtrans
     
    32543257       IMPLICIT NONE
    32553258
    3256        CHARACTER (LEN = *), INTENT(IN)    ::  sk_char !<
     3259       CHARACTER (LEN = *), INTENT(IN)    ::  sk_char !< string identifier, used for assign fluxes to the correct dimension in the analysis array
    32573260       
    3258        INTEGER(iwp) ::  i      !<
    3259        INTEGER(iwp) ::  ibit0  !<
    3260        INTEGER(iwp) ::  ibit1  !<
    3261        INTEGER(iwp) ::  ibit2  !<
    3262        INTEGER(iwp) ::  ibit3  !<
    3263        INTEGER(iwp) ::  ibit4  !<
    3264        INTEGER(iwp) ::  ibit5  !<
    3265        INTEGER(iwp) ::  ibit6  !<
    3266        INTEGER(iwp) ::  ibit7  !<
    3267        INTEGER(iwp) ::  ibit8  !<
    3268        INTEGER(iwp) ::  j      !<
    3269        INTEGER(iwp) ::  k      !<
    3270        INTEGER(iwp) ::  k_mm   !<
    3271        INTEGER(iwp) ::  k_pp   !<
    3272        INTEGER(iwp) ::  k_ppp  !<
    3273        INTEGER(iwp) ::  tn = 0 !<
     3261       INTEGER(iwp) ::  i      !< grid index along x-direction
     3262       INTEGER(iwp) ::  ibit0  !< flag indicating 1st-order scheme along x-direction
     3263       INTEGER(iwp) ::  ibit1  !< flag indicating 3rd-order scheme along x-direction
     3264       INTEGER(iwp) ::  ibit2  !< flag indicating 5th-order scheme along x-direction
     3265       INTEGER(iwp) ::  ibit3  !< flag indicating 1st-order scheme along y-direction
     3266       INTEGER(iwp) ::  ibit4  !< flag indicating 3rd-order scheme along y-direction
     3267       INTEGER(iwp) ::  ibit5  !< flag indicating 5th-order scheme along y-direction
     3268       INTEGER(iwp) ::  ibit6  !< flag indicating 1st-order scheme along z-direction
     3269       INTEGER(iwp) ::  ibit7  !< flag indicating 3rd-order scheme along z-direction
     3270       INTEGER(iwp) ::  ibit8  !< flag indicating 5th-order scheme along z-direction
     3271       INTEGER(iwp) ::  j      !< grid index along y-direction
     3272       INTEGER(iwp) ::  k      !< grid index along z-direction
     3273       INTEGER(iwp) ::  k_mm   !< k-2 index in disretization, can be modified to avoid segmentation faults
     3274       INTEGER(iwp) ::  k_pp   !< k+2 index in disretization, can be modified to avoid segmentation faults
     3275       INTEGER(iwp) ::  k_ppp  !< k+3 index in disretization, can be modified to avoid segmentation faults
     3276       INTEGER(iwp) ::  tn = 0 !< number of OpenMP thread
    32743277       
    32753278#if defined( __nopointer )
    3276        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
     3279       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !< advected scalar
    32773280#else
    3278        REAL(wp), DIMENSION(:,:,:), POINTER ::  sk !<
     3281       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk !< advected scalar
    32793282#endif
    32803283
    3281        REAL(wp) ::  diss_d !<
    3282        REAL(wp) ::  div    !<
    3283        REAL(wp) ::  flux_d !<
    3284        REAL(wp) ::  u_comp !<
    3285        REAL(wp) ::  v_comp !<
     3284       REAL(wp) ::  diss_d !< artificial dissipation term at grid box bottom
     3285       REAL(wp) ::  div    !< diverence on scalar grid
     3286       REAL(wp) ::  flux_d !< 6th-order flux at grid box bottom
     3287       REAL(wp) ::  u_comp !< advection velocity along x-direction
     3288       REAL(wp) ::  v_comp !< advection velocity along y-direction
    32863289       
    3287        REAL(wp), DIMENSION(nzb:nzt)   ::  diss_n !<
    3288        REAL(wp), DIMENSION(nzb:nzt)   ::  diss_r !<
    3289        REAL(wp), DIMENSION(nzb:nzt)   ::  diss_t !<
    3290        REAL(wp), DIMENSION(nzb:nzt)   ::  flux_n !<
    3291        REAL(wp), DIMENSION(nzb:nzt)   ::  flux_r !<
    3292        REAL(wp), DIMENSION(nzb:nzt)   ::  flux_t !<
     3290       REAL(wp), DIMENSION(nzb:nzt)   ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     3291       REAL(wp), DIMENSION(nzb:nzt)   ::  diss_r !< discretized artificial dissipation at rightward-side of the grid box
     3292       REAL(wp), DIMENSION(nzb:nzt)   ::  diss_t !< discretized artificial dissipation at rightward-side of the grid box
     3293       REAL(wp), DIMENSION(nzb:nzt)   ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     3294       REAL(wp), DIMENSION(nzb:nzt)   ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     3295       REAL(wp), DIMENSION(nzb:nzt)   ::  flux_t !< discretized 6th-order flux at rightward-side of the grid box
    32933296       
    3294        REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local !<
    3295        REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local !<
     3297       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local !< discretized artificial dissipation term at southward-side of the grid box
     3298       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local !< discretized 6th-order flux at northward-side of the grid box
    32963299       
    3297        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local !<
    3298        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local !<
     3300       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local !< discretized artificial dissipation term at leftward-side of the grid box
     3301       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local !< discretized 6th-order flux at leftward-side of the grid box
    32993302       
    33003303
     
    38133816       IMPLICIT NONE
    38143817
    3815        INTEGER(iwp) ::  i      !<
    3816        INTEGER(iwp) ::  ibit9  !<
    3817        INTEGER(iwp) ::  ibit10 !<
    3818        INTEGER(iwp) ::  ibit11 !<
    3819        INTEGER(iwp) ::  ibit12 !<
    3820        INTEGER(iwp) ::  ibit13 !<
    3821        INTEGER(iwp) ::  ibit14 !<
    3822        INTEGER(iwp) ::  ibit15 !<
    3823        INTEGER(iwp) ::  ibit16 !<
    3824        INTEGER(iwp) ::  ibit17 !<
    3825        INTEGER(iwp) ::  j      !<
    3826        INTEGER(iwp) ::  k      !<
    3827        INTEGER(iwp) ::  k_mm   !<
    3828        INTEGER(iwp) ::  k_pp   !<
    3829        INTEGER(iwp) ::  k_ppp  !<
    3830        INTEGER(iwp) ::  tn = 0 !<
     3818       INTEGER(iwp) ::  i      !< grid index along x-direction
     3819       INTEGER(iwp) ::  ibit9  !< flag indicating 1st-order scheme along x-direction
     3820       INTEGER(iwp) ::  ibit10 !< flag indicating 3rd-order scheme along x-direction
     3821       INTEGER(iwp) ::  ibit11 !< flag indicating 5th-order scheme along x-direction
     3822       INTEGER(iwp) ::  ibit12 !< flag indicating 1st-order scheme along y-direction
     3823       INTEGER(iwp) ::  ibit13 !< flag indicating 3rd-order scheme along y-direction
     3824       INTEGER(iwp) ::  ibit14 !< flag indicating 5th-order scheme along y-direction
     3825       INTEGER(iwp) ::  ibit15 !< flag indicating 1st-order scheme along z-direction
     3826       INTEGER(iwp) ::  ibit16 !< flag indicating 3rd-order scheme along z-direction
     3827       INTEGER(iwp) ::  ibit17 !< flag indicating 5th-order scheme along z-direction
     3828       INTEGER(iwp) ::  j      !< grid index along y-direction
     3829       INTEGER(iwp) ::  k      !< grid index along z-direction
     3830       INTEGER(iwp) ::  k_mm   !< k-2 index in disretization, can be modified to avoid segmentation faults
     3831       INTEGER(iwp) ::  k_pp   !< k+2 index in disretization, can be modified to avoid segmentation faults
     3832       INTEGER(iwp) ::  k_ppp  !< k+3 index in disretization, can be modified to avoid segmentation faults
     3833       INTEGER(iwp) ::  tn = 0 !< number of OpenMP thread
    38313834       
    3832        REAL(wp)    ::  diss_d !<
    3833        REAL(wp)    ::  div    !<
    3834        REAL(wp)    ::  flux_d !<
    3835        REAL(wp)    ::  gu     !<
    3836        REAL(wp)    ::  gv     !<
    3837        REAL(wp)    ::  v_comp !<
    3838        REAL(wp)    ::  w_comp !<
     3835       REAL(wp)    ::  diss_d !< artificial dissipation term at grid box bottom
     3836       REAL(wp)    ::  div    !< diverence on u-grid
     3837       REAL(wp)    ::  flux_d !< 6th-order flux at grid box bottom
     3838       REAL(wp)    ::  gu     !< Galilei-transformation velocity along x
     3839       REAL(wp)    ::  gv     !< Galilei-transformation velocity along y
     3840       REAL(wp)    ::  v_comp !< advection velocity along y
     3841       REAL(wp)    ::  w_comp !< advection velocity along z
    38393842       
    3840        REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local_u !<
    3841        REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local_u !<
     3843       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local_u !< discretized artificial dissipation at southward-side of the grid box
     3844       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local_u !< discretized 6th-order flux at southward-side of the grid box
    38423845       
    3843        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_u !<
    3844        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_u !<
     3846       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_u !< discretized artificial dissipation at leftward-side of the grid box
     3847       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_u !< discretized 6th-order flux at leftward-side of the grid box
    38453848       
    3846        REAL(wp), DIMENSION(nzb:nzt) ::  diss_n !<
    3847        REAL(wp), DIMENSION(nzb:nzt) ::  diss_r !<
    3848        REAL(wp), DIMENSION(nzb:nzt) ::  diss_t !<
    3849        REAL(wp), DIMENSION(nzb:nzt) ::  flux_n !<
    3850        REAL(wp), DIMENSION(nzb:nzt) ::  flux_r !<
    3851        REAL(wp), DIMENSION(nzb:nzt) ::  flux_t !<
    3852        REAL(wp), DIMENSION(nzb:nzt) ::  u_comp !<
     3849       REAL(wp), DIMENSION(nzb:nzt) ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     3850       REAL(wp), DIMENSION(nzb:nzt) ::  diss_r !< discretized artificial dissipation at leftward-side of the grid box
     3851       REAL(wp), DIMENSION(nzb:nzt) ::  diss_t !< discretized artificial dissipation at top of the grid box
     3852       REAL(wp), DIMENSION(nzb:nzt) ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     3853       REAL(wp), DIMENSION(nzb:nzt) ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     3854       REAL(wp), DIMENSION(nzb:nzt) ::  flux_t !< discretized 6th-order flux at top of the grid box
     3855       REAL(wp), DIMENSION(nzb:nzt) ::  u_comp !< advection velocity along x
    38533856 
    38543857       gu = 2.0_wp * u_gtrans
     
    43054308
    43064309
    4307        INTEGER(iwp) ::  i      !<
    4308        INTEGER(iwp) ::  ibit18 !<
    4309        INTEGER(iwp) ::  ibit19 !<
    4310        INTEGER(iwp) ::  ibit20 !<
    4311        INTEGER(iwp) ::  ibit21 !<
    4312        INTEGER(iwp) ::  ibit22 !<
    4313        INTEGER(iwp) ::  ibit23 !<
    4314        INTEGER(iwp) ::  ibit24 !<
    4315        INTEGER(iwp) ::  ibit25 !<
    4316        INTEGER(iwp) ::  ibit26 !<
    4317        INTEGER(iwp) ::  j      !<
    4318        INTEGER(iwp) ::  k      !<
    4319        INTEGER(iwp) ::  k_mm   !<
    4320        INTEGER(iwp) ::  k_pp   !<
    4321        INTEGER(iwp) ::  k_ppp  !<
    4322        INTEGER(iwp) ::  tn = 0 !<
     4310       INTEGER(iwp) ::  i      !< grid index along x-direction
     4311       INTEGER(iwp) ::  ibit18 !< flag indicating 1st-order scheme along x-direction
     4312       INTEGER(iwp) ::  ibit19 !< flag indicating 3rd-order scheme along x-direction
     4313       INTEGER(iwp) ::  ibit20 !< flag indicating 5th-order scheme along x-direction
     4314       INTEGER(iwp) ::  ibit21 !< flag indicating 1st-order scheme along y-direction
     4315       INTEGER(iwp) ::  ibit22 !< flag indicating 3rd-order scheme along y-direction
     4316       INTEGER(iwp) ::  ibit23 !< flag indicating 5th-order scheme along y-direction
     4317       INTEGER(iwp) ::  ibit24 !< flag indicating 1st-order scheme along z-direction
     4318       INTEGER(iwp) ::  ibit25 !< flag indicating 3rd-order scheme along z-direction
     4319       INTEGER(iwp) ::  ibit26 !< flag indicating 5th-order scheme along z-direction
     4320       INTEGER(iwp) ::  j      !< grid index along y-direction
     4321       INTEGER(iwp) ::  k      !< grid index along z-direction
     4322       INTEGER(iwp) ::  k_mm   !< k-2 index in disretization, can be modified to avoid segmentation faults
     4323       INTEGER(iwp) ::  k_pp   !< k+2 index in disretization, can be modified to avoid segmentation faults
     4324       INTEGER(iwp) ::  k_ppp  !< k+3 index in disretization, can be modified to avoid segmentation faults
     4325       INTEGER(iwp) ::  tn = 0 !< number of OpenMP thread
    43234326       
    4324        REAL(wp)    ::  diss_d !<
    4325        REAL(wp)    ::  div    !<
    4326        REAL(wp)    ::  flux_d !<
    4327        REAL(wp)    ::  gu     !<
    4328        REAL(wp)    ::  gv     !<
    4329        REAL(wp)    ::  u_comp !<
    4330        REAL(wp)    ::  w_comp !<
     4327       REAL(wp)    ::  diss_d !< artificial dissipation term at grid box bottom
     4328       REAL(wp)    ::  div    !< diverence on v-grid
     4329       REAL(wp)    ::  flux_d !< artificial 6th-order flux at grid box bottom
     4330       REAL(wp)    ::  gu     !< Galilei-transformation velocity along x
     4331       REAL(wp)    ::  gv     !< Galilei-transformation velocity along y
     4332       REAL(wp)    ::  u_comp !< advection velocity along x
     4333       REAL(wp)    ::  w_comp !< advection velocity along z
    43314334       
    4332        REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local_v !<
    4333        REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local_v !<
     4335       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local_v !< discretized artificial dissipation at southward-side of the grid box
     4336       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local_v !< discretized 6th-order flux at southward-side of the grid box
    43344337       
    4335        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_v !<
    4336        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_v !<
     4338       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_v !< discretized artificial dissipation at leftward-side of the grid box
     4339       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_v !< discretized 6th-order flux at leftward-side of the grid box
    43374340       
    4338        REAL(wp), DIMENSION(nzb:nzt) ::  diss_n !<
    4339        REAL(wp), DIMENSION(nzb:nzt) ::  diss_r !<
    4340        REAL(wp), DIMENSION(nzb:nzt) ::  diss_t !<
    4341        REAL(wp), DIMENSION(nzb:nzt) ::  flux_n !<
    4342        REAL(wp), DIMENSION(nzb:nzt) ::  flux_r !<
    4343        REAL(wp), DIMENSION(nzb:nzt) ::  flux_t !<
    4344        REAL(wp), DIMENSION(nzb:nzt) ::  v_comp !<
     4341       REAL(wp), DIMENSION(nzb:nzt) ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     4342       REAL(wp), DIMENSION(nzb:nzt) ::  diss_r !< discretized artificial dissipation at rightward-side of the grid box
     4343       REAL(wp), DIMENSION(nzb:nzt) ::  diss_t !< discretized artificial dissipation at top of the grid box
     4344       REAL(wp), DIMENSION(nzb:nzt) ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     4345       REAL(wp), DIMENSION(nzb:nzt) ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     4346       REAL(wp), DIMENSION(nzb:nzt) ::  flux_t !< discretized 6th-order flux at top of the grid box
     4347       REAL(wp), DIMENSION(nzb:nzt) ::  v_comp !< advection velocity along y
    43454348
    43464349       gu = 2.0_wp * u_gtrans
     
    48074810       IMPLICIT NONE
    48084811
    4809        INTEGER(iwp) ::  i      !<
    4810        INTEGER(iwp) ::  ibit27 !<
    4811        INTEGER(iwp) ::  ibit28 !<
    4812        INTEGER(iwp) ::  ibit29 !<
    4813        INTEGER(iwp) ::  ibit30 !<
    4814        INTEGER(iwp) ::  ibit31 !<
    4815        INTEGER(iwp) ::  ibit32 !<
    4816        INTEGER(iwp) ::  ibit33 !<
    4817        INTEGER(iwp) ::  ibit34 !<
    4818        INTEGER(iwp) ::  ibit35 !<
    4819        INTEGER(iwp) ::  j      !<
    4820        INTEGER(iwp) ::  k      !<
    4821        INTEGER(iwp) ::  k_mm   !<
    4822        INTEGER(iwp) ::  k_pp   !<
    4823        INTEGER(iwp) ::  k_ppp  !<
    4824        INTEGER(iwp) ::  tn = 0 !<
     4812       INTEGER(iwp) ::  i      !< grid index along x-direction
     4813       INTEGER(iwp) ::  ibit27 !< flag indicating 1st-order scheme along x-direction
     4814       INTEGER(iwp) ::  ibit28 !< flag indicating 3rd-order scheme along x-direction
     4815       INTEGER(iwp) ::  ibit29 !< flag indicating 5th-order scheme along x-direction
     4816       INTEGER(iwp) ::  ibit30 !< flag indicating 1st-order scheme along y-direction
     4817       INTEGER(iwp) ::  ibit31 !< flag indicating 3rd-order scheme along y-direction
     4818       INTEGER(iwp) ::  ibit32 !< flag indicating 5th-order scheme along y-direction
     4819       INTEGER(iwp) ::  ibit33 !< flag indicating 1st-order scheme along z-direction
     4820       INTEGER(iwp) ::  ibit34 !< flag indicating 3rd-order scheme along z-direction
     4821       INTEGER(iwp) ::  ibit35 !< flag indicating 5th-order scheme along z-direction
     4822       INTEGER(iwp) ::  j      !< grid index along y-direction
     4823       INTEGER(iwp) ::  k      !< grid index along z-direction
     4824       INTEGER(iwp) ::  k_mm   !< k-2 index in disretization, can be modified to avoid segmentation faults
     4825       INTEGER(iwp) ::  k_pp   !< k+2 index in disretization, can be modified to avoid segmentation faults
     4826       INTEGER(iwp) ::  k_ppp  !< k+3 index in disretization, can be modified to avoid segmentation faults
     4827       INTEGER(iwp) ::  tn = 0 !< number of OpenMP thread
    48254828       
    4826        REAL(wp)    ::  diss_d !<
    4827        REAL(wp)    ::  div    !<
    4828        REAL(wp)    ::  flux_d !<
    4829        REAL(wp)    ::  gu     !<
    4830        REAL(wp)    ::  gv     !<
    4831        REAL(wp)    ::  u_comp !<
    4832        REAL(wp)    ::  v_comp !<
    4833        REAL(wp)    ::  w_comp !<
     4829       REAL(wp)    ::  diss_d !< artificial dissipation term at grid box bottom
     4830       REAL(wp)    ::  div    !< divergence on w-grid
     4831       REAL(wp)    ::  flux_d !< 6th-order flux at grid box bottom
     4832       REAL(wp)    ::  gu     !< Galilei-transformation velocity along x
     4833       REAL(wp)    ::  gv     !< Galilei-transformation velocity along y
     4834       REAL(wp)    ::  u_comp !< advection velocity along x
     4835       REAL(wp)    ::  v_comp !< advection velocity along y
     4836       REAL(wp)    ::  w_comp !< advection velocity along z
    48344837       
    4835        REAL(wp), DIMENSION(nzb:nzt)    ::  diss_t !<
    4836        REAL(wp), DIMENSION(nzb:nzt)    ::  flux_t !<
     4838       REAL(wp), DIMENSION(nzb:nzt)    ::  diss_t !< discretized artificial dissipation at top of the grid box
     4839       REAL(wp), DIMENSION(nzb:nzt)    ::  flux_t !< discretized 6th-order flux at top of the grid box
    48374840       
    4838        REAL(wp), DIMENSION(nzb+1:nzt)  ::  diss_n !<
    4839        REAL(wp), DIMENSION(nzb+1:nzt)  ::  diss_r !<
    4840        REAL(wp), DIMENSION(nzb+1:nzt)  ::  flux_n !<
    4841        REAL(wp), DIMENSION(nzb+1:nzt)  ::  flux_r !<
    4842        REAL(wp), DIMENSION(nzb+1:nzt)  ::  swap_diss_y_local_w !<
    4843        REAL(wp), DIMENSION(nzb+1:nzt)  ::  swap_flux_y_local_w !<
     4841       REAL(wp), DIMENSION(nzb+1:nzt)  ::  diss_n !< discretized artificial dissipation at northward-side of the grid box
     4842       REAL(wp), DIMENSION(nzb+1:nzt)  ::  diss_r !< discretized artificial dissipation at rightward-side of the grid box
     4843       REAL(wp), DIMENSION(nzb+1:nzt)  ::  flux_n !< discretized 6th-order flux at northward-side of the grid box
     4844       REAL(wp), DIMENSION(nzb+1:nzt)  ::  flux_r !< discretized 6th-order flux at rightward-side of the grid box
     4845       REAL(wp), DIMENSION(nzb+1:nzt)  ::  swap_diss_y_local_w !< discretized artificial dissipation at southward-side of the grid box
     4846       REAL(wp), DIMENSION(nzb+1:nzt)  ::  swap_flux_y_local_w !< discretized 6th-order flux at southward-side of the grid box
    48444847       
    4845        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_w !<
    4846        REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_w !<
     4848       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_w !< discretized artificial dissipation at leftward-side of the grid box
     4849       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_w !< discretized 6th-order flux at leftward-side of the grid box
    48474850 
    48484851       gu = 2.0_wp * u_gtrans
Note: See TracChangeset for help on using the changeset viewer.