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/disturb_field.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:
     
    2632! $Id$
    2733!
    28 ! 1318 2014-03-17 13:35:16Z raasch
    29 ! module interfaces removed
    30 !
    3134! 1036 2012-10-22 13:43:42Z raasch
    3235! code put under GPL (PALM 3.9)
    33 !
    34 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    35 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    36 ! Calls of exchange_horiz are modified.
    37 !
    38 ! 420 2010-01-13 15:10:53Z franke
    39 ! Loop was split to make runs reproducible when using ifort compiler
    40 !
    41 ! 75 2007-03-22 09:54:05Z raasch
    42 ! xrp, ynp eliminated, 2nd+3rd argument removed from exchange horiz
    43 !
    44 ! RCS Log replace by Id keyword, revision history cleaned up
    45 !
    46 ! Revision 1.11  2006/08/04 14:31:59  raasch
    47 ! izuf renamed iran
    4836!
    4937! Revision 1.1  1998/02/04 15:40:45  raasch
     
    6048!------------------------------------------------------------------------------!
    6149
    62     USE control_parameters
    63     USE cpulog
    64     USE grid_variables
    65     USE indices
    66     USE random_function_mod
     50    USE control_parameters,   &
     51        ONLY:  dist_nxl, dist_nxr, dist_nyn, dist_nys, dist_range,             &
     52               disturbance_amplitude, disturbance_created,                     &
     53               disturbance_level_ind_b, disturbance_level_ind_t, iran,         &
     54               random_generator, topography
     55               
     56    USE cpulog,                                                                &
     57        ONLY:  cpu_log, log_point
     58       
     59    USE indices,                                                               &
     60        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
     61       
     62    USE kinds
     63   
     64    USE random_function_mod,                                                   &
     65        ONLY: random_function
    6766
    6867    IMPLICIT NONE
    6968
    70     INTEGER ::  i, j, k
    71     INTEGER ::  nzb_uv_inner(nysg:nyng,nxlg:nxrg)
    72 
    73     REAL    ::  randomnumber,                             &
    74                 dist1(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
    75                 field(nzb:nzt+1,nysg:nyng,nxlg:nxrg)
    76     REAL, DIMENSION(:,:,:), ALLOCATABLE ::  dist2
     69    INTEGER(iwp) ::  i  !:
     70    INTEGER(iwp) ::  j  !:
     71    INTEGER(iwp) ::  k  !:
     72   
     73    INTEGER(iwp) ::  nzb_uv_inner(nysg:nyng,nxlg:nxrg) !:
     74
     75    REAL(wp) ::  randomnumber  !:
     76   
     77    REAL(wp) ::  dist1(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
     78    REAL(wp) ::  field(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
     79   
     80    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  dist2  !:
    7781
    7882
     
    9296          DO  j = dist_nys(dist_range), dist_nyn(dist_range)
    9397             DO  k = disturbance_level_ind_b, disturbance_level_ind_t
    94                 randomnumber = 3.0 * disturbance_amplitude * &
     98                randomnumber = 3.0 * disturbance_amplitude *                   &
    9599                               ( random_function( iran ) - 0.5 )
    96                 IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  &
    97                      nyn >= j ) &
     100                IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.         &
     101                     nyn >= j )                                                &
    98102                THEN
    99103                   dist1(k,j,i) = randomnumber
     
    107111             DO  k = disturbance_level_ind_b, disturbance_level_ind_t
    108112#if defined( __nec )
    109                 randomnumber = 3.0 * disturbance_amplitude * &
     113                randomnumber = 3.0 * disturbance_amplitude *                   &
    110114                               ( RANDOM( 0 ) - 0.5 )
    111115#else
    112116                CALL RANDOM_NUMBER( randomnumber )
    113                 randomnumber = 3.0 * disturbance_amplitude * &
     117                randomnumber = 3.0 * disturbance_amplitude *                   &
    114118                                ( randomnumber - 0.5 )
    115119#endif
    116                 IF ( nxl <= i .AND. nxr >= i .AND. nys <= j .AND. nyn >= j ) &
     120                IF ( nxl <= i .AND. nxr >= i .AND. nys <= j .AND. nyn >= j )   &
    117121                THEN
    118122                   dist1(k,j,i) = randomnumber
     
    137141        DO  j = nys, nyn
    138142          DO  k = disturbance_level_ind_b-1, disturbance_level_ind_t+1
    139              dist2(k,j,i) = ( dist1(k,j,i-1) + dist1(k,j,i+1) &
    140                             + dist1(k,j+1,i) + dist1(k+1,j,i) &
     143             dist2(k,j,i) = ( dist1(k,j,i-1) + dist1(k,j,i+1)                  &
     144                            + dist1(k,j+1,i) + dist1(k+1,j,i)                  &
    141145                            ) / 12.0
    142146          ENDDO
Note: See TracChangeset for help on using the changeset viewer.