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

    r1586 r1682  
    1  SUBROUTINE sum_up_3d_data
    2 
     1!> @file sum_up_3d_data.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    7574! Description:
    7675! ------------
    77 ! Sum-up the values of 3d-arrays. The real averaging is later done in routine
    78 ! average_3d_data.
     76!> Sum-up the values of 3d-arrays. The real averaging is later done in routine
     77!> average_3d_data.
    7978!------------------------------------------------------------------------------!
     79 SUBROUTINE sum_up_3d_data
     80 
    8081
    8182    USE arrays_3d,                                                             &
     
    121122    IMPLICIT NONE
    122123
    123     INTEGER(iwp) ::  i   !:
    124     INTEGER(iwp) ::  ii  !:
    125     INTEGER(iwp) ::  j   !:
    126     INTEGER(iwp) ::  k   !:
    127     INTEGER(iwp) ::  n   !:
    128     INTEGER(iwp) ::  psi !:
    129 
    130     REAL(wp)     ::  mean_r !:
    131     REAL(wp)     ::  s_r2   !:
    132     REAL(wp)     ::  s_r3   !:
     124    INTEGER(iwp) ::  i   !<
     125    INTEGER(iwp) ::  ii  !<
     126    INTEGER(iwp) ::  j   !<
     127    INTEGER(iwp) ::  k   !<
     128    INTEGER(iwp) ::  n   !<
     129    INTEGER(iwp) ::  psi !<
     130
     131    REAL(wp)     ::  mean_r !<
     132    REAL(wp)     ::  s_r2   !<
     133    REAL(wp)     ::  s_r3   !<
    133134
    134135    CALL cpu_log (log_point(34),'sum_up_3d_data','start')
Note: See TracChangeset for help on using the changeset viewer.