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

Code annotations made doxygen readable

File:
1 edited

Legend:

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

    r1366 r1682  
    1  MODULE calc_mean_profile_mod
    2 
     1!> @file calc_mean_profile.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    3130! Description:
    3231! ------------
    33 ! Calculate the horizontally averaged vertical temperature profile (pr=4 in case
    34 ! of potential temperature, 44 in case of virtual potential temperature, and 64
    35 ! in case of density (ocean runs)).
     32!> Calculate the horizontally averaged vertical temperature profile (pr=4 in case
     33!> of potential temperature, 44 in case of virtual potential temperature, and 64
     34!> in case of density (ocean runs)).
    3635!------------------------------------------------------------------------------!
     36 MODULE calc_mean_profile_mod
     37 
    3738
    3839    PRIVATE
     
    4546 CONTAINS
    4647
     48!------------------------------------------------------------------------------!
     49! Description:
     50! ------------
     51!> @todo Missing subroutine description.
     52!------------------------------------------------------------------------------!
    4753    SUBROUTINE calc_mean_profile( var, pr )
    4854
     
    6369       IMPLICIT NONE
    6470       
    65        INTEGER(iwp) ::  i                  !:
    66        INTEGER(iwp) ::  j                  !:
    67        INTEGER(iwp) ::  k                  !:
    68        INTEGER(iwp) ::  pr                 !:
    69        INTEGER(iwp) ::  omp_get_thread_num !:
    70        INTEGER(iwp) ::  tn                 !:
     71       INTEGER(iwp) ::  i                  !<
     72       INTEGER(iwp) ::  j                  !<
     73       INTEGER(iwp) ::  k                  !<
     74       INTEGER(iwp) ::  pr                 !<
     75       INTEGER(iwp) ::  omp_get_thread_num !<
     76       INTEGER(iwp) ::  tn                 !<
    7177       
    7278#if defined( __nopointer )
    73        REAL(wp), DIMENSION(:,:,:) ::  var  !:
     79       REAL(wp), DIMENSION(:,:,:) ::  var  !<
    7480#else
    7581       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
Note: See TracChangeset for help on using the changeset viewer.