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

    r1375 r1682  
    1  MODULE advec_s_up_mod
    2 
     1!> @file advec_s_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:
     
    5554! Description:
    5655! ------------
    57 ! Advection term for scalar quantities using the Upstream scheme.
    58 ! NOTE: vertical advection at k=1 still has wrong grid spacing for w>0!
    59 !       The same problem occurs for all topography boundaries!
    60 !------------------------------------------------------------------------------!
     56!> Advection term for scalar quantities using the Upstream scheme.
     57!> NOTE: vertical advection at k=1 still has wrong grid spacing for w>0!
     58!>       The same problem occurs for all topography boundaries!
     59!------------------------------------------------------------------------------!
     60 MODULE advec_s_up_mod
     61 
    6162
    6263    PRIVATE
     
    7273
    7374!------------------------------------------------------------------------------!
    74 ! Call for all grid points
     75! Description:
     76! ------------
     77!> Call for all grid points
    7578!------------------------------------------------------------------------------!
    7679    SUBROUTINE advec_s_up( sk )
     
    9497       IMPLICIT NONE
    9598
    96        INTEGER(iwp) ::  i !:
    97        INTEGER(iwp) ::  j !:
    98        INTEGER(iwp) ::  k !:
    99 
    100        REAL(wp) ::  ukomp !:
    101        REAL(wp) ::  vkomp !:
    102        REAL(wp) ::  wkomp !:
     99       INTEGER(iwp) ::  i !<
     100       INTEGER(iwp) ::  j !<
     101       INTEGER(iwp) ::  k !<
     102
     103       REAL(wp) ::  ukomp !<
     104       REAL(wp) ::  vkomp !<
     105       REAL(wp) ::  wkomp !<
    103106#if defined( __nopointer )
    104        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
     107       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
    105108#else
    106109       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
     
    150153
    151154!------------------------------------------------------------------------------!
    152 ! Call for grid point i,j
     155! Description:
     156! ------------
     157!> Call for grid point i,j
    153158!------------------------------------------------------------------------------!
    154159    SUBROUTINE advec_s_up_ij( i, j, sk )
     
    171176       IMPLICIT NONE
    172177
    173        INTEGER(iwp) ::  i !:
    174        INTEGER(iwp) ::  j !:
    175        INTEGER(iwp) ::  k !:
    176 
    177        REAL(wp) ::  ukomp !:
    178        REAL(wp) ::  vkomp !:
    179        REAL(wp) ::  wkomp !:
     178       INTEGER(iwp) ::  i !<
     179       INTEGER(iwp) ::  j !<
     180       INTEGER(iwp) ::  k !<
     181
     182       REAL(wp) ::  ukomp !<
     183       REAL(wp) ::  vkomp !<
     184       REAL(wp) ::  wkomp !<
    180185       
    181186#if defined( __nopointer )
    182        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
     187       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
    183188#else
    184189       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
Note: See TracChangeset for help on using the changeset viewer.