Ignore:
Timestamp:
Mar 29, 2007 12:58:32 AM (17 years ago)
Author:
raasch
Message:

changes for Neumann p conditions both at bottom and top

File:
1 edited

Legend:

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

    r4 r76  
    44! Actual revisions:
    55! -----------------
    6 !
     6! Tridiagonal coefficients adjusted for Neumann boundary conditions both at
     7! the bottom and the top.
    78!
    89! Former revisions:
     
    393394!------------------------------------------------------------------------------!
    394395
     396          USE control_parameters
     397
    395398          IMPLICIT NONE
    396399
     
    443446             ENDDO
    444447          ENDDO
     448
     449!
     450!--       Indices i=0, j=0 correspond to horizontally averaged pressure.
     451!--       The respective values of ar should be zero at all k-levels if
     452!--       acceleration of horizontally averaged vertical velocity is zero.
     453          IF ( ibc_p_b == 1  .AND.  ibc_p_t == 1 )  THEN
     454             IF ( j == 0  .AND.  nxl_z == 0 )  THEN
     455#if defined( __parallel )
     456                DO  k = 1, nz
     457                   ar(nxl_z,j,k) = 0.0
     458                ENDDO
     459#else
     460                DO  k = 1, nz
     461                   ar(k,j,nxl_z) = 0.0
     462                ENDDO
     463#endif
     464             ENDIF
     465          ENDIF
    445466
    446467       END SUBROUTINE substi
     
    14661487          IMPLICIT NONE
    14671488
    1468           INTEGER ::  i, j, k
     1489          INTEGER ::  i, k
    14691490
    14701491          REAL, DIMENSION(0:nx,nz)       ::  ar
     
    14951516          ENDDO
    14961517
     1518!
     1519!--       Indices i=0, j=0 correspond to horizontally averaged pressure.
     1520!--       The respective values of ar should be zero at all k-levels if
     1521!--       acceleration of horizontally averaged vertical velocity is zero.
     1522          IF ( ibc_p_b == 1  .AND.  ibc_p_t == 1 )  THEN
     1523             IF ( j == 0 )  THEN
     1524                DO  k = 1, nz
     1525                   ar(0,k) = 0.0
     1526                ENDDO
     1527             ENDIF
     1528          ENDIF
     1529
    14971530       END SUBROUTINE substi_1dd
    14981531
Note: See TracChangeset for help on using the changeset viewer.