Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/sor.f90

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    2834! 1036 2012-10-22 13:43:42Z raasch
    2935! code put under GPL (PALM 3.9)
    30 !
    31 ! 707 2011-03-29 11:39:40Z raasch
    32 ! bc_lr/ns replaced by bc_lr/ns_cyc
    33 !
    34 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    35 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
    36 ! Call of exchange_horiz are modified.
    37 ! bug removed in declaration of ddzw(), nz replaced by nzt+1
    38 !
    39 ! 75 2007-03-22 09:54:05Z raasch
    40 ! 2nd+3rd argument removed from exchange horiz
    41 !
    42 ! RCS Log replace by Id keyword, revision history cleaned up
    43 !
    44 ! Revision 1.9  2005/03/26 21:02:23  raasch
    45 ! Implementation of non-cyclic (Neumann) horizontal boundary conditions,
    46 ! dx2,dy2 replaced by ddx2,ddy2
    4736!
    4837! Revision 1.1  1997/08/11 06:25:56  raasch
     
    5544!------------------------------------------------------------------------------!
    5645
    57     USE grid_variables
    58     USE indices
    59     USE pegrid
    60     USE control_parameters
     46    USE grid_variables,                                                        &
     47        ONLY:  ddx2, ddy2
     48
     49    USE indices,                                                               &
     50        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nz, nzb, nzt
     51
     52    USE kinds
     53
     54    USE control_parameters,                                                    &
     55        ONLY:  bc_lr_cyc, bc_ns_cyc, ibc_p_b, ibc_p_t, inflow_l, inflow_n,     &
     56               inflow_r, inflow_s, n_sor, omega_sor, outflow_l, outflow_n,     &
     57               outflow_r, outflow_s
    6158
    6259    IMPLICIT NONE
    6360
    64     INTEGER ::  i, j, k, n, nxl1, nxl2, nys1, nys2
    65     REAL    ::  ddzu(1:nz+1), ddzw(1:nzt+1)
    66     REAL    ::  d(nzb+1:nzt,nys:nyn,nxl:nxr),         &
    67                 p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)
    68     REAL, DIMENSION(:), ALLOCATABLE ::  f1, f2, f3
     61    INTEGER(iwp) ::  i              !:
     62    INTEGER(iwp) ::  j              !:
     63    INTEGER(iwp) ::  k              !:
     64    INTEGER(iwp) ::  n              !:
     65    INTEGER(iwp) ::  nxl1           !:
     66    INTEGER(iwp) ::  nxl2           !:
     67    INTEGER(iwp) ::  nys1           !:
     68    INTEGER(iwp) ::  nys2           !:
     69
     70    REAL(wp)     ::  ddzu(1:nz+1)   !:
     71    REAL(wp)     ::  ddzw(1:nzt+1)  !:
     72
     73    REAL(wp)     ::  d(nzb+1:nzt,nys:nyn,nxl:nxr)      !:
     74    REAL(wp)     ::  p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
     75
     76    REAL(wp), DIMENSION(:), ALLOCATABLE ::  f1         !:
     77    REAL(wp), DIMENSION(:), ALLOCATABLE ::  f2         !:
     78    REAL(wp), DIMENSION(:), ALLOCATABLE ::  f3         !:
    6979
    7080    ALLOCATE( f1(1:nz), f2(1:nz), f3(1:nz) )
Note: See TracChangeset for help on using the changeset viewer.