Ignore:
Timestamp:
Feb 23, 2021 4:32:41 PM (4 years ago)
Author:
hellstea
Message:

user switch for particle coupling added

File:
1 edited

Legend:

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

    r4843 r4883  
    2525! -----------------
    2626! $Id$
     27! User switch for particle coupling added
     28!
     29! 4843 2021-01-15 15:22:11Z raasch
    2730! local namelist parameter added to switch off the module although the respective module namelist
    2831! appears in the namelist file
     
    146149!--------------------------------------------------------------------------------------------------!
    147150 SUBROUTINE pmc_init_model( comm, nesting_datatransfer_mode, nesting_mode,                         &
    148                             anterpolation_buffer_width, anterpolation_starting_height, pmc_status )
     151                            anterpolation_buffer_width, anterpolation_starting_height,             &
     152                            particle_coupling, pmc_status )
    149153
    150154    USE control_parameters,                                                                        &
     
    154158        ONLY:  myid
    155159
    156       IMPLICIT NONE
     160    IMPLICIT NONE
    157161
    158162    CHARACTER(LEN=7), INTENT(INOUT) ::  nesting_datatransfer_mode  !<
     
    164168
    165169    REAL(wp), INTENT(INOUT) ::  anterpolation_starting_height  !< steering parameter for canopy restricted anterpolation
     170    LOGICAL, INTENT(INOUT)  ::  particle_coupling              !< switch for particle coupling (default .TRUE.)
    166171   
    167172    INTEGER ::  childcount     !<
     
    190195
    191196       CALL read_coupling_layout( nesting_datatransfer_mode, nesting_mode,                         &
    192             anterpolation_buffer_width, anterpolation_starting_height,                             &
     197            anterpolation_buffer_width, anterpolation_starting_height, particle_coupling,          &
    193198            pmc_status )
    194199
     
    264269    CALL MPI_BCAST( anterpolation_buffer_width, 1, MPI_INT, 0, MPI_COMM_WORLD, istat )
    265270    CALL MPI_BCAST( anterpolation_starting_height, 1, MPI_REAL, 0, MPI_COMM_WORLD, istat )
     271    CALL MPI_BCAST( particle_coupling, 1, MPI_LOGICAL, 0, MPI_COMM_WORLD, istat )
    266272!
    267273!-- Assign global MPI processes to individual models by setting the couple id
     
    435441 SUBROUTINE read_coupling_layout( nesting_datatransfer_mode, nesting_mode,                         &
    436442                                  anterpolation_buffer_width, anterpolation_starting_height,       &
    437                                   pmc_status )
     443                                  particle_coupling, pmc_status )
    438444
    439445    IMPLICIT NONE
     
    446452
    447453    REAL(wp), INTENT(INOUT) ::  anterpolation_starting_height   !< steering parameter for canopy restricted anterpolation
     454    LOGICAL, INTENT(INOUT)  ::  particle_coupling               !< switch for particle coupling (default .TRUE.)
    448455
    449456    INTEGER(iwp) ::  bad_llcorner  !<
     
    462469                                   nesting_datatransfer_mode,                                      &
    463470                                   nesting_mode,                                                   &
    464                                    switch_off_module
     471                                   switch_off_module,                                              &
     472                                   particle_coupling
    465473
    466474
Note: See TracChangeset for help on using the changeset viewer.