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

    r75 r76  
    55! -----------------
    66! Volume flow control for non-cyclic boundary conditions added (currently only
    7 ! for the north boundary!!), 2nd+3rd argument removed from exchange horiz
     7! for the north boundary!!), 2nd+3rd argument removed from exchange horiz,
     8! mean vertical velocity is removed in case of Neumann boundary conditions
     9! both at the bottom and the top
    810!
    911! Former revisions:
     
    4547
    4648    REAL, DIMENSION(1:2) ::  volume_flow_l, volume_flow_offset
     49    REAL, DIMENSION(1:nzt) ::  w_l, w_l_l
    4750
    4851
     
    9699    ENDIF
    97100
     101!
     102!-- Remove mean vertical velocity
     103    IF ( ibc_p_b == 1  .AND.  ibc_p_t == 1 )  THEN
     104       IF ( simulated_time > 0.0 )  THEN ! otherwise nzb_w_inner is not yet known
     105          w_l = 0.0;  w_l_l = 0.0
     106          DO  i = nxl, nxr
     107             DO  j = nys, nyn
     108                DO  k = nzb_w_inner(j,i)+1, nzt
     109                   w_l_l(k) = w_l_l(k) + w(k,j,i)
     110                ENDDO
     111             ENDDO
     112          ENDDO
     113#if defined( __parallel )   
     114          CALL MPI_ALLREDUCE( w_l_l(1), w_l(1), nzt, MPI_REAL, MPI_SUM, comm2d, &
     115                              ierr )
     116#else
     117          w_l = w_l_l 
     118#endif
     119          DO  k = 1, nzt
     120             w_l(k) = w_l(k) / ngp_2dh_outer(k,0)
     121          ENDDO
     122          DO  i = nxl, nxr
     123             DO  j = nys, nyn
     124                DO  k = nzb_w_inner(j,i)+1, nzt
     125                   w(k,j,i) = w(k,j,i) - w_l(k)
     126                ENDDO
     127             ENDDO
     128          ENDDO
     129       ENDIF
     130    ENDIF
    98131
    99132!
Note: See TracChangeset for help on using the changeset viewer.