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

    r1518 r1682  
    1 MODULE advec_s_bc_mod
    2 
     1!> @file advec_s_bc.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    6867! Description:
    6968! ------------
    70 ! Advection term for scalar quantities using the Bott-Chlond scheme.
    71 ! Computation in individual steps for each of the three dimensions.
    72 ! Limiting assumptions:
    73 ! So far the scheme has been assuming equidistant grid spacing. As this is not
    74 ! the case in the stretched portion of the z-direction, there dzw(k) is used as
    75 ! a substitute for a constant grid length. This certainly causes incorrect
    76 ! results; however, it is hoped that they are not too apparent for weakly
    77 ! stretched grids.
    78 ! NOTE: This is a provisional, non-optimised version!
     69!> Advection term for scalar quantities using the Bott-Chlond scheme.
     70!> Computation in individual steps for each of the three dimensions.
     71!> Limiting assumptions:
     72!> So far the scheme has been assuming equidistant grid spacing. As this is not
     73!> the case in the stretched portion of the z-direction, there dzw(k) is used as
     74!> a substitute for a constant grid length. This certainly causes incorrect
     75!> results; however, it is hoped that they are not too apparent for weakly
     76!> stretched grids.
     77!> NOTE: This is a provisional, non-optimised version!
    7978!------------------------------------------------------------------------------!
     79MODULE advec_s_bc_mod
     80 
    8081
    8182    PRIVATE
     
    8889 CONTAINS
    8990
     91!------------------------------------------------------------------------------!
     92! Description:
     93! ------------
     94!> @todo Missing subroutine description.
     95!------------------------------------------------------------------------------!
    9096    SUBROUTINE advec_s_bc( sk, sk_char )
    9197
     
    120126       IMPLICIT NONE
    121127
    122        CHARACTER (LEN=*) ::  sk_char !:
    123 
    124        INTEGER(iwp) ::  i         !:
    125        INTEGER(iwp) ::  ix        !:
    126        INTEGER(iwp) ::  j         !:
    127        INTEGER(iwp) ::  k         !:
    128        INTEGER(iwp) ::  ngp       !:
    129        INTEGER(iwp) ::  sr        !:
    130        INTEGER(iwp) ::  type_xz_2 !:
    131 
    132        REAL(wp) ::  cim    !:
    133        REAL(wp) ::  cimf   !:
    134        REAL(wp) ::  cip    !:
    135        REAL(wp) ::  cipf   !:
    136        REAL(wp) ::  d_new  !:
    137        REAL(wp) ::  denomi !: denominator
    138        REAL(wp) ::  fminus !:
    139        REAL(wp) ::  fplus  !:
    140        REAL(wp) ::  f2     !:
    141        REAL(wp) ::  f4     !:
    142        REAL(wp) ::  f8     !:
    143        REAL(wp) ::  f12    !:
    144        REAL(wp) ::  f24    !:
    145        REAL(wp) ::  f48    !:
    146        REAL(wp) ::  f1920  !:
    147        REAL(wp) ::  im     !:
    148        REAL(wp) ::  ip     !:
    149        REAL(wp) ::  m2     !:
    150        REAL(wp) ::  m3     !:
    151        REAL(wp) ::  numera !: numerator
    152        REAL(wp) ::  snenn  !:
    153        REAL(wp) ::  sterm  !:
    154        REAL(wp) ::  tendcy !:
    155        REAL(wp) ::  t1     !:
    156        REAL(wp) ::  t2     !:
    157 
    158        REAL(wp) ::  fmax(2)   !:
    159        REAL(wp) ::  fmax_l(2) !:
     128       CHARACTER (LEN=*) ::  sk_char !<
     129
     130       INTEGER(iwp) ::  i         !<
     131       INTEGER(iwp) ::  ix        !<
     132       INTEGER(iwp) ::  j         !<
     133       INTEGER(iwp) ::  k         !<
     134       INTEGER(iwp) ::  ngp       !<
     135       INTEGER(iwp) ::  sr        !<
     136       INTEGER(iwp) ::  type_xz_2 !<
     137
     138       REAL(wp) ::  cim    !<
     139       REAL(wp) ::  cimf   !<
     140       REAL(wp) ::  cip    !<
     141       REAL(wp) ::  cipf   !<
     142       REAL(wp) ::  d_new  !<
     143       REAL(wp) ::  denomi !< denominator
     144       REAL(wp) ::  fminus !<
     145       REAL(wp) ::  fplus  !<
     146       REAL(wp) ::  f2     !<
     147       REAL(wp) ::  f4     !<
     148       REAL(wp) ::  f8     !<
     149       REAL(wp) ::  f12    !<
     150       REAL(wp) ::  f24    !<
     151       REAL(wp) ::  f48    !<
     152       REAL(wp) ::  f1920  !<
     153       REAL(wp) ::  im     !<
     154       REAL(wp) ::  ip     !<
     155       REAL(wp) ::  m2     !<
     156       REAL(wp) ::  m3     !<
     157       REAL(wp) ::  numera !< numerator
     158       REAL(wp) ::  snenn  !<
     159       REAL(wp) ::  sterm  !<
     160       REAL(wp) ::  tendcy !<
     161       REAL(wp) ::  t1     !<
     162       REAL(wp) ::  t2     !<
     163
     164       REAL(wp) ::  fmax(2)   !<
     165       REAL(wp) ::  fmax_l(2) !<
    160166       
    161167#if defined( __nopointer )
    162        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !:
     168       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
    163169#else
    164170       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
    165171#endif
    166172
    167        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a0   !:
    168        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a1   !:
    169        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a12  !:
    170        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a2   !:
    171        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a22  !:
    172        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  immb !:
    173        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  imme !:
    174        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  impb !:
    175        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  impe !:
    176        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ipmb !:
    177        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ipme !:
    178        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ippb !:
    179        REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ippe !:
     173       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a0   !<
     174       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a1   !<
     175       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a12  !<
     176       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a2   !<
     177       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a22  !<
     178       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  immb !<
     179       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  imme !<
     180       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  impb !<
     181       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  impe !<
     182       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ipmb !<
     183       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ipme !<
     184       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ippb !<
     185       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ippe !<
    180186       
    181        REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  sk_p !:
     187       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  sk_p !<
    182188
    183189#if defined( __nec )
    184        REAL(sp) ::  m1n, m1z  !Wichtig: Division !:
    185        REAL(sp), DIMENSION(:,:), ALLOCATABLE :: m1, sw !:
     190       REAL(sp) ::  m1n, m1z  !Wichtig: Division !<
     191       REAL(sp), DIMENSION(:,:), ALLOCATABLE :: m1, sw !<
    186192#else
    187193       REAL(wp) ::  m1n, m1z
Note: See TracChangeset for help on using the changeset viewer.