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/sum_up_3d_data.f90

    r1319 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:
     
    4450! 978 2012-08-09 08:28:32Z fricke
    4551! +z0h*
    46 !
    47 ! 790 2011-11-29 03:11:20Z raasch
    48 ! bugfix: calculation of 'pr' must depend on the particle weighting factor
    49 !
    50 ! 771 2011-10-27 10:56:21Z heinze
    51 ! +lpt_av
    52 !
    53 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    54 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    55 !
    56 ! 402 2009-10-21 11:59:41Z maronga
    57 ! Bugfix in calculation of shf*_av, qsws*_av
    58 !
    59 ! 2009-08-25 08:35:52Z maronga
    60 ! +shf*, qsws*
    61 !
    62 ! 96 2007-06-04 08:07:41Z raasch
    63 ! +sum-up of density and salinity
    64 !
    65 ! 72 2007-03-19 08:20:46Z raasch
    66 ! +sum-up of precipitation rate and roughness length (prr*, z0*)
    67 !
    68 ! RCS Log replace by Id keyword, revision history cleaned up
    6952!
    7053! Revision 1.1  2006/02/23 12:55:23  raasch
     
    7861!------------------------------------------------------------------------------!
    7962
    80     USE arrays_3d
    81     USE averaging
    82     USE cloud_parameters
    83     USE control_parameters
    84     USE cpulog
    85     USE indices
    86     USE particle_attributes
     63    USE arrays_3d,                                                             &
     64        ONLY:  dzw, e, nr, p, pt, q, qc, ql, ql_c, ql_v, qr, qsws, rho, sa,    &
     65               shf, ts, u, us, v, vpt, w, z0, z0h
     66
     67    USE averaging,                                                             &
     68        ONLY:  e_av, lpt_av, lwp_av, nr_av, p_av, pc_av, pr_av, prr_av,        &
     69               precipitation_rate_av, pt_av, q_av, qc_av, ql_av, ql_c_av,      &
     70               ql_v_av, ql_vp_av, qr_av, qsws_av, qv_av, rho_av, s_av, sa_av,  &
     71               shf_av, ts_av, u_av, us_av, v_av, vpt_av, w_av, z0_av, z0h_av
     72
     73    USE cloud_parameters,                                                      &
     74        ONLY:  l_d_cp, precipitation_rate, pt_d_t
     75
     76    USE control_parameters,                                                    &
     77        ONLY:  average_count_3d, cloud_physics, doav, doav_n
     78
     79    USE cpulog,                                                                &
     80        ONLY:  cpu_log, log_point
     81
     82    USE indices,                                                               &
     83        ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
     84
     85    USE kinds
     86
     87    USE particle_attributes,                                                   &
     88        ONLY:  particles, prt_count, prt_start_index
    8789
    8890    IMPLICIT NONE
    8991
    90     INTEGER ::  i, ii, j, k, n, psi
    91 
    92     REAL    ::  mean_r, s_r3, s_r4
    93 
     92    INTEGER(iwp) ::  i   !:
     93    INTEGER(iwp) ::  ii  !:
     94    INTEGER(iwp) ::  j   !:
     95    INTEGER(iwp) ::  k   !:
     96    INTEGER(iwp) ::  n   !:
     97    INTEGER(iwp) ::  psi !:
     98
     99    REAL(wp)     ::  mean_r !:
     100    REAL(wp)     ::  s_r3   !:
     101    REAL(wp)     ::  s_r4   !:
    94102
    95103    CALL cpu_log (log_point(34),'sum_up_3d_data','start')
Note: See TracChangeset for help on using the changeset viewer.