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/calc_precipitation.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! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2328!
    2429! Former revisions:
     
    2833! 1036 2012-10-22 13:43:42Z raasch
    2934! code put under GPL (PALM 3.9)
    30 !
    31 ! 403 2009-10-22 13:57:16Z franke
    32 ! Bugfix in calculation of precipitation_rate(j,i)
    33 !
    34 ! 73 2007-03-20 08:33:14Z raasch
    35 ! Precipitation rate and amount are calculated/stored,
    36 ! + module control_parameters
    37 !
    38 ! 19 2007-02-23 04:53:48Z raasch
    39 ! Calculation extended for gridpoint nzt
    40 !
    41 ! RCS Log replace by Id keyword, revision history cleaned up
    42 !
    43 ! Revision 1.5  2004/01/30 10:15:57  raasch
    44 ! Scalar lower k index nzb replaced by 2d-array nzb_2d
    4535!
    4636! Revision 1.1  2000/04/13 14:45:22  schroeter
     
    7161    SUBROUTINE calc_precipitation
    7262
    73        USE arrays_3d
    74        USE cloud_parameters
    75        USE constants
    76        USE control_parameters
    77        USE indices
     63       USE arrays_3d,                                                          &
     64           ONLY:  dzw, ql, tend
     65
     66       USE cloud_parameters,                                                   &
     67           ONLY:  precipitation_amount, precipitation_rate, prec_time_const,   &
     68                  ql_crit
     69
     70       USE control_parameters,                                                 &
     71           ONLY:  dt_do2d_xy, dt_3d,                                           &
     72                  intermediate_timestep_count, intermediate_timestep_count_max,&
     73                  precipitation_amount_interval, time_do2d_xy
     74
     75       USE indices,                                                            &
     76           ONLY:  nxl, nxr, nyn, nys, nzb_2d, nzt
     77
     78       USE kinds
     79
    7880
    7981       IMPLICIT NONE
    8082
    81        INTEGER ::  i, j, k
    82        REAL    ::  dqdt_precip
     83       INTEGER(iwp) ::  i !:
     84       INTEGER(iwp) ::  j !:
     85       INTEGER(iwp) ::  k !:
     86       
     87       REAL(wp)    ::  dqdt_precip !:
    8388
    8489       precipitation_rate = 0.0
     
    96101!
    97102!--             Precipitation rate in kg / m**2 / s (= mm/s)
    98                 precipitation_rate(j,i) = precipitation_rate(j,i) + &
     103                precipitation_rate(j,i) = precipitation_rate(j,i) +            &
    99104                                          dqdt_precip * dzw(k)
    100105
     
    102107!
    103108!--          Sum up the precipitation amount, unit kg / m**2 (= mm)
    104              IF ( intermediate_timestep_count ==         &
    105                   intermediate_timestep_count_max  .AND. &
     109             IF ( intermediate_timestep_count ==                               &
     110                  intermediate_timestep_count_max  .AND.                       &
    106111                  ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
    107112             THEN
    108                 precipitation_amount(j,i) = precipitation_amount(j,i) + &
     113                precipitation_amount(j,i) = precipitation_amount(j,i) +        &
    109114                                            precipitation_rate(j,i) * dt_3d
    110115             ENDIF
     
    120125    SUBROUTINE calc_precipitation_ij( i, j )
    121126
    122        USE arrays_3d
    123        USE cloud_parameters
    124        USE constants
    125        USE control_parameters
    126        USE indices
     127       USE arrays_3d,                                                          &
     128           ONLY:  dzw, ql, tend
     129
     130       USE cloud_parameters,                                                   &
     131           ONLY:  precipitation_amount, precipitation_rate, prec_time_const,   &
     132                  ql_crit
     133
     134       USE control_parameters,                                                 &
     135           ONLY:  dt_do2d_xy, dt_3d,                                           &
     136                  intermediate_timestep_count, intermediate_timestep_count_max,&
     137                  precipitation_amount_interval, time_do2d_xy
     138
     139       USE indices,                                                            &
     140           ONLY:  nzb_2d, nzt
     141
     142       USE kinds
     143
    127144
    128145       IMPLICIT NONE
    129146
    130        INTEGER ::  i, j, k
    131        REAL    ::  dqdt_precip
     147       INTEGER(iwp) ::  i !:
     148       INTEGER(iwp) ::  j !:
     149       INTEGER(iwp) ::  k !:
     150       
     151       REAL(wp)    ::  dqdt_precip !:       
    132152
    133153       precipitation_rate(j,i) = 0.0
     
    147167!
    148168!--       Precipitation rate in kg / m**2 / s (= mm/s)
    149           precipitation_rate(j,i) = precipitation_rate(j,i) + dqdt_precip * &
     169          precipitation_rate(j,i) = precipitation_rate(j,i) + dqdt_precip *    &
    150170                                                              dzw(k)
    151171
     
    157177            .AND. ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
    158178       THEN
    159           precipitation_amount(j,i) = precipitation_amount(j,i) + &
     179          precipitation_amount(j,i) = precipitation_amount(j,i) +              &
    160180                                      precipitation_rate(j,i) * dt_3d
    161181       ENDIF
Note: See TracChangeset for help on using the changeset viewer.