Ignore:
Timestamp:
Mar 22, 2007 9:54:05 AM (17 years ago)
Author:
raasch
Message:

preliminary update for changes concerning non-cyclic boundary conditions

File:
1 edited

Legend:

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

    r4 r75  
    1  SUBROUTINE disturb_field( nzb_uv_inner, dist1, field, xrp, ynp )
     1 SUBROUTINE disturb_field( nzb_uv_inner, dist1, field )
    22
    33!------------------------------------------------------------------------------!
    44! Actual revisions:
    55! -----------------
    6 !
     6! xrp, ynp eliminated, 2nd+3rd argument removed from exchange horiz
    77!
    88! Former revisions:
     
    3636    IMPLICIT NONE
    3737
    38     INTEGER ::  i, j, k, xrp, ynp
     38    INTEGER ::  i, j, k
    3939    INTEGER ::  nzb_uv_inner(nys-1:nyn+1,nxl-1:nxr+1)
    4040
    4141    REAL    ::  randomnumber,                             &
    4242                dist1(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1), &
    43                 field(nzb:nzt+1,nys-1:nyn+ynp+1,nxl-1:nxr+xrp+1)
     43                field(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
    4444    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  dist2
    4545
     
    9494!
    9595!-- Exchange of ghost points for the random perturbation
    96     CALL exchange_horiz( dist1, 0, 0 )
     96    CALL exchange_horiz( dist1 )
    9797
    9898!
     
    114114!-- Exchange of ghost points for the filtered perturbation.
    115115!-- Afterwards, filter operation and exchange of ghost points are repeated.
    116     CALL exchange_horiz( dist2, 0, 0 )
     116    CALL exchange_horiz( dist2 )
    117117    DO  i = nxl, nxr
    118118       DO  j = nys, nyn
     
    125125       ENDDO
    126126    ENDDO
    127     CALL exchange_horiz( dist1, 0, 0 )
     127    CALL exchange_horiz( dist1 )
    128128
    129129!
Note: See TracChangeset for help on using the changeset viewer.