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

    r1354 r1682  
    1  MODULE advec_u_pw_mod
    2 
     1!> @file advec_u_pw.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4645! Description:
    4746! ------------
    48 ! Advection term for u velocity-component using Piacsek and Williams.
    49 ! Vertical advection at the first grid point above the surface is done with
    50 ! normal centred differences, because otherwise no information from the surface
    51 ! would be communicated upwards due to w=0 at K=nzb.
     47!> Advection term for u velocity-component using Piacsek and Williams.
     48!> Vertical advection at the first grid point above the surface is done with
     49!> normal centred differences, because otherwise no information from the surface
     50!> would be communicated upwards due to w=0 at K=nzb.
    5251!------------------------------------------------------------------------------!
     52 MODULE advec_u_pw_mod
     53 
    5354
    5455    PRIVATE
     
    6465
    6566!------------------------------------------------------------------------------!
    66 ! Call for all grid points
     67! Description:
     68! ------------
     69!> Call for all grid points
    6770!------------------------------------------------------------------------------!
    6871    SUBROUTINE advec_u_pw
     
    8588       IMPLICIT NONE
    8689
    87        INTEGER(iwp) ::  i !:
    88        INTEGER(iwp) ::  j !:
    89        INTEGER(iwp) ::  k !:
     90       INTEGER(iwp) ::  i !<
     91       INTEGER(iwp) ::  j !<
     92       INTEGER(iwp) ::  k !<
    9093       
    91        REAL(wp)    ::  gu !:
    92        REAL(wp)    ::  gv !:
     94       REAL(wp)    ::  gu !<
     95       REAL(wp)    ::  gv !<
    9396 
    9497       gu = 2.0_wp * u_gtrans
     
    114117
    115118!------------------------------------------------------------------------------!
    116 ! Call for grid point i,j
     119! Description:
     120! ------------
     121!> Call for grid point i,j
    117122!------------------------------------------------------------------------------!
    118123    SUBROUTINE advec_u_pw_ij( i, j )
     
    135140       IMPLICIT NONE
    136141
    137        INTEGER(iwp) ::  i !:
    138        INTEGER(iwp) ::  j !:
    139        INTEGER(iwp) ::  k !:
     142       INTEGER(iwp) ::  i !<
     143       INTEGER(iwp) ::  j !<
     144       INTEGER(iwp) ::  k !<
    140145       
    141        REAL(wp)    ::  gu !:
    142        REAL(wp)    ::  gv !:
     146       REAL(wp)    ::  gu !<
     147       REAL(wp)    ::  gv !<
    143148
    144149       gu = 2.0_wp * u_gtrans
Note: See TracChangeset for help on using the changeset viewer.