Ignore:
Timestamp:
Dec 19, 2017 12:49:40 PM (6 years ago)
Author:
suehring
Message:

Bugfixes in CFL check; non-allocated array used in 1D decomposition

File:
1 edited

Legend:

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

    r2696 r2709  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Bugfix in CFL check.
     23! Further bugfix, non-allocated array used in case of 1D decomposition.
    2324!
    2425! Former revisions:
     
    441442!     
    442443!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
    443 !--    variables in structure particle_type (due to the calculation of par_size)
     444!--    variables in structure particle_type (due to the calculation of par_size).
     445!--    Please note, in case of 1D decomposition ( only 1 core along
     446!--    x dimension), array trlp is not allocated, leading to program crash.
     447!--    Hence, check if array is allocated and allocate it temporarily if
     448!--    if required.
     449       IF ( .NOT. ALLOCATED( trlp ) )  ALLOCATE( trlp(1:1) )
     450
    444451       par_size = c_sizeof(trlp(1))
    445452#endif
     
    11301137    IMPLICIT NONE
    11311138   
    1132     INTEGER(iwp)  ::  i
    1133     INTEGER(iwp)  ::  j
    1134     INTEGER(iwp)  ::  k
    1135     INTEGER(iwp)  ::  n
    1136    
     1139    INTEGER(iwp)  ::  i !< running index, x-direction
     1140    INTEGER(iwp)  ::  j !< running index, y-direction
     1141    INTEGER(iwp)  ::  k !< running index, z-direction
     1142    INTEGER(iwp)  ::  n !< running index, number of particles
     1143
    11371144    DO  i = nxl, nxr
    11381145       DO  j = nys, nyn
     
    11421149             particles => grid_particles(k,j,i)%particles(1:number_of_particles)         
    11431150             DO n = 1, number_of_particles
    1144                 IF(ABS(particles(n)%speed_x) >                                 &
    1145                    (dx/(particles(n)%age-particles(n)%age_m))  .OR.            &
    1146                    ABS(particles(n)%speed_y) >                                 &
    1147                    (dx/(particles(n)%age-particles(n)%age_m))  .OR.            &
    1148                    ABS(particles(n)%speed_z) >                                 &
    1149                    ((zw(k)-zw(k-1))/(particles(n)%age-particles(n)%age_m))) THEN
    1150                    WRITE( message_string, * )                                  &
    1151                    'Particle violated CFL-criterion: particle with id ',       &
    1152                    particles(n)%id,' will be deleted!'   
    1153                    CALL message( 'lpm_check_cfl', 'PA0475', 0, 1, 0, 6, 0 )
    1154                    particles(n)%particle_mask= .FALSE.
     1151!
     1152!--             Note, check for CFL does not work at first particle timestep
     1153!--             when both, age and age_m are zero.
     1154                IF ( particles(n)%age - particles(n)%age_m > 0.0_wp )  THEN 
     1155                   IF(ABS(particles(n)%speed_x) >                              &
     1156                      (dx/(particles(n)%age-particles(n)%age_m))  .OR.         &
     1157                      ABS(particles(n)%speed_y) >                              &
     1158                      (dy/(particles(n)%age-particles(n)%age_m))  .OR.         &
     1159                      ABS(particles(n)%speed_z) >                              &
     1160                      ((zw(k)-zw(k-1))/(particles(n)%age-particles(n)%age_m))) &
     1161                   THEN
     1162                      WRITE( message_string, * )                               &
     1163                      'Particle violated CFL-criterion: particle with id ',    &
     1164                      particles(n)%id,' will be deleted!'   
     1165                      CALL message( 'lpm_check_cfl', 'PA0475', 0, 1, 0, 6, 0 )
     1166                      particles(n)%particle_mask= .FALSE.
     1167                   ENDIF
    11551168                ENDIF
    11561169             ENDDO
Note: See TracChangeset for help on using the changeset viewer.