Ignore:
Timestamp:
Feb 14, 2018 4:01:55 PM (6 years ago)
Author:
thiele
Message:

Introduce particle transfer in nested models

File:
1 edited

Legend:

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

    r2718 r2801  
     1MODULE lpm_mod
     2
    13!> @file lpm.f90
    24!------------------------------------------------------------------------------!
     
    2527! -----------------
    2628! $Id$
     29! Changed lpm from subroutine to module.
     30! Introduce particle transfer in nested models.
     31!
     32! 2718 2018-01-02 08:49:38Z maronga
    2733! Corrected "Former revisions" section
    2834!
     
    139145!> Particle advection
    140146!------------------------------------------------------------------------------!
    141  SUBROUTINE lpm
    142147 
    143148
     
    163168        ONLY: lpm_create_particle, PHASE_RELEASE
    164169
    165     USE lpm_pack_and_sort_mod,                                                   &
    166         ONLY:  lpm_sort_in_subboxes, lpm_sort_timeloop_done
     170    USE lpm_pack_and_sort_mod
    167171
    168172    USE particle_attributes,                                                   &
     
    179183    USE pegrid
    180184
     185 USE pmc_particle_interface,                                                &
     186     ONLY: pmcp_c_get_particle_from_parent, pmcp_p_fill_particle_win,       &
     187           pmcp_c_send_particle_to_parent, pmcp_p_empty_particle_win,       &
     188           pmcp_p_delete_particles_in_fine_grid_area
     189
     190    USE pmc_interface,                                                      &
     191       ONLY: nested_run
     192
     193 IMPLICIT NONE
     194 PRIVATE
     195 SAVE
     196
     197 INTERFACE lpm
     198    MODULE PROCEDURE lpm
     199 END INTERFACE lpm
     200
     201 PUBLIC lpm
     202
     203CONTAINS
     204 SUBROUTINE lpm
    181205    IMPLICIT NONE
    182206
     
    424448!--    Horizontal boundary conditions including exchange between subdmains
    425449       CALL lpm_exchange_horiz
    426 !
    427 !--    Pack particles (eliminate those marked for deletion),
    428 !--    determine new number of particles
    429        CALL lpm_sort_in_subboxes
    430 !
    431 !--    Initialize variables for the next (sub-) timestep, i.e., for marking
    432 !--    those particles to be deleted after the timestep
    433        deleted_particles = 0
     450
     451       IF ( .NOT. dt_3d_reached .OR. .NOT. nested_run )   THEN    ! IF .FALSE., lpm_sort_in_subboxes is done inside pcmp
     452!
     453!--       Pack particles (eliminate those marked for deletion),
     454!--       determine new number of particles
     455          CALL lpm_sort_in_subboxes
     456!
     457!--       Initialize variables for the next (sub-) timestep, i.e., for marking
     458!--       those particles to be deleted after the timestep
     459          deleted_particles = 0
     460       ENDIF
    434461
    435462       IF ( dt_3d_reached )  EXIT
     
    437464       first_loop_stride = .FALSE.
    438465    ENDDO   ! timestep loop
     466!   
     467!-- in case of nested runs do the transfer of particles after every full model time step
     468    IF ( nested_run )   THEN
     469       CALL particles_from_parent_to_child
     470       CALL particles_from_child_to_parent
     471       CALL pmcp_p_delete_particles_in_fine_grid_area
     472
     473       CALL lpm_sort_in_subboxes
     474
     475       deleted_particles = 0
     476    ENDIF
    439477
    440478!
     
    469507
    470508 END SUBROUTINE lpm
     509
     510 SUBROUTINE particles_from_parent_to_child
     511    IMPLICIT NONE
     512
     513    CALL pmcp_c_get_particle_from_parent                         ! Child actions
     514    CALL pmcp_p_fill_particle_win                                ! Parent actions
     515
     516    RETURN
     517 END SUBROUTINE particles_from_parent_to_child
     518
     519 SUBROUTINE particles_from_child_to_parent
     520    IMPLICIT NONE
     521
     522    CALL pmcp_c_send_particle_to_parent                         ! Child actions
     523    CALL pmcp_p_empty_particle_win                              ! Parent actions
     524
     525    RETURN
     526 END SUBROUTINE particles_from_child_to_parent
     527
     528
     529END MODULE lpm_mod
Note: See TracChangeset for help on using the changeset viewer.