Ignore:
Timestamp:
May 11, 2016 1:06:12 PM (8 years ago)
Author:
suehring
Message:

Bugfix: enable special_exchange_horiz only for finer grid levels

File:
1 edited

Legend:

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

    r1899 r1904  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Bugfix: enable special_exchange_horiz only for finer grid levels.
     22! Some formatting adjustments and variable descriptions.
    2223!
    2324! Former revisions:
     
    17911792           ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, ibc_p_b, ibc_p_t,          &
    17921793                  inflow_l, inflow_n, inflow_r, inflow_s, maximum_grid_level,  &
    1793                   outflow_l, outflow_n, outflow_r, outflow_s,                  &
    1794                   synchronous_exchange
     1794                  mg_switch_to_pe0_level, outflow_l, outflow_n, outflow_r,     &
     1795                  outflow_s, synchronous_exchange
    17951796
    17961797       USE indices,                                                            &
     
    18021803       REAL(wp), DIMENSION(nzb:nzt_mg(grid_level)+1,                           &
    18031804                           nys_mg(grid_level)-1:nyn_mg(grid_level)+1,          &
    1804                            nxl_mg(grid_level)-1:nxr_mg(grid_level)+1) ::  p_mg  !<
    1805 
    1806        INTEGER(iwp), intent(IN) ::  color  !<
     1805                           nxl_mg(grid_level)-1:nxr_mg(grid_level)+1) ::       &
     1806                                    p_mg   !< treated array
     1807
     1808       INTEGER(iwp), intent(IN) ::  color  !< flag for grid point type (red or black)
    18071809!
    18081810!--    Local variables
    1809        INTEGER(iwp) ::  i,i1,i2  !<
    1810        INTEGER(iwp) ::  j,j1,j2  !<
    1811        INTEGER(iwp) ::  k        !<
    1812        INTEGER(iwp) ::  l        !<
    1813        INTEGER(iwp) ::  jys      !<
    1814        INTEGER(iwp) ::  jyn      !<
    1815        INTEGER(iwp) ::  ixl      !<
    1816        INTEGER(iwp) ::  ixr      !<
    1817        logical      ::  sendrecv_in_background_save  !<
    1818        logical      ::  synchronous_exchange_save    !<
    1819 
    1820        REAL(wp), DIMENSION(nzb:nzt_mg(grid_level-1)+1,                         &
    1821                            nys_mg(grid_level-1)-1:nyn_mg(grid_level-1)+1,      &
    1822                            nxl_mg(grid_level-1)-1:nxr_mg(grid_level-1)+1) ::  temp  !<
     1811       INTEGER(iwp) ::  i        !< index variable along x
     1812       INTEGER(iwp) ::  i1       !< index variable along x on coarse level
     1813       INTEGER(iwp) ::  i2       !< index variable along x on coarse level
     1814
     1815       INTEGER(iwp) ::  j        !< index variable along y
     1816       INTEGER(iwp) ::  j1       !< index variable along y on coarse level
     1817       INTEGER(iwp) ::  j2       !< index variable along y on coarse level
     1818       INTEGER(iwp) ::  k        !< index variable along z
     1819       INTEGER(iwp) ::  l        !< short for grid level
     1820       INTEGER(iwp) ::  jys      !< index for lower local PE boundary along y
     1821       INTEGER(iwp) ::  jyn      !< index for upper local PE boundary along y
     1822       INTEGER(iwp) ::  ixl      !< index for lower local PE boundary along x
     1823       INTEGER(iwp) ::  ixr      !< index for upper local PE boundary along x
     1824
     1825       LOGICAL      ::  sendrecv_in_background_save  !< dummy to reset sendrecv_in_background to prescribed value
     1826       LOGICAL      ::  synchronous_exchange_save    !< dummy to reset synchronous_exchange to prescribed value
     1827
     1828       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  temp  !< temporary array on next coarser grid level
    18231829
    18241830#if defined ( __parallel )
     
    18321838       ind_even_odd = even_odd_level(grid_level)
    18331839
    1834        jys = nys_mg(grid_level-1)
    1835        jyn = nyn_mg(grid_level-1)
    1836        ixl = nxl_mg(grid_level-1)
    1837        ixr = nxr_mg(grid_level-1)
    1838 
    1839 !
    1840 !--    Restricted transfer only on finer levels with enough data
    1841        IF ( ngp_xz(grid_level) >= 900 .OR. ngp_yz(grid_level) >= 900 )  THEN
     1840!
     1841!--    Restricted transfer only on finer levels with enough data.
     1842!--    Restricted transfer is not possible for levels smaller or equal to
     1843!--    'switch to PE0 levels', since array bounds does not fit. Moreover,
     1844!--    it is not possible for the coarsest grid level, since the dimensions
     1845!--    of temp are not defined. For such cases, normal exchange_horiz is called.
     1846       IF ( l > 1 .AND. l > mg_switch_to_pe0_level + 1 .AND.                   &
     1847            ( ngp_xz(grid_level) >= 900 .OR. ngp_yz(grid_level) >= 900 ) )  THEN
     1848
     1849          jys = nys_mg(grid_level-1)
     1850          jyn = nyn_mg(grid_level-1)
     1851          ixl = nxl_mg(grid_level-1)
     1852          ixr = nxr_mg(grid_level-1)
     1853          ALLOCATE( temp(nzb:nzt_mg(l-1)+1,jys-1:jyn+1,ixl-1:ixr+1) )
    18421854!
    18431855!--       Handling the even k Values
     
    23052317          ENDDO
    23062318
     2319          DEALLOCATE( temp )
     2320
    23072321       ELSE
    23082322
Note: See TracChangeset for help on using the changeset viewer.