Changeset 4044 for palm/trunk/SOURCE/lagrangian_particle_model_mod.f90
- Timestamp:
- Jun 19, 2019 12:28:27 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/lagrangian_particle_model_mod.f90
r4043 r4044 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Bugfix in case of grid strecting: corrected calculation of k-Index 28 ! 29 ! 4043 2019-06-18 16:59:00Z schwenkel 27 30 ! Remove min_nr_particle, Add lpm_droplet_interactions_ptq into module 28 31 ! … … 186 189 particle_maximum_age, iran, & 187 190 simulated_time, topography, dopts_time_count, & 188 time_since_reference_point, rho_surface, u_gtrans, v_gtrans 191 time_since_reference_point, rho_surface, u_gtrans, v_gtrans, & 192 dz_stretch_level, dz_stretch_level_start 189 193 190 194 USE cpulog, & … … 682 686 683 687 14 CONTINUE 684 688 685 689 END SUBROUTINE lpm_parin 686 690 … … 1329 1333 ip = INT( tmp_particle%x * ddx ) 1330 1334 jp = INT( tmp_particle%y * ddy ) 1331 kp = INT( tmp_particle%z / dz(1) + 1 + offset_ocean_nzt ) 1332 DO WHILE( zw(kp) < tmp_particle%z ) 1333 kp = kp + 1 1334 ENDDO 1335 DO WHILE( zw(kp-1) > tmp_particle%z ) 1336 kp = kp - 1 1337 ENDDO 1335 ! 1336 !-- In case of stretching the actual k index is found iteratively 1337 IF ( dz_stretch_level .NE. -9999999.9 .OR. & 1338 dz_stretch_level_start(1) .NE. -9999999.9 ) THEN 1339 kp = MINLOC( ABS( tmp_particle%z - zu ), DIM = 1 ) - 1 1340 ELSE 1341 kp = INT( tmp_particle%z / dz(1) + 1 + offset_ocean_nzt ) 1342 ENDIF 1338 1343 ! 1339 1344 !-- Determine surface level. Therefore, check for … … 6923 6928 6924 6929 ALLOCATE(rvlp(MAX(1,trlp_count_recv))) 6925 ! 6930 ! 6926 6931 !-- This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit 6927 6932 !-- variables in structure particle_type (due to the calculation of par_size) … … 6990 6995 trsp_count = nr_move_south 6991 6996 trnp_count = nr_move_north 6992 6997 6993 6998 trsp(1:nr_move_south) = move_also_south(1:nr_move_south) 6994 6999 trnp(1:nr_move_north) = move_also_north(1:nr_move_north) … … 7338 7343 ip = particle_array(n)%x * ddx 7339 7344 jp = particle_array(n)%y * ddy 7340 kp = particle_array(n)%z / dz(1) + 1 + offset_ocean_nzt 7341 ! 7342 !-- In case of grid stretching a particle might be above or below the 7343 !-- previously calculated particle grid box (indices). 7344 DO WHILE( zw(kp) < particle_array(n)%z ) 7345 kp = kp + 1 7346 ENDDO 7347 7348 DO WHILE( zw(kp-1) > particle_array(n)%z ) 7349 kp = kp - 1 7350 ENDDO 7345 ! 7346 !-- In case of stretching the actual k index must be found 7347 IF ( dz_stretch_level .NE. -9999999.9 .OR. & 7348 dz_stretch_level_start(1) .NE. -9999999.9 ) THEN 7349 kp = MINLOC( ABS( particle_array(n)%z - zu ), DIM = 1 ) - 1 7350 ELSE 7351 kp = INT( particle_array(n)%z / dz(1) + 1 + offset_ocean_nzt ) 7352 ENDIF 7351 7353 7352 7354 IF ( ip >= nxl .AND. ip <= nxr .AND. jp >= nys .AND. jp <= nyn &
Note: See TracChangeset
for help on using the changeset viewer.