Ignore:
Timestamp:
Jun 13, 2016 7:12:51 AM (8 years ago)
Author:
hellstea
Message:

last commit documented

File:
1 edited

Legend:

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

    r1818 r1933  
    2525! $Id$
    2626!
     27! 1818 2016-04-06 15:53:27Z maronga
     28! Initial version of purely vertical nesting introduced.
     29!
    2730! 1804 2016-04-05 16:30:18Z maronga
    2831! Removed code for parameter file check (__check)
     
    8184    USE pegrid
    8285
     86    USE pmc_interface,                                                         &
     87        ONLY : nesting_mode
     88
     89
    8390    IMPLICIT NONE
    8491
     
    160167!
    161168!-- Neumann-conditions at inflow/outflow/nested boundaries
    162     IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
    163        DO  i = nbgp, 1, -1
    164          ar(:,nxl-i) = ar(:,nxl)
    165        ENDDO
    166     ENDIF
    167     IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
    168        DO  i = 1, nbgp
    169           ar(:,nxr+i) = ar(:,nxr)
    170        ENDDO
    171     ENDIF
    172     IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
    173        DO  i = nbgp, 1, -1
    174          ar(nys-i,:) = ar(nys,:)
    175        ENDDO
    176     ENDIF
    177     IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
    178        DO  i = 1, nbgp
    179          ar(nyn+i,:) = ar(nyn,:)
    180        ENDDO
     169    IF ( nesting_mode /= 'vertical' )  THEN
     170       IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
     171          DO  i = nbgp, 1, -1
     172             ar(:,nxl-i) = ar(:,nxl)
     173          ENDDO
     174       ENDIF
     175       IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
     176          DO  i = 1, nbgp
     177             ar(:,nxr+i) = ar(:,nxr)
     178          ENDDO
     179       ENDIF
     180       IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
     181          DO  i = nbgp, 1, -1
     182             ar(nys-i,:) = ar(nys,:)
     183          ENDDO
     184       ENDIF
     185       IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
     186          DO  i = 1, nbgp
     187             ar(nyn+i,:) = ar(nyn,:)
     188          ENDDO
     189       ENDIF
    181190    ENDIF
    182191
Note: See TracChangeset for help on using the changeset viewer.