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

    r1354 r1682  
    1  SUBROUTINE sor( d, ddzu, ddzw, p )
    2 
     1!> @file sor.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4746! Description:
    4847! ------------
    49 ! Solve the Poisson-equation with the SOR-Red/Black-scheme.
     48!> Solve the Poisson-equation with the SOR-Red/Black-scheme.
    5049!------------------------------------------------------------------------------!
     50 SUBROUTINE sor( d, ddzu, ddzw, p )
     51 
    5152
    5253    USE grid_variables,                                                        &
     
    6566    IMPLICIT NONE
    6667
    67     INTEGER(iwp) ::  i              !:
    68     INTEGER(iwp) ::  j              !:
    69     INTEGER(iwp) ::  k              !:
    70     INTEGER(iwp) ::  n              !:
    71     INTEGER(iwp) ::  nxl1           !:
    72     INTEGER(iwp) ::  nxl2           !:
    73     INTEGER(iwp) ::  nys1           !:
    74     INTEGER(iwp) ::  nys2           !:
    75 
    76     REAL(wp)     ::  ddzu(1:nz+1)   !:
    77     REAL(wp)     ::  ddzw(1:nzt+1)  !:
    78 
    79     REAL(wp)     ::  d(nzb+1:nzt,nys:nyn,nxl:nxr)      !:
    80     REAL(wp)     ::  p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
    81 
    82     REAL(wp), DIMENSION(:), ALLOCATABLE ::  f1         !:
    83     REAL(wp), DIMENSION(:), ALLOCATABLE ::  f2         !:
    84     REAL(wp), DIMENSION(:), ALLOCATABLE ::  f3         !:
     68    INTEGER(iwp) ::  i              !<
     69    INTEGER(iwp) ::  j              !<
     70    INTEGER(iwp) ::  k              !<
     71    INTEGER(iwp) ::  n              !<
     72    INTEGER(iwp) ::  nxl1           !<
     73    INTEGER(iwp) ::  nxl2           !<
     74    INTEGER(iwp) ::  nys1           !<
     75    INTEGER(iwp) ::  nys2           !<
     76
     77    REAL(wp)     ::  ddzu(1:nz+1)   !<
     78    REAL(wp)     ::  ddzw(1:nzt+1)  !<
     79
     80    REAL(wp)     ::  d(nzb+1:nzt,nys:nyn,nxl:nxr)      !<
     81    REAL(wp)     ::  p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !<
     82
     83    REAL(wp), DIMENSION(:), ALLOCATABLE ::  f1         !<
     84    REAL(wp), DIMENSION(:), ALLOCATABLE ::  f2         !<
     85    REAL(wp), DIMENSION(:), ALLOCATABLE ::  f3         !<
    8586
    8687    ALLOCATE( f1(1:nz), f2(1:nz), f3(1:nz) )
Note: See TracChangeset for help on using the changeset viewer.