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_v_up.f90

    r1354 r1682  
    1  MODULE advec_v_up_mod
    2 
     1!> @file advec_v_up.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 the v velocity-component using upstream scheme.
    49 ! NOTE: vertical advection at k=1 still has wrong grid spacing for w>0!
    50 !       The same problem occurs for all topography boundaries!
    51 !------------------------------------------------------------------------------!
     47!> Advection term for the v velocity-component using upstream scheme.
     48!> NOTE: vertical advection at k=1 still has wrong grid spacing for w>0!
     49!>       The same problem occurs for all topography boundaries!
     50!------------------------------------------------------------------------------!
     51 MODULE advec_v_up_mod
     52 
    5253
    5354    PRIVATE
     
    6364
    6465!------------------------------------------------------------------------------!
    65 ! Call for all grid points
     66! Description:
     67! ------------
     68!> Call for all grid points
    6669!------------------------------------------------------------------------------!
    6770    SUBROUTINE advec_v_up
     
    8487       IMPLICIT NONE
    8588
    86        INTEGER(iwp) ::  i !:
    87        INTEGER(iwp) ::  j !:
    88        INTEGER(iwp) ::  k !:
    89 
    90        REAL(wp) ::  ukomp !:
    91        REAL(wp) ::  vkomp !:
    92        REAL(wp) ::  wkomp !:       
     89       INTEGER(iwp) ::  i !<
     90       INTEGER(iwp) ::  j !<
     91       INTEGER(iwp) ::  k !<
     92
     93       REAL(wp) ::  ukomp !<
     94       REAL(wp) ::  vkomp !<
     95       REAL(wp) ::  wkomp !<       
    9396
    9497
     
    137140
    138141!------------------------------------------------------------------------------!
    139 ! Call for grid point i,j
     142! Description:
     143! ------------
     144!> Call for grid point i,j
    140145!------------------------------------------------------------------------------!
    141146    SUBROUTINE advec_v_up_ij( i, j )
     
    158163       IMPLICIT NONE
    159164
    160        INTEGER(iwp) ::  i !:
    161        INTEGER(iwp) ::  j !:
    162        INTEGER(iwp) ::  k !:
    163 
    164        REAL(wp) ::  ukomp !:
    165        REAL(wp) ::  vkomp !:
    166        REAL(wp) ::  wkomp !:
     165       INTEGER(iwp) ::  i !<
     166       INTEGER(iwp) ::  j !<
     167       INTEGER(iwp) ::  k !<
     168
     169       REAL(wp) ::  ukomp !<
     170       REAL(wp) ::  vkomp !<
     171       REAL(wp) ::  wkomp !<
    167172
    168173
Note: See TracChangeset for help on using the changeset viewer.