Ignore:
Timestamp:
Nov 4, 2020 1:12:46 PM (3 years ago)
Author:
hellstea
Message:

Canopy-restricted anterpolation introduced

File:
1 edited

Legend:

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

    r4650 r4771  
    2525! -----------------
    2626! $Id$
     27! Canopy-restricted anterpolation introduced. New namelist parameter anterpolation_starting_height
     28! introduced for controlling canopy-restricted anterpolation.
     29!
     30! 4650 2020-08-25 14:35:50Z raasch
    2731! bugfix for r4649
    2832!
     
    138142!--------------------------------------------------------------------------------------------------!
    139143 SUBROUTINE pmc_init_model( comm, nesting_datatransfer_mode, nesting_mode,                         &
    140                             anterpolation_buffer_width, pmc_status )
     144                            anterpolation_buffer_width, anterpolation_starting_height, pmc_status )
    141145
    142146    USE control_parameters,                                                                        &
     
    155159    INTEGER, INTENT(INOUT) ::  pmc_status                  !<
    156160
     161    REAL(wp), INTENT(INOUT) ::  anterpolation_starting_height  !< steering parameter for canopy restricted anterpolation
     162   
    157163    INTEGER ::  childcount     !<
    158164    INTEGER ::  i              !<
     
    180186
    181187       CALL read_coupling_layout( nesting_datatransfer_mode, nesting_mode,                         &
    182                                   anterpolation_buffer_width, pmc_status )
     188            anterpolation_buffer_width, anterpolation_starting_height,                             &
     189            pmc_status )
    183190
    184191       IF ( pmc_status /= pmc_no_namelist_found  .AND.                                             &
     
    252259                    MPI_COMM_WORLD, istat )
    253260    CALL MPI_BCAST( anterpolation_buffer_width, 1, MPI_INT, 0, MPI_COMM_WORLD, istat )
     261    CALL MPI_BCAST( anterpolation_starting_height, 1, MPI_REAL, 0, MPI_COMM_WORLD, istat )
    254262!
    255263!-- Assign global MPI processes to individual models by setting the couple id
     
    422430!--------------------------------------------------------------------------------------------------!
    423431 SUBROUTINE read_coupling_layout( nesting_datatransfer_mode, nesting_mode,                         &
    424                                   anterpolation_buffer_width, pmc_status )
     432                                  anterpolation_buffer_width, anterpolation_starting_height,       &
     433                                  pmc_status )
    425434
    426435    IMPLICIT NONE
     
    431440    INTEGER, INTENT(INOUT)      ::  anterpolation_buffer_width  !< Boundary buffer width for anterpolation
    432441    INTEGER(iwp), INTENT(INOUT) ::  pmc_status                  !<
     442
     443    REAL(wp), INTENT(INOUT) ::  anterpolation_starting_height   !< steering parameter for canopy restricted anterpolation
    433444
    434445    INTEGER(iwp) ::  bad_llcorner  !<
     
    441452                                   nesting_datatransfer_mode,                                      &
    442453                                   nesting_mode,                                                   &
    443                                    anterpolation_buffer_width
     454                                   anterpolation_buffer_width,                                     &
     455                                   anterpolation_starting_height
    444456
    445457!
Note: See TracChangeset for help on using the changeset viewer.