Ignore:
Timestamp:
Mar 5, 2020 3:59:50 PM (4 years ago)
Author:
raasch
Message:

bugfix: cpp-directives for serial mode added

File:
1 edited

Legend:

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

    r4430 r4444  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives for serial mode added
     28!
     29! 4430 2020-02-27 18:02:20Z suehring
    2730! - Bugfix in logarithmic interpolation of near-ground particle speed (density
    2831!   was not considered).
     
    175178    USE particle_attributes
    176179
     180#if defined( __parallel )
    177181    USE pmc_particle_interface,                                                &
    178182        ONLY: pmcp_c_get_particle_from_parent, pmcp_p_fill_particle_win,       &
     
    180184              pmcp_p_delete_particles_in_fine_grid_area, pmcp_g_init,          &
    181185              pmcp_g_print_number_of_particles
     186#endif
    182187
    183188    USE pmc_interface,                                                         &
     
    307312
    308313    INTEGER(iwp), PARAMETER ::  NR_2_direction_move = 10000 !<
     314
     315#if defined( __parallel )
    309316    INTEGER(iwp)            ::  nr_move_north               !<
    310317    INTEGER(iwp)            ::  nr_move_south               !<
     
    312319    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  move_also_north
    313320    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  move_also_south
     321#endif
    314322
    315323    REAL(wp) ::  epsilon_collision !<
     
    12341242    ENDIF
    12351243
     1244#if defined( __parallel )
    12361245    IF ( nested_run )  CALL pmcp_g_init
     1246#endif
     1247
    12371248!
    12381249!-- To avoid programm abort, assign particles array to the local version of
     
    22632274                first_loop_stride = .FALSE.
    22642275             ENDDO   ! timestep loop
     2276
     2277#if defined( __parallel )
    22652278!
    22662279!--          in case of nested runs do the transfer of particles after every full model time step
     
    22742287                deleted_particles = 0
    22752288             ENDIF
     2289#endif
    22762290
    22772291!
     
    23412355 END SUBROUTINE lpm_actions
    23422356 
     2357
     2358#if defined( __parallel )
     2359!------------------------------------------------------------------------------!
     2360! Description:
     2361! ------------
     2362!
     2363!------------------------------------------------------------------------------!
     2364 SUBROUTINE particles_from_parent_to_child
     2365
     2366    CALL pmcp_c_get_particle_from_parent                         ! Child actions
     2367    CALL pmcp_p_fill_particle_win                                ! Parent actions
     2368
     2369    RETURN
     2370
     2371 END SUBROUTINE particles_from_parent_to_child
     2372
    23432373 
    23442374!------------------------------------------------------------------------------!
     
    23472377!
    23482378!------------------------------------------------------------------------------!
    2349  SUBROUTINE particles_from_parent_to_child
    2350 
    2351     CALL pmcp_c_get_particle_from_parent                         ! Child actions
    2352     CALL pmcp_p_fill_particle_win                                ! Parent actions
    2353 
    2354     RETURN
    2355 
    2356  END SUBROUTINE particles_from_parent_to_child
    2357 
    2358  
    2359 !------------------------------------------------------------------------------!
    2360 ! Description:
    2361 ! ------------
    2362 !
    2363 !------------------------------------------------------------------------------!
    23642379 SUBROUTINE particles_from_child_to_parent
    23652380
     
    23702385
    23712386 END SUBROUTINE particles_from_child_to_parent
     2387#endif
    23722388 
    23732389!------------------------------------------------------------------------------!
     
    24212437#endif
    24222438
     2439#if defined( __parallel )
    24232440    IF ( nested_run )  THEN
    24242441       CALL pmcp_g_print_number_of_particles( simulated_time+dt_3d,            &
    24252442                                              tot_number_of_particles)
    24262443    ENDIF
     2444#endif
    24272445
    24282446!
     
    69736991 SUBROUTINE lpm_exchange_horiz
    69746992
    6975     INTEGER(iwp) ::  i                 !< grid index (x) of particle positition
    69766993    INTEGER(iwp) ::  ip                !< index variable along x
    6977     INTEGER(iwp) ::  j                 !< grid index (y) of particle positition
    69786994    INTEGER(iwp) ::  jp                !< index variable along y
    69796995    INTEGER(iwp) ::  kp                !< index variable along z
    69806996    INTEGER(iwp) ::  n                 !< particle index variable
     6997
     6998#if defined( __parallel )
     6999    INTEGER(iwp) ::  i                 !< grid index (x) of particle positition
     7000    INTEGER(iwp) ::  j                 !< grid index (y) of particle positition
    69817001    INTEGER(iwp) ::  par_size          !< Particle size in bytes
    69827002    INTEGER(iwp) ::  trlp_count        !< number of particles send to left PE
     
    69977017    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  trrp  !< particles send to right PE
    69987018    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  trsp  !< particles send to south PE
     7019#endif
    69997020
    70007021    CALL cpu_log( log_point_s(23), 'lpm_exchange_horiz', 'start' )
     
    76147635 END SUBROUTINE lpm_exchange_horiz
    76157636
     7637#if defined( __parallel )
    76167638!------------------------------------------------------------------------------!
    76177639! Description:
     
    77737795    ENDDO
    77747796
    7775     RETURN
    7776 
    77777797 END SUBROUTINE lpm_add_particles_to_gridcell
     7798#endif
    77787799 
    77797800 
Note: See TracChangeset for help on using the changeset viewer.