Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1310 r1320  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    8591! dimension.
    8692!
    87 ! 743 2011-08-18 16:10:16Z suehring
    88 ! Evaluation of turbulent fluxes with WS-scheme only for the whole model
    89 ! domain. Therefor dimension of arrays needed for statistical evaluation
    90 ! decreased.
    91 !
    92 ! 736 2011-08-17 14:13:26Z suehring
    93 ! Bugfix concerning OpenMP parallelization. i_omp introduced, because first
    94 ! index where fluxes on left side have to be calculated explicitly is
    95 ! different on each thread. Furthermore the swapping of fluxes is now
    96 ! thread-safe by adding an additional dimension.
    97 !
    98 ! 713 2011-03-30 14:21:21Z suehring
    99 ! File reformatted.
    100 ! Bugfix in vertical advection of w concerning the optimized version for   
    101 ! vector architecture.
    102 ! Constants adv_mom_3, adv_mom_5, adv_sca_5, adv_sca_3 reformulated as
    103 ! broken numbers.
    104 !
    105 ! 709 2011-03-30 09:31:40Z raasch
    106 ! formatting adjustments
    107 !
    108 ! 705 2011-03-25 11:21:43 Z suehring $
    109 ! Bugfix in declaration of logicals concerning outflow boundaries.
    110 !
    111 ! 411 2009-12-11 12:31:43 Z suehring
    112 ! Allocation of weight_substep moved to init_3d_model.
    113 ! Declaration of ws_scheme_sca and ws_scheme_mom moved to check_parameters.
    114 ! Setting bc for the horizontal velocity variances added (moved from
    115 ! flow_statistics).
    116 !
    11793! Initial revision
    11894!
     
    186162    SUBROUTINE ws_init
    187163
    188        USE arrays_3d
    189        USE constants
    190        USE control_parameters
    191        USE indices
     164       USE arrays_3d,                                                          &
     165           ONLY:  diss_l_e, diss_l_nr, diss_l_pt, diss_l_q, diss_l_qr,         &
     166                  diss_l_sa, diss_l_u, diss_l_v, diss_l_w,  flux_l_e,          &
     167                  flux_l_nr, flux_l_pt, flux_l_q, flux_l_qr, flux_l_sa,        &
     168                  flux_l_u, flux_l_v, flux_l_w, diss_s_e, diss_s_nr, diss_s_pt,&
     169                  diss_s_q, diss_s_qr, diss_s_sa, diss_s_u, diss_s_v, diss_s_w,&
     170                  flux_s_e, flux_s_nr, flux_s_pt, flux_s_q, flux_s_qr,         &
     171                  flux_s_sa, flux_s_u, flux_s_v, flux_s_w
     172
     173       USE constants,                                                          &
     174           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5, adv_sca_1, adv_sca_3,       &
     175                  adv_sca_5
     176
     177       USE control_parameters,                                                 &
     178           ONLY:  cloud_physics, humidity, icloud_scheme, loop_optimization,   &
     179                  passive_scalar, precipitation, ocean, ws_scheme_mom,         &
     180                  ws_scheme_sca
     181
     182       USE indices,                                                            &
     183           ONLY:  nyn, nys, nzb, nzt 
     184       
    192185       USE pegrid
    193        USE statistics
     186
     187       USE statistics,                                                         &
     188           ONLY:  sums_us2_ws_l, sums_vs2_ws_l, sums_ws2_ws_l, sums_wsnrs_ws_l,&
     189                  sums_wspts_ws_l, sums_wsqrs_ws_l, sums_wsqs_ws_l,            &
     190                  sums_wssas_ws_l,  sums_wsus_ws_l, sums_wsvs_ws_l 
    194191
    195192!
     
    205202       IF ( ws_scheme_mom )  THEN
    206203
    207           ALLOCATE( sums_wsus_ws_l(nzb:nzt+1,0:threads_per_task-1),  &
    208                     sums_wsvs_ws_l(nzb:nzt+1,0:threads_per_task-1),  &
    209                     sums_us2_ws_l(nzb:nzt+1,0:threads_per_task-1),   &
    210                     sums_vs2_ws_l(nzb:nzt+1,0:threads_per_task-1),   &
     204          ALLOCATE( sums_wsus_ws_l(nzb:nzt+1,0:threads_per_task-1),            &
     205                    sums_wsvs_ws_l(nzb:nzt+1,0:threads_per_task-1),            &
     206                    sums_us2_ws_l(nzb:nzt+1,0:threads_per_task-1),             &
     207                    sums_vs2_ws_l(nzb:nzt+1,0:threads_per_task-1),             &
    211208                    sums_ws2_ws_l(nzb:nzt+1,0:threads_per_task-1) )
    212209
     
    229226          ENDIF
    230227
    231           IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
     228          IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                 &
    232229               precipitation )  THEN
    233230             ALLOCATE( sums_wsqrs_ws_l(nzb:nzt+1,0:threads_per_task-1) )
     
    253250          IF ( ws_scheme_mom )  THEN
    254251
    255              ALLOCATE( flux_s_u(nzb+1:nzt,0:threads_per_task-1),            &
    256                        flux_s_v(nzb+1:nzt,0:threads_per_task-1),            &
    257                        flux_s_w(nzb+1:nzt,0:threads_per_task-1),            &
    258                        diss_s_u(nzb+1:nzt,0:threads_per_task-1),            &
    259                        diss_s_v(nzb+1:nzt,0:threads_per_task-1),            &
     252             ALLOCATE( flux_s_u(nzb+1:nzt,0:threads_per_task-1),               &
     253                       flux_s_v(nzb+1:nzt,0:threads_per_task-1),               &
     254                       flux_s_w(nzb+1:nzt,0:threads_per_task-1),               &
     255                       diss_s_u(nzb+1:nzt,0:threads_per_task-1),               &
     256                       diss_s_v(nzb+1:nzt,0:threads_per_task-1),               &
    260257                       diss_s_w(nzb+1:nzt,0:threads_per_task-1) )
    261              ALLOCATE( flux_l_u(nzb+1:nzt,nys:nyn,0:threads_per_task-1),    &
    262                        flux_l_v(nzb+1:nzt,nys:nyn,0:threads_per_task-1),    &
    263                        flux_l_w(nzb+1:nzt,nys:nyn,0:threads_per_task-1),    &
    264                        diss_l_u(nzb+1:nzt,nys:nyn,0:threads_per_task-1),    &
    265                        diss_l_v(nzb+1:nzt,nys:nyn,0:threads_per_task-1),    &
     258             ALLOCATE( flux_l_u(nzb+1:nzt,nys:nyn,0:threads_per_task-1),       &
     259                       flux_l_v(nzb+1:nzt,nys:nyn,0:threads_per_task-1),       &
     260                       flux_l_w(nzb+1:nzt,nys:nyn,0:threads_per_task-1),       &
     261                       diss_l_u(nzb+1:nzt,nys:nyn,0:threads_per_task-1),       &
     262                       diss_l_v(nzb+1:nzt,nys:nyn,0:threads_per_task-1),       &
    266263                       diss_l_w(nzb+1:nzt,nys:nyn,0:threads_per_task-1) )
    267264
     
    270267          IF ( ws_scheme_sca )  THEN
    271268
    272              ALLOCATE( flux_s_pt(nzb+1:nzt,0:threads_per_task-1),           &
    273                        flux_s_e(nzb+1:nzt,0:threads_per_task-1),            &
    274                        diss_s_pt(nzb+1:nzt,0:threads_per_task-1),           &
     269             ALLOCATE( flux_s_pt(nzb+1:nzt,0:threads_per_task-1),              &
     270                       flux_s_e(nzb+1:nzt,0:threads_per_task-1),               &
     271                       diss_s_pt(nzb+1:nzt,0:threads_per_task-1),              &
    275272                       diss_s_e(nzb+1:nzt,0:threads_per_task-1) )
    276              ALLOCATE( flux_l_pt(nzb+1:nzt,nys:nyn,0:threads_per_task-1),   &
    277                        flux_l_e(nzb+1:nzt,nys:nyn,0:threads_per_task-1),    &
    278                        diss_l_pt(nzb+1:nzt,nys:nyn,0:threads_per_task-1),   &
     273             ALLOCATE( flux_l_pt(nzb+1:nzt,nys:nyn,0:threads_per_task-1),      &
     274                       flux_l_e(nzb+1:nzt,nys:nyn,0:threads_per_task-1),       &
     275                       diss_l_pt(nzb+1:nzt,nys:nyn,0:threads_per_task-1),      &
    279276                       diss_l_e(nzb+1:nzt,nys:nyn,0:threads_per_task-1) )
    280277
    281278             IF ( humidity  .OR.  passive_scalar )  THEN
    282                 ALLOCATE( flux_s_q(nzb+1:nzt,0:threads_per_task-1),          &
     279                ALLOCATE( flux_s_q(nzb+1:nzt,0:threads_per_task-1),            &
    283280                          diss_s_q(nzb+1:nzt,0:threads_per_task-1) )
    284                 ALLOCATE( flux_l_q(nzb+1:nzt,nys:nyn,0:threads_per_task-1),  &
     281                ALLOCATE( flux_l_q(nzb+1:nzt,nys:nyn,0:threads_per_task-1),    &
    285282                          diss_l_q(nzb+1:nzt,nys:nyn,0:threads_per_task-1) )
    286283             ENDIF
    287284
    288              IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.            &
     285             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.              &
    289286                  precipitation )  THEN
    290                 ALLOCATE( flux_s_qr(nzb+1:nzt,0:threads_per_task-1),         &
    291                           diss_s_qr(nzb+1:nzt,0:threads_per_task-1),         &
    292                           flux_s_nr(nzb+1:nzt,0:threads_per_task-1),         &
     287                ALLOCATE( flux_s_qr(nzb+1:nzt,0:threads_per_task-1),           &
     288                          diss_s_qr(nzb+1:nzt,0:threads_per_task-1),           &
     289                          flux_s_nr(nzb+1:nzt,0:threads_per_task-1),           &
    293290                          diss_s_nr(nzb+1:nzt,0:threads_per_task-1) )
    294                 ALLOCATE( flux_l_qr(nzb+1:nzt,nys:nyn,0:threads_per_task-1), &
    295                           diss_l_qr(nzb+1:nzt,nys:nyn,0:threads_per_task-1), &
    296                           flux_l_nr(nzb+1:nzt,nys:nyn,0:threads_per_task-1), &
     291                ALLOCATE( flux_l_qr(nzb+1:nzt,nys:nyn,0:threads_per_task-1),   &
     292                          diss_l_qr(nzb+1:nzt,nys:nyn,0:threads_per_task-1),   &
     293                          flux_l_nr(nzb+1:nzt,nys:nyn,0:threads_per_task-1),   &
    297294                          diss_l_nr(nzb+1:nzt,nys:nyn,0:threads_per_task-1) )
    298295             ENDIF
    299296
    300297             IF ( ocean )  THEN
    301                 ALLOCATE( flux_s_sa(nzb+1:nzt,0:threads_per_task-1),         &
     298                ALLOCATE( flux_s_sa(nzb+1:nzt,0:threads_per_task-1),           &
    302299                          diss_s_sa(nzb+1:nzt,0:threads_per_task-1) )
    303                 ALLOCATE( flux_l_sa(nzb+1:nzt,nys:nyn,0:threads_per_task-1), &
     300                ALLOCATE( flux_l_sa(nzb+1:nzt,nys:nyn,0:threads_per_task-1),   &
    304301                          diss_l_sa(nzb+1:nzt,nys:nyn,0:threads_per_task-1) )
    305302             ENDIF
     
    317314    SUBROUTINE ws_statistics
    318315   
    319        USE control_parameters
    320        USE statistics
     316       USE control_parameters,                                                 &
     317           ONLY:  cloud_physics, humidity, icloud_scheme, passive_scalar,      &
     318                  precipitation, ocean, ws_scheme_mom, ws_scheme_sca
     319
     320       USE statistics,                                                         &
     321           ONLY:  sums_us2_ws_l, sums_vs2_ws_l, sums_ws2_ws_l, sums_wsnrs_ws_l,&
     322                  sums_wspts_ws_l, sums_wsqrs_ws_l, sums_wsqs_ws_l,            &
     323                  sums_wssas_ws_l,  sums_wsus_ws_l, sums_wsvs_ws_l 
    321324
    322325       IMPLICIT NONE
     
    336339          sums_wspts_ws_l = 0.0
    337340          IF ( humidity  .OR.  passive_scalar )  sums_wsqs_ws_l = 0.0
    338           IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
     341          IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                 &
    339342               precipitation )  THEN
    340343             sums_wsqrs_ws_l = 0.0
     
    351354! Scalar advection - Call for grid point i,j
    352355!------------------------------------------------------------------------------!
    353     SUBROUTINE advec_s_ws_ij( i, j, sk, sk_char, swap_flux_y_local,  &
    354                               swap_diss_y_local, swap_flux_x_local,  &
     356    SUBROUTINE advec_s_ws_ij( i, j, sk, sk_char, swap_flux_y_local,            &
     357                              swap_diss_y_local, swap_flux_x_local,            &
    355358                              swap_diss_x_local, i_omp, tn )
    356359
    357        USE arrays_3d
    358        USE constants
    359        USE control_parameters
    360        USE grid_variables
    361        USE indices
     360       USE arrays_3d,                                                          &
     361           ONLY:  ddzw, tend, u, v, w
     362
     363       USE constants,                                                          &
     364           ONLY:  adv_sca_1, adv_sca_3, adv_sca_5
     365
     366       USE control_parameters,                                                 &
     367           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     368
     369       USE grid_variables,                                                     &
     370           ONLY:  ddx, ddy
     371
     372       USE indices,                                                            &
     373           ONLY:  nxl, nxr, nyn, nys, nzb, nzb_max, nzt, wall_flags_0
     374
     375       USE kinds
     376
    362377       USE pegrid
    363        USE statistics
     378
     379       USE statistics,                                                         &
     380           ONLY:  sums_wsnrs_ws_l, sums_wspts_ws_l, sums_wsqrs_ws_l,           &
     381                  sums_wsqs_ws_l, sums_wssas_ws_l, weight_substep
    364382
    365383       IMPLICIT NONE
    366384
    367        INTEGER ::  i, ibit0, ibit1, ibit2, ibit3, ibit4, ibit5, ibit6,        &
    368                    ibit7, ibit8, i_omp, j, k, k_mm, k_pp, k_ppp,  tn
    369        REAL    ::  diss_d, div, flux_d, u_comp, v_comp
     385       CHARACTER (LEN = *), INTENT(IN) ::  sk_char !:
     386       
     387       INTEGER(iwp) ::  i     !:
     388       INTEGER(iwp) ::  ibit0 !:
     389       INTEGER(iwp) ::  ibit1 !:
     390       INTEGER(iwp) ::  ibit2 !:
     391       INTEGER(iwp) ::  ibit3 !:
     392       INTEGER(iwp) ::  ibit4 !:
     393       INTEGER(iwp) ::  ibit5 !:
     394       INTEGER(iwp) ::  ibit6 !:
     395       INTEGER(iwp) ::  ibit7 !:
     396       INTEGER(iwp) ::  ibit8 !:
     397       INTEGER(iwp) ::  i_omp !:
     398       INTEGER(iwp) ::  j     !:
     399       INTEGER(iwp) ::  k     !:
     400       INTEGER(iwp) ::  k_mm  !:
     401       INTEGER(iwp) ::  k_pp  !:
     402       INTEGER(iwp) ::  k_ppp !:
     403       INTEGER(iwp) ::  tn    !:
     404       
     405       REAL(wp)     ::  diss_d !:
     406       REAL(wp)     ::  div    !:
     407       REAL(wp)     ::  flux_d !:
     408       REAL(wp)     ::  u_comp !:
     409       REAL(wp)     ::  v_comp !:
     410       
    370411#if defined( __nopointer )
    371        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
     412       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
    372413#else
    373        REAL, DIMENSION(:,:,:), POINTER    ::  sk
     414       REAL(wp), DIMENSION(:,:,:), POINTER    ::  sk     !:
    374415#endif
    375        REAL, DIMENSION(nzb:nzt+1)         ::  diss_n, diss_r, diss_t, flux_n,  &
    376                                               flux_r, flux_t
    377        REAL, DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  swap_diss_y_local,  &
    378                                                            swap_flux_y_local
    379        REAL, DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::              &
    380                                                           swap_diss_x_local,   &
    381                                                           swap_flux_x_local
    382        CHARACTER (LEN = *), INTENT(IN)    ::  sk_char
     416       REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_n !:
     417       REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_r !:
     418       REAL(wp), DIMENSION(nzb:nzt+1)         ::  diss_t !:
     419       REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_n !:
     420       REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_r !:
     421       REAL(wp), DIMENSION(nzb:nzt+1)         ::  flux_t !:
     422       
     423       REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  swap_diss_y_local !:
     424       REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1) ::  swap_flux_y_local !:
     425       
     426       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  swap_diss_x_local !:
     427       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1) ::  swap_flux_x_local !:
     428       
    383429
    384430!
     
    800846    SUBROUTINE advec_u_ws_ij( i, j, i_omp, tn )
    801847
    802        USE arrays_3d
    803        USE constants
    804        USE control_parameters
    805        USE grid_variables
    806        USE indices
    807        USE statistics
     848       USE arrays_3d,                                                          &
     849           ONLY:  ddzw, diss_l_u, diss_s_u, flux_l_u, flux_s_u, tend, u, v, w
     850
     851       USE constants,                                                          &
     852           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     853
     854       USE control_parameters,                                                 &
     855           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     856
     857       USE grid_variables,                                                     &
     858           ONLY:  ddx, ddy
     859
     860       USE indices,                                                            &
     861           ONLY:  nxl, nxr, nyn, nys, nzb, nzb_max, nzt, wall_flags_0
     862
     863       USE kinds
     864
     865       USE statistics,                                                         &
     866           ONLY:  hom, sums_us2_ws_l, sums_wsus_ws_l, weight_substep
    808867
    809868       IMPLICIT NONE
    810869
    811        INTEGER ::  i, ibit9, ibit10, ibit11, ibit12, ibit13, ibit14, ibit15,  &
    812                    ibit16, ibit17, i_omp, j, k, k_mm, k_pp, k_ppp, tn
    813        REAL    ::  diss_d, div, flux_d, gu, gv, u_comp_l, v_comp, w_comp
    814        REAL, DIMENSION(nzb:nzt+1) :: diss_n, diss_r, diss_t, flux_n, flux_r,  &
    815                                      flux_t, u_comp
     870       INTEGER(iwp) ::  i      !:
     871       INTEGER(iwp) ::  ibit9  !:
     872       INTEGER(iwp) ::  ibit10 !:
     873       INTEGER(iwp) ::  ibit11 !:
     874       INTEGER(iwp) ::  ibit12 !:
     875       INTEGER(iwp) ::  ibit13 !:
     876       INTEGER(iwp) ::  ibit14 !:
     877       INTEGER(iwp) ::  ibit15 !:
     878       INTEGER(iwp) ::  ibit16 !:
     879       INTEGER(iwp) ::  ibit17 !:
     880       INTEGER(iwp) ::  i_omp  !:
     881       INTEGER(iwp) ::  j      !:
     882       INTEGER(iwp) ::  k      !:
     883       INTEGER(iwp) ::  k_mm   !:
     884       INTEGER(iwp) ::  k_pp   !:
     885       INTEGER(iwp) ::  k_ppp  !:
     886       INTEGER(iwp) ::  tn     !:
     887       
     888       REAL(wp)    ::  diss_d   !:
     889       REAL(wp)    ::  div      !:
     890       REAL(wp)    ::  flux_d   !:
     891       REAL(wp)    ::  gu       !:
     892       REAL(wp)    ::  gv       !:
     893       REAL(wp)    ::  u_comp_l !:
     894       REAL(wp)    ::  v_comp   !:
     895       REAL(wp)    ::  w_comp   !:
     896       
     897       REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_n !:
     898       REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_r !:
     899       REAL(wp), DIMENSION(nzb:nzt+1) ::  diss_t !:
     900       REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_n !:
     901       REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_r !:
     902       REAL(wp), DIMENSION(nzb:nzt+1) ::  flux_t !:
     903       REAL(wp), DIMENSION(nzb:nzt+1) ::  u_comp !:
    816904
    817905       gu = 2.0 * u_gtrans
     
    12121300   SUBROUTINE advec_v_ws_ij( i, j, i_omp, tn )
    12131301
    1214        USE arrays_3d
    1215        USE constants
    1216        USE control_parameters
    1217        USE grid_variables
    1218        USE indices
    1219        USE statistics
     1302       USE arrays_3d,                                                          &
     1303           ONLY:  ddzw, diss_l_v, diss_s_v, flux_l_v, flux_s_v, tend, u, v, w
     1304
     1305       USE constants,                                                          &
     1306           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     1307
     1308       USE control_parameters,                                                 &
     1309           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     1310
     1311       USE grid_variables,                                                     &
     1312           ONLY:  ddx, ddy
     1313
     1314       USE indices,                                                            &
     1315           ONLY:  nxl, nxr, nyn, nys, nysv, nzb, nzb_max, nzt, wall_flags_0
     1316
     1317       USE kinds
     1318
     1319       USE statistics,                                                         &
     1320           ONLY:  hom, sums_vs2_ws_l, sums_wsvs_ws_l, weight_substep
    12201321
    12211322       IMPLICIT NONE
    12221323
    1223        INTEGER  ::  i, ibit18, ibit19, ibit20, ibit21, ibit22, ibit23, ibit24, &
    1224                     ibit25, ibit26, i_omp, j, k, k_mm, k_pp, k_ppp, tn
    1225        REAL     ::  diss_d, div, flux_d, gu, gv, u_comp, v_comp_l, w_comp
    1226        REAL, DIMENSION(nzb:nzt+1)  :: diss_n, diss_r, diss_t, flux_n, flux_r,  &
    1227                                       flux_t, v_comp
     1324       INTEGER(iwp)  ::  i      !:
     1325       INTEGER(iwp)  ::  ibit18 !:
     1326       INTEGER(iwp)  ::  ibit19 !:
     1327       INTEGER(iwp)  ::  ibit20 !:
     1328       INTEGER(iwp)  ::  ibit21 !:
     1329       INTEGER(iwp)  ::  ibit22 !:
     1330       INTEGER(iwp)  ::  ibit23 !:
     1331       INTEGER(iwp)  ::  ibit24 !:
     1332       INTEGER(iwp)  ::  ibit25 !:
     1333       INTEGER(iwp)  ::  ibit26 !:
     1334       INTEGER(iwp)  ::  i_omp  !:
     1335       INTEGER(iwp)  ::  j      !:
     1336       INTEGER(iwp)  ::  k      !:
     1337       INTEGER(iwp)  ::  k_mm   !:
     1338       INTEGER(iwp)  ::  k_pp   !:
     1339       INTEGER(iwp)  ::  k_ppp  !:
     1340       INTEGER(iwp)  ::  tn     !:
     1341       
     1342       REAL(wp)     ::  diss_d   !:
     1343       REAL(wp)     ::  div      !:
     1344       REAL(wp)     ::  flux_d   !:
     1345       REAL(wp)     ::  gu       !:
     1346       REAL(wp)     ::  gv       !:
     1347       REAL(wp)     ::  u_comp   !:
     1348       REAL(wp)     ::  v_comp_l !:
     1349       REAL(wp)     ::  w_comp   !:
     1350       
     1351       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_n !:
     1352       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_r !:
     1353       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_t !:
     1354       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_n !:
     1355       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_r !:
     1356       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_t !:
     1357       REAL(wp), DIMENSION(nzb:nzt+1)  ::  v_comp !:
    12281358
    12291359       gu = 2.0 * u_gtrans
     
    16311761    SUBROUTINE advec_w_ws_ij( i, j, i_omp, tn )
    16321762
    1633        USE arrays_3d
    1634        USE constants
    1635        USE control_parameters
    1636        USE grid_variables
    1637        USE indices
    1638        USE statistics
     1763       USE arrays_3d,                                                          &
     1764           ONLY:  ddzu, diss_l_w, diss_s_w, flux_l_w, flux_s_w, tend, u, v, w
     1765
     1766       USE constants,                                                          &
     1767           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     1768
     1769       USE control_parameters,                                                 &
     1770           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     1771
     1772       USE grid_variables,                                                     &
     1773           ONLY:  ddx, ddy
     1774
     1775       USE indices,                                                            &
     1776           ONLY:  nxl, nxr, nyn, nys, nzb, nzb_max, nzt, wall_flags_0,         &
     1777                  wall_flags_00
     1778
     1779       USE kinds
     1780       
     1781       USE statistics,                                                         &
     1782           ONLY:  hom, sums_ws2_ws_l, weight_substep
    16391783
    16401784       IMPLICIT NONE
    16411785
    1642        INTEGER ::  i, ibit27, ibit28, ibit29, ibit30, ibit31, ibit32, ibit33, &
    1643                    ibit34, ibit35, i_omp, j, k, k_mm, k_pp, k_ppp, tn
    1644        REAL    ::  diss_d, div, flux_d, gu, gv, u_comp, v_comp, w_comp
    1645        REAL, DIMENSION(nzb:nzt+1)  :: diss_n, diss_r, diss_t, flux_n, flux_r, &
    1646                                       flux_t
     1786       INTEGER(iwp) ::  i      !:
     1787       INTEGER(iwp) ::  ibit27 !:
     1788       INTEGER(iwp) ::  ibit28 !:
     1789       INTEGER(iwp) ::  ibit29 !:
     1790       INTEGER(iwp) ::  ibit30 !:
     1791       INTEGER(iwp) ::  ibit31 !:
     1792       INTEGER(iwp) ::  ibit32 !:
     1793       INTEGER(iwp) ::  ibit33 !:
     1794       INTEGER(iwp) ::  ibit34 !:
     1795       INTEGER(iwp) ::  ibit35 !:
     1796       INTEGER(iwp) ::  i_omp  !:
     1797       INTEGER(iwp) ::  j      !:
     1798       INTEGER(iwp) ::  k      !:
     1799       INTEGER(iwp) ::  k_mm   !:
     1800       INTEGER(iwp) ::  k_pp   !:
     1801       INTEGER(iwp) ::  k_ppp  !:
     1802       INTEGER(iwp) ::  tn     !:
     1803       
     1804       REAL(wp)    ::  diss_d  !:
     1805       REAL(wp)    ::  div     !:
     1806       REAL(wp)    ::  flux_d  !:
     1807       REAL(wp)    ::  gu      !:
     1808       REAL(wp)    ::  gv      !:
     1809       REAL(wp)    ::  u_comp  !:
     1810       REAL(wp)    ::  v_comp  !:
     1811       REAL(wp)    ::  w_comp  !:
     1812       
     1813       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_n !:
     1814       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_r !:
     1815       REAL(wp), DIMENSION(nzb:nzt+1)  ::  diss_t !:
     1816       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_n !:
     1817       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_r !:
     1818       REAL(wp), DIMENSION(nzb:nzt+1)  ::  flux_t !:
    16471819
    16481820       gu = 2.0 * u_gtrans
     
    20272199    SUBROUTINE advec_s_ws( sk, sk_char )
    20282200
    2029        USE arrays_3d
    2030        USE constants
    2031        USE control_parameters
    2032        USE grid_variables
    2033        USE indices
    2034        USE statistics
     2201       USE arrays_3d,                                                          &
     2202           ONLY:  ddzw, tend, u, v, w
     2203
     2204       USE constants,                                                          &
     2205           ONLY:  adv_sca_1, adv_sca_3, adv_sca_5
     2206
     2207       USE control_parameters,                                                 &
     2208           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     2209
     2210       USE grid_variables,                                                     &
     2211           ONLY:  ddx, ddy
     2212
     2213       USE indices,                                                            &
     2214           ONLY:  nxl, nxr, nyn, nys, nzb, nzb_max, nzt, wall_flags_0
     2215           
     2216       USE kinds
     2217       
     2218       USE statistics,                                                         &
     2219           ONLY:  sums_wspts_ws_l, sums_wsqs_ws_l, sums_wssas_ws_l,            &
     2220                  weight_substep
    20352221
    20362222       IMPLICIT NONE
    20372223
    2038        INTEGER ::  i, ibit0, ibit1, ibit2, ibit3, ibit4, ibit5, ibit6,        &
    2039                    ibit7, ibit8, j, k, k_mm, k_pp, k_ppp, tn = 0
     2224       CHARACTER (LEN = *), INTENT(IN)    ::  sk_char !:
     2225       
     2226       INTEGER(iwp) ::  i      !:
     2227       INTEGER(iwp) ::  ibit0  !:
     2228       INTEGER(iwp) ::  ibit1  !:
     2229       INTEGER(iwp) ::  ibit2  !:
     2230       INTEGER(iwp) ::  ibit3  !:
     2231       INTEGER(iwp) ::  ibit4  !:
     2232       INTEGER(iwp) ::  ibit5  !:
     2233       INTEGER(iwp) ::  ibit6  !:
     2234       INTEGER(iwp) ::  ibit7  !:
     2235       INTEGER(iwp) ::  ibit8  !:
     2236       INTEGER(iwp) ::  j      !:
     2237       INTEGER(iwp) ::  k      !:
     2238       INTEGER(iwp) ::  k_mm   !:
     2239       INTEGER(iwp) ::  k_pp   !:
     2240       INTEGER(iwp) ::  k_ppp  !:
     2241       INTEGER(iwp) ::  tn = 0 !:
     2242       
    20402243#if defined( __nopointer )
    2041        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
     2244       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
    20422245#else
    2043        REAL, DIMENSION(:,:,:), POINTER ::  sk
     2246       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk !:
    20442247#endif
    2045        REAL ::  diss_d, div, flux_d, u_comp, v_comp
    2046        REAL, DIMENSION(nzb:nzt)   ::  diss_n, diss_r, diss_t, flux_n, flux_r,  &
    2047                                       flux_t
    2048        REAL, DIMENSION(nzb+1:nzt) ::  swap_diss_y_local, swap_flux_y_local
    2049        REAL, DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local,               &
    2050                                               swap_flux_x_local
    2051        CHARACTER (LEN = *), INTENT(IN)    ::  sk_char
     2248
     2249       REAL(wp) ::  diss_d !:
     2250       REAL(wp) ::  div    !:
     2251       REAL(wp) ::  flux_d !:
     2252       REAL(wp) ::  u_comp !:
     2253       REAL(wp) ::  v_comp !:
     2254       
     2255       REAL(wp), DIMENSION(nzb:nzt)   ::  diss_n !:
     2256       REAL(wp), DIMENSION(nzb:nzt)   ::  diss_r !:
     2257       REAL(wp), DIMENSION(nzb:nzt)   ::  diss_t !:
     2258       REAL(wp), DIMENSION(nzb:nzt)   ::  flux_n !:
     2259       REAL(wp), DIMENSION(nzb:nzt)   ::  flux_r !:
     2260       REAL(wp), DIMENSION(nzb:nzt)   ::  flux_t !:
     2261       
     2262       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local !:
     2263       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local !:
     2264       
     2265       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local !:
     2266       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local !:
     2267       
    20522268
    20532269!
     
    24392655    SUBROUTINE advec_s_ws_acc ( sk, sk_char )
    24402656
    2441        USE arrays_3d
    2442        USE constants
    2443        USE control_parameters
    2444        USE grid_variables
    2445        USE indices
    2446        USE statistics
     2657       USE arrays_3d,                                                          &
     2658           ONLY:  ddzw, tend, u, v, w
     2659
     2660       USE constants,                                                          &
     2661           ONLY:  adv_sca_1, adv_sca_3, adv_sca_5
     2662
     2663       USE control_parameters,                                                 &
     2664           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     2665
     2666       USE grid_variables,                                                     &
     2667           ONLY:  ddx, ddy
     2668
     2669       USE indices,                                                            &
     2670           ONLY:  i_left, i_right, j_north, j_south, nxlg, nxrg, nyng, nysg,   &
     2671                  nzb, nzb_max, nzt, wall_flags_0
     2672
     2673       USE kinds
     2674       
     2675!        USE statistics,                                                       &
     2676!            ONLY:  sums_wspts_ws_l, sums_wsqs_ws_l, sums_wssas_ws_l,          &
     2677!                   weight_substep
    24472678
    24482679       IMPLICIT NONE
    24492680
    2450        CHARACTER (LEN = *), INTENT(IN)    :: sk_char
    2451 
    2452        INTEGER ::  i, ibit0, ibit1, ibit2, ibit3, ibit4, ibit5, ibit6,        &
    2453                    ibit7, ibit8, j, k, k_mm, k_mmm, k_pp, k_ppp, tn = 0
    2454 
    2455        REAL    :: diss_d, diss_l, diss_n, diss_r, diss_s, diss_t, div, flux_d, &
    2456                   flux_l, flux_n, flux_r, flux_s, flux_t, u_comp, v_comp
    2457 
    2458        REAL, INTENT(IN), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  ::  sk
     2681       CHARACTER (LEN = *), INTENT(IN)    :: sk_char !:
     2682
     2683       INTEGER(iwp) ::  i      !:
     2684       INTEGER(iwp) ::  ibit0  !:
     2685       INTEGER(iwp) ::  ibit1  !:
     2686       INTEGER(iwp) ::  ibit2  !:
     2687       INTEGER(iwp) ::  ibit3  !:
     2688       INTEGER(iwp) ::  ibit4  !:
     2689       INTEGER(iwp) ::  ibit5  !:
     2690       INTEGER(iwp) ::  ibit6  !:
     2691       INTEGER(iwp) ::  ibit7  !:
     2692       INTEGER(iwp) ::  ibit8  !:
     2693       INTEGER(iwp) ::  j      !:
     2694       INTEGER(iwp) ::  k      !:
     2695       INTEGER(iwp) ::  k_mm   !:
     2696       INTEGER(iwp) ::  k_mmm  !:
     2697       INTEGER(iwp) ::  k_pp   !:
     2698       INTEGER(iwp) ::  k_ppp  !:
     2699       INTEGER(iwp) ::  tn = 0 !:
     2700
     2701       REAL(wp)    ::  diss_d !:
     2702       REAL(wp)    ::  diss_l !:
     2703       REAL(wp)    ::  diss_n !:
     2704       REAL(wp)    ::  diss_r !:
     2705       REAL(wp)    ::  diss_s !:
     2706       REAL(wp)    ::  diss_t !:
     2707       REAL(wp)    ::  div    !:
     2708       REAL(wp)    ::  flux_d !:
     2709       REAL(wp)    ::  flux_l !:
     2710       REAL(wp)    ::  flux_n !:
     2711       REAL(wp)    ::  flux_r !:
     2712       REAL(wp)    ::  flux_s !:
     2713       REAL(wp)    ::  flux_t !:
     2714       REAL(wp)    ::  u_comp !:
     2715       REAL(wp)    ::  v_comp !:
     2716
     2717       REAL(wp), INTENT(IN), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  ::  sk !:
    24592718
    24602719!
     
    27192978    SUBROUTINE advec_u_ws
    27202979
    2721        USE arrays_3d
    2722        USE constants
    2723        USE control_parameters
    2724        USE grid_variables
    2725        USE indices
    2726        USE statistics
     2980       USE arrays_3d,                                                          &
     2981           ONLY:  ddzw, tend, u, v, w
     2982
     2983       USE constants,                                                          &
     2984           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     2985
     2986       USE control_parameters,                                                 &
     2987           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     2988
     2989       USE grid_variables,                                                     &
     2990           ONLY:  ddx, ddy
     2991
     2992       USE indices,                                                            &
     2993           ONLY:  nxl, nxlu, nxr, nyn, nys, nzb, nzb_max, nzt, wall_flags_0
     2994           
     2995       USE kinds
     2996       
     2997       USE statistics,                                                         &
     2998           ONLY:  hom, sums_us2_ws_l, sums_wsus_ws_l, weight_substep
    27272999
    27283000       IMPLICIT NONE
    27293001
    2730        INTEGER ::  i, ibit9, ibit10, ibit11, ibit12, ibit13, ibit14, ibit15,   &
    2731                    ibit16, ibit17, j, k, k_mm, k_pp, k_ppp, tn = 0
    2732        REAL    ::  diss_d, div, flux_d, gu, gv, v_comp, w_comp
    2733        REAL, DIMENSION(nzb+1:nzt) :: swap_diss_y_local_u, swap_flux_y_local_u
    2734        REAL, DIMENSION(nzb+1:nzt,nys:nyn) :: swap_diss_x_local_u,              &
    2735                                              swap_flux_x_local_u
    2736        REAL, DIMENSION(nzb:nzt) :: diss_n, diss_r, diss_t, flux_n, flux_r,     &
    2737                                    flux_t, u_comp
     3002       INTEGER(iwp) ::  i      !:
     3003       INTEGER(iwp) ::  ibit9  !:
     3004       INTEGER(iwp) ::  ibit10 !:
     3005       INTEGER(iwp) ::  ibit11 !:
     3006       INTEGER(iwp) ::  ibit12 !:
     3007       INTEGER(iwp) ::  ibit13 !:
     3008       INTEGER(iwp) ::  ibit14 !:
     3009       INTEGER(iwp) ::  ibit15 !:
     3010       INTEGER(iwp) ::  ibit16 !:
     3011       INTEGER(iwp) ::  ibit17 !:
     3012       INTEGER(iwp) ::  j      !:
     3013       INTEGER(iwp) ::  k      !:
     3014       INTEGER(iwp) ::  k_mm   !:
     3015       INTEGER(iwp) ::  k_pp   !:
     3016       INTEGER(iwp) ::  k_ppp  !:
     3017       INTEGER(iwp) ::  tn = 0 !:
     3018       
     3019       REAL(wp)    ::  diss_d !:
     3020       REAL(wp)    ::  div    !:
     3021       REAL(wp)    ::  flux_d !:
     3022       REAL(wp)    ::  gu     !:
     3023       REAL(wp)    ::  gv     !:
     3024       REAL(wp)    ::  v_comp !:
     3025       REAL(wp)    ::  w_comp !:
     3026       
     3027       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local_u !:
     3028       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local_u !:
     3029       
     3030       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_u !:
     3031       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_u !:
     3032       
     3033       REAL(wp), DIMENSION(nzb:nzt) ::  diss_n !:
     3034       REAL(wp), DIMENSION(nzb:nzt) ::  diss_r !:
     3035       REAL(wp), DIMENSION(nzb:nzt) ::  diss_t !:
     3036       REAL(wp), DIMENSION(nzb:nzt) ::  flux_n !:
     3037       REAL(wp), DIMENSION(nzb:nzt) ::  flux_r !:
     3038       REAL(wp), DIMENSION(nzb:nzt) ::  flux_t !:
     3039       REAL(wp), DIMENSION(nzb:nzt) ::  u_comp !:
    27383040 
    27393041       gu = 2.0 * u_gtrans
     
    31373439    SUBROUTINE advec_u_ws_acc
    31383440
    3139        USE arrays_3d
    3140        USE constants
    3141        USE control_parameters
    3142        USE grid_variables
    3143        USE indices
    3144        USE statistics
     3441       USE arrays_3d,                                                          &
     3442           ONLY:  ddzw, tend, u, v, w
     3443
     3444       USE constants,                                                          &
     3445           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     3446
     3447       USE control_parameters,                                                 &
     3448           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     3449
     3450       USE grid_variables,                                                     &
     3451           ONLY:  ddx, ddy
     3452
     3453       USE indices,                                                            &
     3454           ONLY:  i_left, i_right, j_north, j_south, nxl, nxr, nyn, nys, nzb,  &
     3455                  nzb_max, nzt, wall_flags_0
     3456           
     3457       USE kinds
     3458       
     3459!        USE statistics,                                                       &
     3460!            ONLY:  hom, sums_us2_ws_l, sums_wsus_ws_l, weight_substep
    31453461
    31463462       IMPLICIT NONE
    31473463
    3148        INTEGER ::  i, ibit9, ibit10, ibit11, ibit12, ibit13, ibit14, ibit15,   &
    3149                    ibit16, ibit17, j, k, k_mmm, k_mm, k_pp, k_ppp, tn = 0
    3150 
    3151        REAL    ::  diss_d, diss_l, diss_n, diss_r, diss_s, diss_t, div,    &
    3152                    flux_d, flux_l, flux_n, flux_r, flux_s, flux_t, gu, gv, &
    3153                    u_comp, u_comp_l, v_comp, v_comp_s, w_comp
     3464       INTEGER(iwp) ::  i      !:
     3465       INTEGER(iwp) ::  ibit9  !:
     3466       INTEGER(iwp) ::  ibit10 !:
     3467       INTEGER(iwp) ::  ibit11 !:
     3468       INTEGER(iwp) ::  ibit12 !:
     3469       INTEGER(iwp) ::  ibit13 !:
     3470       INTEGER(iwp) ::  ibit14 !:
     3471       INTEGER(iwp) ::  ibit15 !:
     3472       INTEGER(iwp) ::  ibit16 !:
     3473       INTEGER(iwp) ::  ibit17 !:
     3474       INTEGER(iwp) ::  j      !:
     3475       INTEGER(iwp) ::  k      !:
     3476       INTEGER(iwp) ::  k_mmm  !:
     3477       INTEGER(iwp) ::  k_mm   !:
     3478       INTEGER(iwp) ::  k_pp   !:
     3479       INTEGER(iwp) ::  k_ppp  !:
     3480       INTEGER(iwp) ::  tn = 0 !:
     3481
     3482       REAL(wp)    ::  diss_d   !:
     3483       REAL(wp)    ::  diss_l   !:
     3484       REAL(wp)    ::  diss_n   !:
     3485       REAL(wp)    ::  diss_r   !:
     3486       REAL(wp)    ::  diss_s   !:
     3487       REAL(wp)    ::  diss_t   !:
     3488       REAL(wp)    ::  div      !:
     3489       REAL(wp)    ::  flux_d   !:
     3490       REAL(wp)    ::  flux_l   !:
     3491       REAL(wp)    ::  flux_n   !:
     3492       REAL(wp)    ::  flux_r   !:
     3493       REAL(wp)    ::  flux_s   !:
     3494       REAL(wp)    ::  flux_t   !:
     3495       REAL(wp)    ::  gu       !:
     3496       REAL(wp)    ::  gv       !:
     3497       REAL(wp)    ::  u_comp   !:
     3498       REAL(wp)    ::  u_comp_l !:
     3499       REAL(wp)    ::  v_comp   !:
     3500       REAL(wp)    ::  v_comp_s !:
     3501       REAL(wp)    ::  w_comp   !:
    31543502
    31553503
     
    34243772    SUBROUTINE advec_v_ws
    34253773
    3426        USE arrays_3d
    3427        USE constants
    3428        USE control_parameters
    3429        USE grid_variables
    3430        USE indices
    3431        USE statistics
     3774       USE arrays_3d,                                                          &
     3775           ONLY:  ddzw, tend, u, v, w
     3776
     3777       USE constants,                                                          &
     3778           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     3779
     3780       USE control_parameters,                                                 &
     3781           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     3782
     3783       USE grid_variables,                                                     &
     3784           ONLY:  ddx, ddy
     3785
     3786       USE indices,                                                            &
     3787           ONLY:  nxl, nxr, nyn, nys, nysv, nzb, nzb_max, nzt, wall_flags_0
     3788
     3789       USE kinds
     3790
     3791       USE statistics,                                                         &
     3792           ONLY:  hom, sums_vs2_ws_l, sums_wsvs_ws_l, weight_substep
    34323793
    34333794       IMPLICIT NONE
    34343795
    34353796
    3436        INTEGER ::  i, ibit18, ibit19, ibit20, ibit21, ibit22, ibit23, ibit24, &
    3437                     ibit25, ibit26, j, k, k_mm, k_pp, k_ppp, tn = 0
    3438        REAL    ::  diss_d, div, flux_d, gu, gv, u_comp, w_comp
    3439        REAL, DIMENSION(nzb+1:nzt) :: swap_diss_y_local_v, swap_flux_y_local_v
    3440        REAL, DIMENSION(nzb+1:nzt,nys:nyn) :: swap_diss_x_local_v,             &
    3441                                              swap_flux_x_local_v
    3442        REAL, DIMENSION(nzb:nzt) :: diss_n, diss_r, diss_t, flux_n, flux_r,    &
    3443                                    flux_t, v_comp
     3797       INTEGER(iwp) ::  i      !:
     3798       INTEGER(iwp) ::  ibit18 !:
     3799       INTEGER(iwp) ::  ibit19 !:
     3800       INTEGER(iwp) ::  ibit20 !:
     3801       INTEGER(iwp) ::  ibit21 !:
     3802       INTEGER(iwp) ::  ibit22 !:
     3803       INTEGER(iwp) ::  ibit23 !:
     3804       INTEGER(iwp) ::  ibit24 !:
     3805       INTEGER(iwp) ::  ibit25 !:
     3806       INTEGER(iwp) ::  ibit26 !:
     3807       INTEGER(iwp) ::  j      !:
     3808       INTEGER(iwp) ::  k      !:
     3809       INTEGER(iwp) ::  k_mm   !:
     3810       INTEGER(iwp) ::  k_pp   !:
     3811       INTEGER(iwp) ::  k_ppp  !:
     3812       INTEGER(iwp) ::  tn = 0 !:
     3813       
     3814       REAL(wp)    ::  diss_d !:
     3815       REAL(wp)    ::  div    !:
     3816       REAL(wp)    ::  flux_d !:
     3817       REAL(wp)    ::  gu     !:
     3818       REAL(wp)    ::  gv     !:
     3819       REAL(wp)    ::  u_comp !:
     3820       REAL(wp)    ::  w_comp !:
     3821       
     3822       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_diss_y_local_v !:
     3823       REAL(wp), DIMENSION(nzb+1:nzt) ::  swap_flux_y_local_v !:
     3824       
     3825       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_v !:
     3826       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_v !:
     3827       
     3828       REAL(wp), DIMENSION(nzb:nzt) ::  diss_n !:
     3829       REAL(wp), DIMENSION(nzb:nzt) ::  diss_r !:
     3830       REAL(wp), DIMENSION(nzb:nzt) ::  diss_t !:
     3831       REAL(wp), DIMENSION(nzb:nzt) ::  flux_n !:
     3832       REAL(wp), DIMENSION(nzb:nzt) ::  flux_r !:
     3833       REAL(wp), DIMENSION(nzb:nzt) ::  flux_t !:
     3834       REAL(wp), DIMENSION(nzb:nzt) ::  v_comp !:
    34443835
    34453836       gu = 2.0 * u_gtrans
     
    38524243    SUBROUTINE advec_v_ws_acc
    38534244
    3854        USE arrays_3d
    3855        USE constants
    3856        USE control_parameters
    3857        USE grid_variables
    3858        USE indices
    3859        USE statistics
     4245       USE arrays_3d,                                                          &
     4246           ONLY:  ddzw, tend, u, v, w
     4247
     4248       USE constants,                                                          &
     4249           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     4250
     4251       USE control_parameters,                                                 &
     4252           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     4253
     4254       USE grid_variables,                                                     &
     4255           ONLY:  ddx, ddy
     4256
     4257       USE indices,                                                            &
     4258           ONLY:  i_left, i_right, j_north, j_south, nxl, nxr, nyn, nys, nzb,  &
     4259                  nzb_max, nzt, wall_flags_0
     4260           
     4261       USE kinds
     4262       
     4263!        USE statistics,                                                       &
     4264!            ONLY:  hom, sums_vs2_ws_l, sums_wsvs_ws_l, weight_substep
    38604265
    38614266       IMPLICIT NONE
    38624267
    38634268
    3864        INTEGER ::  i, ibit18, ibit19, ibit20, ibit21, ibit22, ibit23, ibit24, &
    3865                     ibit25, ibit26, j, k, k_mm, k_mmm, k_pp, k_ppp, tn = 0
    3866 
    3867        REAL    ::  diss_d, diss_l, diss_n, diss_r, diss_s, diss_t, div,    &
    3868                    flux_d, flux_l, flux_n, flux_r, flux_s, flux_t, gu, gv, &
    3869                    u_comp, u_comp_l, v_comp, v_comp_s, w_comp
     4269       INTEGER(iwp) ::  i      !:
     4270       INTEGER(iwp) ::  ibit18 !:
     4271       INTEGER(iwp) ::  ibit19 !:
     4272       INTEGER(iwp) ::  ibit20 !:
     4273       INTEGER(iwp) ::  ibit21 !:
     4274       INTEGER(iwp) ::  ibit22 !:
     4275       INTEGER(iwp) ::  ibit23 !:
     4276       INTEGER(iwp) ::  ibit24 !:
     4277       INTEGER(iwp) ::  ibit25 !:
     4278       INTEGER(iwp) ::  ibit26 !:
     4279       INTEGER(iwp) ::  j      !:
     4280       INTEGER(iwp) ::  k      !:
     4281       INTEGER(iwp) ::  k_mm   !:
     4282       INTEGER(iwp) ::  k_mmm  !:
     4283       INTEGER(iwp) ::  k_pp   !:
     4284       INTEGER(iwp) ::  k_ppp  !:
     4285       INTEGER(iwp) ::  tn = 0 !:
     4286
     4287       REAL(wp)    ::  diss_d   !:
     4288       REAL(wp)    ::  diss_l   !:
     4289       REAL(wp)    ::  diss_n   !:
     4290       REAL(wp)    ::  diss_r   !:
     4291       REAL(wp)    ::  diss_s   !:
     4292       REAL(wp)    ::  diss_t   !:
     4293       REAL(wp)    ::  div      !:
     4294       REAL(wp)    ::  flux_d   !:
     4295       REAL(wp)    ::  flux_l   !:
     4296       REAL(wp)    ::  flux_n   !:
     4297       REAL(wp)    ::  flux_r   !:
     4298       REAL(wp)    ::  flux_s   !:
     4299       REAL(wp)    ::  flux_t   !:
     4300       REAL(wp)    ::  gu       !:
     4301       REAL(wp)    ::  gv       !:
     4302       REAL(wp)    ::  u_comp   !:
     4303       REAL(wp)    ::  u_comp_l !:
     4304       REAL(wp)    ::  v_comp   !:
     4305       REAL(wp)    ::  v_comp_s !:
     4306       REAL(wp)    ::  w_comp   !:
    38704307
    38714308       gu = 2.0 * u_gtrans
     
    41414578    SUBROUTINE advec_w_ws
    41424579
    4143        USE arrays_3d
    4144        USE constants
    4145        USE control_parameters
    4146        USE grid_variables
    4147        USE indices
    4148        USE statistics
     4580       USE arrays_3d,                                                          &
     4581           ONLY:  ddzu, tend, u, v, w
     4582
     4583       USE constants,                                                          &
     4584           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     4585
     4586       USE control_parameters,                                                 &
     4587           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     4588
     4589       USE grid_variables,                                                     &
     4590           ONLY:  ddx, ddy
     4591
     4592       USE indices,                                                            &
     4593           ONLY:  nxl, nxr, nyn, nys, nzb, nzb_max, nzt, wall_flags_0,         &
     4594                  wall_flags_00
     4595
     4596       USE kinds
     4597       
     4598       USE statistics,                                                         &
     4599           ONLY:  hom, sums_ws2_ws_l, weight_substep
    41494600
    41504601       IMPLICIT NONE
    41514602
    4152        INTEGER ::  i, ibit27, ibit28, ibit29, ibit30, ibit31, ibit32, ibit33, &
    4153                    ibit34, ibit35, j, k, k_mm, k_pp, k_ppp, tn = 0
    4154        REAL    ::  diss_d, div, flux_d, gu, gv, u_comp, v_comp, w_comp
    4155        REAL, DIMENSION(nzb:nzt)    ::  diss_t, flux_t
    4156        REAL, DIMENSION(nzb+1:nzt)  ::  diss_n, diss_r, flux_n, flux_r,        &
    4157                                        swap_diss_y_local_w,                   &
    4158                                        swap_flux_y_local_w
    4159        REAL, DIMENSION(nzb+1:nzt,nys:nyn) :: swap_diss_x_local_w,             &
    4160                                              swap_flux_x_local_w
     4603       INTEGER(iwp) ::  i      !:
     4604       INTEGER(iwp) ::  ibit27 !:
     4605       INTEGER(iwp) ::  ibit28 !:
     4606       INTEGER(iwp) ::  ibit29 !:
     4607       INTEGER(iwp) ::  ibit30 !:
     4608       INTEGER(iwp) ::  ibit31 !:
     4609       INTEGER(iwp) ::  ibit32 !:
     4610       INTEGER(iwp) ::  ibit33 !:
     4611       INTEGER(iwp) ::  ibit34 !:
     4612       INTEGER(iwp) ::  ibit35 !:
     4613       INTEGER(iwp) ::  j      !:
     4614       INTEGER(iwp) ::  k      !:
     4615       INTEGER(iwp) ::  k_mm   !:
     4616       INTEGER(iwp) ::  k_pp   !:
     4617       INTEGER(iwp) ::  k_ppp  !:
     4618       INTEGER(iwp) ::  tn = 0 !:
     4619       
     4620       REAL(wp)    ::  diss_d !:
     4621       REAL(wp)    ::  div    !:
     4622       REAL(wp)    ::  flux_d !:
     4623       REAL(wp)    ::  gu     !:
     4624       REAL(wp)    ::  gv     !:
     4625       REAL(wp)    ::  u_comp !:
     4626       REAL(wp)    ::  v_comp !:
     4627       REAL(wp)    ::  w_comp !:
     4628       
     4629       REAL(wp), DIMENSION(nzb:nzt)    ::  diss_t !:
     4630       REAL(wp), DIMENSION(nzb:nzt)    ::  flux_t !:
     4631       
     4632       REAL(wp), DIMENSION(nzb+1:nzt)  ::  diss_n !:
     4633       REAL(wp), DIMENSION(nzb+1:nzt)  ::  diss_r !:
     4634       REAL(wp), DIMENSION(nzb+1:nzt)  ::  flux_n !:
     4635       REAL(wp), DIMENSION(nzb+1:nzt)  ::  flux_r !:
     4636       REAL(wp), DIMENSION(nzb+1:nzt)  ::  swap_diss_y_local_w !:
     4637       REAL(wp), DIMENSION(nzb+1:nzt)  ::  swap_flux_y_local_w !:
     4638       
     4639       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_diss_x_local_w !:
     4640       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  swap_flux_x_local_w !:
    41614641 
    41624642       gu = 2.0 * u_gtrans
     
    45465026    SUBROUTINE advec_w_ws_acc
    45475027
    4548        USE arrays_3d
    4549        USE constants
    4550        USE control_parameters
    4551        USE grid_variables
    4552        USE indices
    4553        USE statistics
     5028       USE arrays_3d,                                                          &
     5029           ONLY:  ddzu, tend, u, v, w
     5030
     5031       USE constants,                                                          &
     5032           ONLY:  adv_mom_1, adv_mom_3, adv_mom_5
     5033
     5034       USE control_parameters,                                                 &
     5035           ONLY:  intermediate_timestep_count, u_gtrans, v_gtrans
     5036
     5037       USE grid_variables,                                                     &
     5038           ONLY:  ddx, ddy
     5039
     5040       USE indices,                                                            &
     5041           ONLY:  i_left, i_right, j_north, j_south, nxl, nxr, nyn, nys, nzb,  &
     5042                  nzb_max, nzt, wall_flags_0, wall_flags_00
     5043           
     5044       USE kinds
     5045       
     5046!        USE statistics,                                                       &
     5047!            ONLY:  hom, sums_ws2_ws_l, weight_substep
    45545048
    45555049       IMPLICIT NONE
    45565050
    4557        INTEGER ::  i, ibit27, ibit28, ibit29, ibit30, ibit31, ibit32, ibit33, &
    4558                    ibit34, ibit35, j, k, k_mmm, k_mm, k_pp, k_ppp, tn = 0
    4559 
    4560        REAL    ::  diss_d, diss_l, diss_n, diss_r, diss_s, diss_t, div,    &
    4561                    flux_d, flux_l, flux_n, flux_r, flux_s, flux_t, gu, gv, &
    4562                    u_comp, u_comp_l, v_comp, v_comp_s, w_comp
     5051       INTEGER(iwp) ::  i      !:
     5052       INTEGER(iwp) ::  ibit27 !:
     5053       INTEGER(iwp) ::  ibit28 !:
     5054       INTEGER(iwp) ::  ibit29 !:
     5055       INTEGER(iwp) ::  ibit30 !:
     5056       INTEGER(iwp) ::  ibit31 !:
     5057       INTEGER(iwp) ::  ibit32 !:
     5058       INTEGER(iwp) ::  ibit33 !:
     5059       INTEGER(iwp) ::  ibit34 !:
     5060       INTEGER(iwp) ::  ibit35 !:
     5061       INTEGER(iwp) ::  j      !:
     5062       INTEGER(iwp) ::  k      !:
     5063       INTEGER(iwp) ::  k_mmm  !:
     5064       INTEGER(iwp) ::  k_mm   !:
     5065       INTEGER(iwp) ::  k_pp   !:
     5066       INTEGER(iwp) ::  k_ppp  !:
     5067       INTEGER(iwp) ::  tn = 0 !:
     5068
     5069       REAL(wp)    ::  diss_d   !:
     5070       REAL(wp)    ::  diss_l   !:
     5071       REAL(wp)    ::  diss_n   !:
     5072       REAL(wp)    ::  diss_r   !:
     5073       REAL(wp)    ::  diss_s   !:
     5074       REAL(wp)    ::  diss_t   !:
     5075       REAL(wp)    ::  div      !:
     5076       REAL(wp)    ::  flux_d   !:
     5077       REAL(wp)    ::  flux_l   !:
     5078       REAL(wp)    ::  flux_n   !:
     5079       REAL(wp)    ::  flux_r   !:
     5080       REAL(wp)    ::  flux_s   !:
     5081       REAL(wp)    ::  flux_t   !:
     5082       REAL(wp)    ::  gu       !:
     5083       REAL(wp)    ::  gv       !:
     5084       REAL(wp)    ::  u_comp   !:
     5085       REAL(wp)    ::  u_comp_l !:
     5086       REAL(wp)    ::  v_comp   !:
     5087       REAL(wp)    ::  v_comp_s !:
     5088       REAL(wp)    ::  w_comp   !:
    45635089
    45645090       gu = 2.0 * u_gtrans
Note: See TracChangeset for help on using the changeset viewer.