Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/disturb_field.f90

    r1426 r1682  
    1  SUBROUTINE disturb_field( nzb_uv_inner, dist1, field )
    2 
     1!> @file disturb_field.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5554! Description:
    5655! ------------
    57 ! Imposing a random perturbation on a 3D-array.
    58 ! On parallel computers, the random number generator is as well called for all
    59 ! gridpoints of the total domain to ensure, regardless of the number of PEs
    60 ! used, that the elements of the array have the same values in the same
    61 ! order in every case. The perturbation range is steered by dist_range.
     56!> Imposing a random perturbation on a 3D-array.
     57!> On parallel computers, the random number generator is as well called for all
     58!> gridpoints of the total domain to ensure, regardless of the number of PEs
     59!> used, that the elements of the array have the same values in the same
     60!> order in every case. The perturbation range is steered by dist_range.
    6261!------------------------------------------------------------------------------!
     62 SUBROUTINE disturb_field( nzb_uv_inner, dist1, field )
     63 
    6364
    6465    USE control_parameters,   &
     
    8586    IMPLICIT NONE
    8687
    87     INTEGER(iwp) ::  i  !:
    88     INTEGER(iwp) ::  j  !:
    89     INTEGER(iwp) ::  k  !:
    90    
    91     INTEGER(iwp) ::  nzb_uv_inner(nysg:nyng,nxlg:nxrg) !:
    92 
    93     REAL(wp) ::  randomnumber  !:
    94    
    95     REAL(wp) ::  dist1(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
    96     REAL(wp) ::  field(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
    97    
    98     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  dist2  !:
     88    INTEGER(iwp) ::  i  !<
     89    INTEGER(iwp) ::  j  !<
     90    INTEGER(iwp) ::  k  !<
     91   
     92    INTEGER(iwp) ::  nzb_uv_inner(nysg:nyng,nxlg:nxrg) !<
     93
     94    REAL(wp) ::  randomnumber  !<
     95   
     96    REAL(wp) ::  dist1(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !<
     97    REAL(wp) ::  field(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !<
     98   
     99    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  dist2  !<
    99100
    100101
Note: See TracChangeset for help on using the changeset viewer.