Ignore:
Timestamp:
Mar 27, 2019 11:01:36 AM (5 years ago)
Author:
hellstea
Message:

Adjustable anterpolation buffer introduced on all nest boundaries

File:
1 edited

Legend:

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

    r3655 r3819  
    2525! -----------------
    2626! $Id$
     27! Adjustable anterpolation buffer introduced on all nest boundaries, it is controlled
     28! by the new nesting_parameters parameter anterpolation_buffer_width.
     29!
     30! 3655 2019-01-07 16:51:22Z knoop
    2731! nestpar renamed to nesting_parameters
    2832!
     
    185189
    186190 SUBROUTINE pmc_init_model( comm, nesting_datatransfer_mode, nesting_mode,      &
    187                             pmc_status )
     191                            anterpolation_buffer_width, pmc_status )
    188192
    189193    USE control_parameters,                                                     &
     
    198202    CHARACTER(LEN=7), INTENT(INOUT) ::  nesting_datatransfer_mode  !<
    199203
     204    INTEGER, INTENT(INOUT) ::  anterpolation_buffer_width          !< Boundary buffer width for anterpolation
    200205    INTEGER, INTENT(INOUT) ::  comm        !<
    201206    INTEGER, INTENT(INOUT) ::  pmc_status  !<
     
    226231
    227232       CALL read_coupling_layout( nesting_datatransfer_mode, nesting_mode,      &
    228                                   pmc_status )
     233                                  anterpolation_buffer_width, pmc_status )
    229234
    230235       IF ( pmc_status /= pmc_no_namelist_found  .AND.                          &
     
    473478
    474479 SUBROUTINE read_coupling_layout( nesting_datatransfer_mode, nesting_mode,      &
    475       pmc_status )
     480      anterpolation_buffer_width, pmc_status )
    476481
    477482    IMPLICIT NONE
     
    479484    CHARACTER(LEN=8), INTENT(INOUT) ::  nesting_mode
    480485    CHARACTER(LEN=7), INTENT(INOUT) ::  nesting_datatransfer_mode
    481 
     486   
     487    INTEGER, INTENT(INOUT)      ::  anterpolation_buffer_width     !< Boundary buffer width for anterpolation
    482488    INTEGER(iwp), INTENT(INOUT) ::  pmc_status
    483489    INTEGER(iwp)                ::  bad_llcorner
     
    488494
    489495    NAMELIST /nesting_parameters/  domain_layouts, nesting_datatransfer_mode,  &
    490                                    nesting_mode
     496                                   nesting_mode, anterpolation_buffer_width
    491497   
    492498!
Note: See TracChangeset for help on using the changeset viewer.