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/prandtl_fluxes.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:
     
    4046! 978 2012-08-09 08:28:32Z fricke
    4147! roughness length for scalar quantities z0h added
    42 !
    43 ! 759 2011-09-15 13:58:31Z raasch
    44 ! Bugfix for ts limitation
    45 !
    46 ! 709 2011-03-30 09:31:40Z raasch
    47 ! formatting adjustments
    48 !
    49 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    50 ! Changed surface boundary conditions for u and v from mirror to Dirichlet.
    51 ! Therefore u(uzb,:,:) and v(nzb,:,:) are now representative for height z0.
    52 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    53 !
    54 ! 315 2009-05-13 10:57:59Z raasch
    55 ! Saturation condition at (sea) surface is not used in precursor runs (only
    56 ! in the following coupled runs)
    57 ! Bugfix: qsws was calculated in case of constant heatflux = .FALSE.
    58 !
    59 ! 187 2008-08-06 16:25:09Z letzel
    60 ! Bugfix: modification of the calculation of the vertical turbulent momentum
    61 ! fluxes u'w' and v'w'
    62 ! Bugfix: change definition of us_wall from 1D to 2D
    63 ! Change: modification of the integrated version of the profile function for
    64 ! momentum for unstable stratification (does not effect results)
    65 !
    66 ! 108 2007-08-24 15:10:38Z letzel
    67 ! assume saturation at k=nzb_s_inner(j,i) for atmosphere coupled to ocean
    68 !
    69 ! 75 2007-03-22 09:54:05Z raasch
    70 ! moisture renamed humidity
    71 !
    72 ! RCS Log replace by Id keyword, revision history cleaned up
    73 !
    74 ! Revision 1.19  2006/04/26 12:24:35  raasch
    75 ! +OpenMP directives and optimization (array assignments replaced by DO loops)
    7648!
    7749! Revision 1.1  1998/01/23 10:06:06  raasch
     
    8557!------------------------------------------------------------------------------!
    8658
    87     USE arrays_3d
    88     USE control_parameters
    89     USE grid_variables
    90     USE indices
     59    USE arrays_3d,                                                             &
     60        ONLY:  e, pt, q, qs, qsws, rif, shf, ts, u, us, usws, v, vpt, vsws,    &
     61               zu, zw, z0, z0h
     62
     63    USE control_parameters,                                                    &
     64        ONLY:  constant_heatflux, constant_waterflux, coupling_mode, g,        &
     65               humidity, ibc_e_b, kappa, large_scale_forcing, lsf_surf,        &
     66               passive_scalar, pt_surface, q_surface, rif_max, rif_min,        &
     67               run_coupled, surface_pressure
     68
     69    USE indices,                                                               &
     70        ONLY:  nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb_s_inner,        &
     71               nzb_u_inner, nzb_v_inner
     72
     73    USE kinds
    9174
    9275    IMPLICIT NONE
    9376
    94     INTEGER ::  i, j, k
    95     LOGICAL ::  coupled_run
    96     REAL    ::  a, b, e_q, rifm, uv_total, z_p
     77    INTEGER(iwp) ::  i            !:
     78    INTEGER(iwp) ::  j            !:
     79    INTEGER(iwp) ::  k            !:
     80
     81    LOGICAL      ::  coupled_run  !:
     82
     83    REAL(wp)     ::  a            !:
     84    REAL(wp)     ::  b            !:
     85    REAL(wp)     ::  e_q          !:
     86    REAL(wp)     ::  rifm         !:
     87    REAL(wp)     ::  uv_total     !:
     88    REAL(wp)     ::  z_p          !:
    9789
    9890!
Note: See TracChangeset for help on using the changeset viewer.