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

    r1375 r1682  
    1  MODULE buoyancy_mod
    2 
     1!> @file buoyancy.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    8180! Description:
    8281! ------------
    83 ! Buoyancy term of the third component of the equation of motion.
    84 ! WARNING: humidity is not regarded when using a sloping surface!
    85 !------------------------------------------------------------------------------!
     82!> Buoyancy term of the third component of the equation of motion.
     83!> @attention Humidity is not regarded when using a sloping surface!
     84!------------------------------------------------------------------------------!
     85 MODULE buoyancy_mod
     86 
    8687
    8788    PRIVATE
     
    101102
    102103!------------------------------------------------------------------------------!
    103 ! Call for all grid points
     104! Description:
     105! ------------
     106!> Call for all grid points
    104107!------------------------------------------------------------------------------!
    105108    SUBROUTINE buoyancy( var, wind_component )
     
    123126       IMPLICIT NONE
    124127
    125        INTEGER(iwp) ::  i              !:
    126        INTEGER(iwp) ::  j              !:
    127        INTEGER(iwp) ::  k              !:
    128        INTEGER(iwp) ::  wind_component !:
     128       INTEGER(iwp) ::  i              !<
     129       INTEGER(iwp) ::  j              !<
     130       INTEGER(iwp) ::  k              !<
     131       INTEGER(iwp) ::  wind_component !<
    129132       
    130133#if defined( __nopointer )
    131        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !:
     134       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !<
    132135#else
    133136       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
     
    197200
    198201!------------------------------------------------------------------------------!
    199 ! Call for all grid points - accelerator version
     202! Description:
     203! ------------
     204!> Call for all grid points - accelerator version
    200205!------------------------------------------------------------------------------!
    201206    SUBROUTINE buoyancy_acc( var, wind_component )
     
    219224       IMPLICIT NONE
    220225
    221        INTEGER(iwp) ::  i              !:
    222        INTEGER(iwp) ::  j              !:
    223        INTEGER(iwp) ::  k              !:
    224        INTEGER(iwp) ::  wind_component !:
     226       INTEGER(iwp) ::  i              !<
     227       INTEGER(iwp) ::  j              !<
     228       INTEGER(iwp) ::  k              !<
     229       INTEGER(iwp) ::  wind_component !<
    225230       
    226231#if defined( __nopointer )
    227        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !:
     232       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !<
    228233#else
    229234       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
     
    297302
    298303!------------------------------------------------------------------------------!
    299 ! Call for grid point i,j
    300 ! ATTENTION: PGI-compiler creates SIGFPE if opt>1 is used! Therefore, opt=1 is
    301 !            forced by compiler-directive.
     304! Description:
     305! ------------
     306!> Call for grid point i,j
     307!> @attention PGI-compiler creates SIGFPE if opt>1 is used! Therefore, opt=1 is
     308!>            forced by compiler-directive.
    302309!------------------------------------------------------------------------------!
    303310!pgi$r opt=1
     
    321328       IMPLICIT NONE
    322329
    323        INTEGER(iwp) ::  i              !:
    324        INTEGER(iwp) ::  j              !:
    325        INTEGER(iwp) ::  k              !:
    326        INTEGER(iwp) ::  pr             !:
    327        INTEGER(iwp) ::  wind_component !:
     330       INTEGER(iwp) ::  i              !<
     331       INTEGER(iwp) ::  j              !<
     332       INTEGER(iwp) ::  k              !<
     333       INTEGER(iwp) ::  pr             !<
     334       INTEGER(iwp) ::  wind_component !<
    328335       
    329336#if defined( __nopointer )
    330        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !:
     337       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !<
    331338#else
    332339       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
Note: See TracChangeset for help on using the changeset viewer.