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/diffusivities.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:
     
    3642! adjustment of mixing length to the Prandtl mixing length at first grid point
    3743! above ground removed
    38 !
    39 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    40 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    41 !
    42 ! 137 2007-11-28 08:50:10Z letzel
    43 ! Bugfix for summation of sums_l_l for flow_statistics
    44 ! Vertical scalar profiles now based on nzb_s_inner and ngp_2dh_s_inner.
    45 !
    46 ! 97 2007-06-21 08:23:15Z raasch
    47 ! Adjustment of mixing length calculation for the ocean version.
    48 ! This is also a bugfix, because the height above the topography is now
    49 ! used instead of the height above level k=0.
    50 ! theta renamed var, dpt_dz renamed dvar_dz, +new argument var_reference
    51 ! use_pt_reference renamed use_reference
    52 !
    53 ! 57 2007-03-09 12:05:41Z raasch
    54 ! Reference temperature pt_reference can be used in buoyancy term
    55 !
    56 ! RCS Log replace by Id keyword, revision history cleaned up
    57 !
    58 ! Revision 1.24  2006/04/26 12:16:26  raasch
    59 ! OpenMP optimization (+sums_l_l_t), sqrt_e must be private
    6044!
    6145! Revision 1.1  1997/09/19 07:41:10  raasch
     
    6953!------------------------------------------------------------------------------!
    7054
    71     USE arrays_3d
    72     USE control_parameters
    73     USE grid_variables
    74     USE indices
     55    USE arrays_3d,                                                             &
     56        ONLY:  dd2zu, e, kh, km, l_grid, l_wall
     57       
     58    USE control_parameters,                                                    &
     59        ONLY:  atmos_ocean_sign, e_min, g, outflow_l, outflow_n, outflow_r,    &
     60                outflow_s, use_single_reference_value, wall_adjustment
     61               
     62    USE indices,                                                               &
     63        ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb_s_inner, nzb, nzt
     64    USE kinds
     65   
    7566    USE pegrid
    76     USE statistics
     67   
     68    USE statistics,                                                            &
     69        ONLY :  rmask, statistic_regions, sums_l_l
    7770
    7871    IMPLICIT NONE
    7972
    80     INTEGER ::  i, j, k, omp_get_thread_num, sr, tn
    81 
    82     REAL    ::  dvar_dz, l, ll, l_stable, sqrt_e, var_reference
    83 
    84     REAL    ::  var(nzb:nzt+1,nysg:nyng,nxlg:nxrg)
     73    INTEGER(iwp) ::  i                   !:
     74    INTEGER(iwp) ::  j                   !:
     75    INTEGER(iwp) ::  k                   !:
     76    INTEGER(iwp) ::  omp_get_thread_num  !:
     77    INTEGER(iwp) ::  sr                  !:
     78    INTEGER(iwp) ::  tn                  !:
     79
     80    REAL(wp)     ::  dvar_dz             !:
     81    REAL(wp)     ::  l                   !:
     82    REAL(wp)     ::  ll                  !:
     83    REAL(wp)     ::  l_stable            !:
     84    REAL(wp)     ::  sqrt_e              !:
     85    REAL(wp)     ::  var_reference       !:
     86
     87    REAL(wp)     ::  var(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
    8588
    8689
     
    136139                IF ( dvar_dz > 0.0 ) THEN
    137140                   IF ( use_single_reference_value )  THEN
    138                       l_stable = 0.76 * sqrt_e / &
     141                      l_stable = 0.76 * sqrt_e /                               &
    139142                                 SQRT( g / var_reference * dvar_dz ) + 1E-5
    140143                   ELSE
    141                       l_stable = 0.76 * sqrt_e / &
     144                      l_stable = 0.76 * sqrt_e /                               &
    142145                                 SQRT( g / var(k,j,i) * dvar_dz ) + 1E-5
    143146                   ENDIF
Note: See TracChangeset for help on using the changeset viewer.