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/lpm_boundary_conds.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! 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:
     
    2631! $Id$
    2732!
    28 ! 1318 2014-03-17 13:35:16Z raasch
    29 ! module interfaces removed
    30 !
    3133! 1036 2012-10-22 13:43:42Z raasch
    3234! code put under GPL (PALM 3.9)
     
    3840! 824 2012-02-17 09:09:57Z raasch
    3941! particle attributes speed_x|y|z_sgs renamed rvar1|2|3
    40 !
    41 ! 150 2008-02-29 08:19:58Z raasch
    42 ! Vertical index calculations adjusted for ocean runs.
    4342!
    4443! Initial version (2007/03/09)
     
    6160!------------------------------------------------------------------------------!
    6261
    63     USE arrays_3d
    64     USE control_parameters
    65     USE cpulog
    66     USE grid_variables
    67     USE indices
    68     USE particle_attributes
     62    USE arrays_3d,                                                             &
     63        ONLY:  zu, zw
     64
     65    USE control_parameters,                                                    &
     66        ONLY:  dz, message_string, particle_maximum_age
     67
     68    USE cpulog,                                                                &
     69        ONLY:  cpu_log, log_point_s
     70
     71    USE grid_variables,                                                        &
     72        ONLY:  ddx, dx, ddy, dy
     73
     74    USE indices,                                                               &
     75        ONLY:  nxl, nxr, nyn, nys, nz, nzb_s_inner
     76
     77    USE kinds
     78
     79    USE particle_attributes,                                                   &
     80        ONLY:  deleted_particles, deleted_tails, ibc_par_b, ibc_par_t,         &
     81               number_of_particles, particles, particle_mask,                  &
     82               particle_tail_coordinates, particle_type, offset_ocean_nzt_m1,  &
     83               tail_mask, use_particle_tails, use_sgs_for_particles
     84
    6985    USE pegrid
    7086
    7187    IMPLICIT NONE
    7288
    73     CHARACTER (LEN=*) ::  range
    74 
    75     INTEGER ::  i, inc, ir, i1, i2, i3, i5, j, jr, j1, j2, j3, j5, k, k1, k2, &
    76                 k3, k5, n, nn, t_index, t_index_number
    77 
    78     LOGICAL ::  reflect_x, reflect_y, reflect_z
    79 
    80     REAL ::  dt_particle, pos_x, pos_x_old, pos_y, pos_y_old, pos_z, &
    81              pos_z_old, prt_x, prt_y, prt_z, tmp_t, xline, yline, zline
    82 
    83     REAL ::  t(1:200)
    84 
    85 
     89    CHARACTER (LEN=*) ::  range     !:
     90   
     91    INTEGER(iwp) ::  i              !:
     92    INTEGER(iwp) ::  inc            !:
     93    INTEGER(iwp) ::  ir             !:
     94    INTEGER(iwp) ::  i1             !:
     95    INTEGER(iwp) ::  i2             !:
     96    INTEGER(iwp) ::  i3             !:
     97    INTEGER(iwp) ::  i5             !:
     98    INTEGER(iwp) ::  j              !:
     99    INTEGER(iwp) ::  jr             !:
     100    INTEGER(iwp) ::  j1             !:
     101    INTEGER(iwp) ::  j2             !:
     102    INTEGER(iwp) ::  j3             !:
     103    INTEGER(iwp) ::  j5             !:
     104    INTEGER(iwp) ::  k              !:
     105    INTEGER(iwp) ::  k1             !:
     106    INTEGER(iwp) ::  k2             !:
     107    INTEGER(iwp) ::  k3             !:
     108    INTEGER(iwp) ::  k5             !:
     109    INTEGER(iwp) ::  n              !:
     110    INTEGER(iwp) ::  nn             !:
     111    INTEGER(iwp) ::  t_index        !:
     112    INTEGER(iwp) ::  t_index_number !:
     113   
     114    LOGICAL  ::  reflect_x   !:
     115    LOGICAL  ::  reflect_y   !:
     116    LOGICAL  ::  reflect_z   !:
     117
     118    REAL(wp) ::  dt_particle !:
     119    REAL(wp) ::  pos_x       !:
     120    REAL(wp) ::  pos_x_old   !:
     121    REAL(wp) ::  pos_y       !:
     122    REAL(wp) ::  pos_y_old   !:
     123    REAL(wp) ::  pos_z       !:
     124    REAL(wp) ::  pos_z_old   !:
     125    REAL(wp) ::  prt_x       !:
     126    REAL(wp) ::  prt_y       !:
     127    REAL(wp) ::  prt_z       !:
     128    REAL(wp) ::  t(1:200)    !:
     129    REAL(wp) ::  tmp_t       !:
     130    REAL(wp) ::  xline       !:
     131    REAL(wp) ::  yline       !:
     132    REAL(wp) ::  zline       !:
    86133
    87134    IF ( range == 'bottom/top' )  THEN
Note: See TracChangeset for help on using the changeset viewer.