Changeset 2628 for palm


Ignore:
Timestamp:
Nov 20, 2017 12:40:38 PM (6 years ago)
Author:
schwenkel
Message:

enable particle advection with grid stretching and some formatation changes in lpm

Location:
palm/trunk/SOURCE
Files:
5 edited

Legend:

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

    r2575 r2628  
    2525! -----------------
    2626! $Id$
     27! Enabled particle advection with grid stretching -> Removed parameter check
     28!
     29! 2575 2017-10-24 09:57:58Z maronga
    2730! Renamed phi --> latitude
    2831!
     
    880883
    881884!
    882 !-- Check if vertical grid stretching is used together with particles
    883     IF ( dz_stretch_level < 100000.0_wp .AND. particle_advection )  THEN
    884        message_string = 'Vertical grid stretching is not allowed together ' // &
    885                         'with particle advection.'
    886        CALL message( 'check_parameters', 'PA0017', 1, 2, 0, 6, 0 )
    887     ENDIF
    888 
    889 !
    890885!-- Check topography setting (check for illegal parameter combinations)
    891886    IF ( topography /= 'flat' )  THEN
  • palm/trunk/SOURCE/lpm_advec.f90

    r2610 r2628  
    2020! Current revisions:
    2121! ------------------
    22 !
     22!  Removed indices ilog and jlog which are no longer needed since particle box
     23! locations are identical to scalar boxes and topography.
     24
    2325!
    2426! Former revisions:
     
    167169    INTEGER(iwp) ::  i                           !< index variable along x
    168170    INTEGER(iwp) ::  ip                          !< index variable along x
    169     INTEGER(iwp) ::  ilog                        !< index variable along x
    170171    INTEGER(iwp) ::  j                           !< index variable along y
    171172    INTEGER(iwp) ::  jp                          !< index variable along y
    172     INTEGER(iwp) ::  jlog                        !< index variable along y
    173173    INTEGER(iwp) ::  k                           !< index variable along z
    174174    INTEGER(iwp) ::  k_wall                      !< vertical index of topography top
     
    299299!--       First, check if particle is located below first vertical grid level
    300300!--       above topography (Prandtl-layer height)
    301           ilog = particles(n)%x * ddx
    302           jlog = particles(n)%y * ddy
    303 !
    304301!--       Determine vertical index of topography top
    305           k_wall = get_topography_top_index( jlog, ilog, 's' )
     302          k_wall = get_topography_top_index( jp, ip, 's' )
    306303
    307304          IF ( constant_flux_layer  .AND.  zv(n) - zw(k_wall) < z_p )  THEN
     
    327324!--             Get friction velocity and momentum flux from new surface data
    328325!--             types.
    329                 IF ( surf_def_h(0)%start_index(jlog,ilog) <=                   &
    330                      surf_def_h(0)%end_index(jlog,ilog) )  THEN
    331                    surf_start = surf_def_h(0)%start_index(jlog,ilog)
     326                IF ( surf_def_h(0)%start_index(jp,ip) <=                   &
     327                     surf_def_h(0)%end_index(jp,ip) )  THEN
     328                   surf_start = surf_def_h(0)%start_index(jp,ip)
    332329!--                Limit friction velocity. In narrow canyons or holes the
    333330!--                friction velocity can become very small, resulting in a too
     
    335332                   us_int    = MAX( surf_def_h(0)%us(surf_start), 0.01_wp ) 
    336333                   usws_int  = surf_def_h(0)%usws(surf_start)
    337                 ELSEIF ( surf_lsm_h%start_index(jlog,ilog) <=                  &
    338                          surf_lsm_h%end_index(jlog,ilog) )  THEN
    339                    surf_start = surf_lsm_h%start_index(jlog,ilog)
     334                ELSEIF ( surf_lsm_h%start_index(jp,ip) <=                  &
     335                         surf_lsm_h%end_index(jp,ip) )  THEN
     336                   surf_start = surf_lsm_h%start_index(jp,ip)
    340337                   us_int    = MAX( surf_lsm_h%us(surf_start), 0.01_wp ) 
    341338                   usws_int  = surf_lsm_h%usws(surf_start)
    342                 ELSEIF ( surf_usm_h%start_index(jlog,ilog) <=                  &
    343                          surf_usm_h%end_index(jlog,ilog) )  THEN
    344                    surf_start = surf_usm_h%start_index(jlog,ilog)
     339                ELSEIF ( surf_usm_h%start_index(jp,ip) <=                  &
     340                         surf_usm_h%end_index(jp,ip) )  THEN
     341                   surf_start = surf_usm_h%start_index(jp,ip)
    345342                   us_int    = MAX( surf_usm_h%us(surf_start), 0.01_wp ) 
    346343                   usws_int  = surf_usm_h%usws(surf_start)
     
    396393       DO  n = start_index(nb), end_index(nb)
    397394
    398           ilog = particles(n)%x * ddx
    399           jlog = particles(n)%y * ddy
    400395!
    401396!--       Determine vertical index of topography top
    402           k_wall = get_topography_top_index( jlog,ilog, 's' )
     397          k_wall = get_topography_top_index( jp,ip, 's' )
    403398
    404399          IF ( constant_flux_layer  .AND.  zv(n) - zw(k_wall) < z_p )  THEN
     
    427422!--             Get friction velocity and momentum flux from new surface data
    428423!--             types.
    429                 IF ( surf_def_h(0)%start_index(jlog,ilog) <=                   &
    430                      surf_def_h(0)%end_index(jlog,ilog) )  THEN
    431                    surf_start = surf_def_h(0)%start_index(jlog,ilog)
     424                IF ( surf_def_h(0)%start_index(jp,ip) <=                   &
     425                     surf_def_h(0)%end_index(jp,ip) )  THEN
     426                   surf_start = surf_def_h(0)%start_index(jp,ip)
    432427!--                Limit friction velocity. In narrow canyons or holes the
    433428!--                friction velocity can become very small, resulting in a too
     
    435430                   us_int    = MAX( surf_def_h(0)%us(surf_start), 0.01_wp ) 
    436431                   vsws_int  = surf_def_h(0)%vsws(surf_start)
    437                 ELSEIF ( surf_lsm_h%start_index(jlog,ilog) <=                  &
    438                          surf_lsm_h%end_index(jlog,ilog) )  THEN
    439                    surf_start = surf_lsm_h%start_index(jlog,ilog)
     432                ELSEIF ( surf_lsm_h%start_index(jp,ip) <=                  &
     433                         surf_lsm_h%end_index(jp,ip) )  THEN
     434                   surf_start = surf_lsm_h%start_index(jp,ip)
    440435                   us_int    = MAX( surf_lsm_h%us(surf_start), 0.01_wp ) 
    441436                   vsws_int  = surf_lsm_h%vsws(surf_start)
    442                 ELSEIF ( surf_usm_h%start_index(jlog,ilog) <=                  &
    443                          surf_usm_h%end_index(jlog,ilog) )  THEN
    444                    surf_start = surf_usm_h%start_index(jlog,ilog)
     437                ELSEIF ( surf_usm_h%start_index(jp,ip) <=                  &
     438                         surf_usm_h%end_index(jp,ip) )  THEN
     439                   surf_start = surf_usm_h%start_index(jp,ip)
    445440                   us_int    = MAX( surf_usm_h%us(surf_start), 0.01_wp ) 
    446441                   vsws_int  = surf_usm_h%vsws(surf_start)
  • palm/trunk/SOURCE/lpm_exchange_horiz.f90

    r2606 r2628  
    2525! -----------------
    2626! $Id$
     27! Enabled particle advection with grid stretching. Furthermore, the CFL-
     28! criterion is checked for every particle at every time step.
     29!
     30! 2606 2017-11-10 10:36:31Z schwenkel
    2731! Changed particle box locations: center of particle box now coincides
    2832! with scalar grid point of same index.
     
    124128 
    125129    USE, INTRINSIC ::  ISO_C_BINDING
    126 
     130   
     131    USE arrays_3d,                                                             &
     132       ONLY:  zw
     133   
    127134    USE control_parameters,                                                    &
    128135        ONLY:  dz, message_string, simulated_time
     
    887894       jp = particle_array(n)%y * ddy
    888895       kp = particle_array(n)%z / dz + 1 + offset_ocean_nzt
     896!
     897!--    In case of grid stretching a particle might be above or below the 
     898!--    previously calculated particle grid box (indices).     
     899       DO WHILE( zw(kp) < particle_array(n)%z )
     900          kp = kp + 1
     901       ENDDO
     902
     903       DO WHILE( zw(kp-1) > particle_array(n)%z )
     904          kp = kp - 1
     905       ENDDO
    889906
    890907       IF ( ip >= nxl  .AND.  ip <= nxr  .AND.  jp >= nys  .AND.  jp <= nyn    &
     
    10221039!------------------------------------------------------------------------------!
    10231040 SUBROUTINE lpm_move_particle
    1024 
     1041 
    10251042    IMPLICIT NONE
    10261043
     
    10381055
    10391056    CALL cpu_log( log_point_s(41), 'lpm_move_particle', 'start' )
    1040 
     1057    CALL lpm_check_cfl
    10411058    DO  ip = nxl, nxr
    10421059       DO  jp = nys, nyn
     
    10501067                i = particles_before_move(n)%x * ddx
    10511068                j = particles_before_move(n)%y * ddy
    1052                 k = particles_before_move(n)%z / dz + 1 + offset_ocean_nzt
    1053 
     1069                k = kp
     1070!
     1071!--             Find correct vertical particle grid box (necessary in case of grid stretching)
     1072!--             Due to the CFL limitations only the neighbouring grid boxes are considered.
     1073                IF( zw(k)   < particles_before_move(n)%z ) k = k + 1
     1074                IF( zw(k-1) > particles_before_move(n)%z ) k = k - 1
     1075               
    10541076!--             For lpm_exchange_horiz to work properly particles need to be moved to the outermost gridboxes
    10551077!--             of the respective processor. If the particle index is inside the processor the following lines
     
    10591081                j = MIN ( j , nyn )
    10601082                j = MAX ( j , nys )
     1083               
    10611084                k = MIN ( k , nzt )
    10621085                k = MAX ( k , nzb+1 )
     1086               
    10631087!
    10641088!--             Check, if particle has moved to another grid cell.
     
    10921116
    10931117 END SUBROUTINE lpm_move_particle
    1094 
     1118 
     1119!------------------------------------------------------------------------------!
     1120! Description:
     1121! ------------
     1122!> Check CFL-criterion for each particle. If one particle violated the
     1123!> criterion the particle will be deleted and a warning message is given.
     1124!------------------------------------------------------------------------------!
     1125 SUBROUTINE lpm_check_cfl 
     1126       
     1127    IMPLICIT NONE
     1128   
     1129    INTEGER(iwp)  ::  i
     1130    INTEGER(iwp)  ::  j
     1131    INTEGER(iwp)  ::  k
     1132    INTEGER(iwp)  ::  n
     1133   
     1134    DO  i = nxl, nxr
     1135       DO  j = nys, nyn
     1136          DO  k = nzb+1, nzt
     1137             number_of_particles = prt_count(k,j,i)
     1138             IF ( number_of_particles <= 0 )  CYCLE
     1139             particles => grid_particles(k,j,i)%particles(1:number_of_particles)         
     1140             DO n = 1, number_of_particles
     1141   
     1142                IF(ABS(particles(n)%speed_x) >                                 &
     1143                   (dx/(particles(n)%age-particles(n)%age_m))  .OR.            &
     1144                   ABS(particles(n)%speed_y) >                                 &
     1145                   (dx/(particles(n)%age-particles(n)%age_m))  .OR.            &
     1146                   ABS(particles(n)%speed_z) >                                 &
     1147                   ((zw(k)-zw(k-1))/(particles(n)%age-particles(n)%age_m))) THEN
     1148                   WRITE( message_string, * ) 'PARTICLE VIOLATED CFL CRITERION'&
     1149                   ': particle with id ',particles(n)%id,' will be deleted!'   
     1150                   CALL message( 'lpm_check_cfl', 'PA0500', 0, 1, 0, 6, 0 )
     1151                   particles(n)%particle_mask= .FALSE.
     1152                ENDIF
     1153             ENDDO
     1154          ENDDO
     1155       ENDDO
     1156    ENDDO   
     1157
     1158 END SUBROUTINE lpm_check_cfl
     1159 
    10951160!------------------------------------------------------------------------------!
    10961161! Description:
  • palm/trunk/SOURCE/lpm_init.f90

    r2608 r2628  
    2525! -----------------
    2626! $Id$
     27! Enabled particle advection with grid stretching.
     28!
     29! 2608 2017-11-13 14:04:26Z schwenkel
    2730! Calculation of magnus equation in external module (diagnostic_quantities_mod).
    2831!
     
    624627!------------------------------------------------------------------------------!
    625628 SUBROUTINE lpm_create_particle (phase)
    626 
     629   
     630    USE arrays_3d,                                                             &
     631       ONLY:  zw
    627632    USE lpm_exchange_horiz_mod,                                                &
    628633        ONLY: lpm_exchange_horiz, lpm_move_particle, realloc_particles_array
    629634
    630     USE lpm_pack_and_sort_mod,                                                   &
     635    USE lpm_pack_and_sort_mod,                                                 &
    631636        ONLY: lpm_sort_in_subboxes
    632637
     
    742747                               ip = tmp_particle%x * ddx
    743748                               jp = tmp_particle%y * ddy
    744                                kp = tmp_particle%z / dz + 1 + offset_ocean_nzt
     749                               kp = tmp_particle%z / dz + 1 + offset_ocean_nzt                               
     750                               DO WHILE( zw(kp) < tmp_particle%z )
     751                                  kp = kp + 1
     752                               ENDDO
     753                               DO WHILE( zw(kp-1) > tmp_particle%z )
     754                                  kp = kp - 1
     755                               ENDDO
    745756!
    746757!--                            Determine surface level. Therefore, check for
     
    929940                   i = particles(n)%x * ddx
    930941                   j = particles(n)%y * ddy
    931                    k =   particles(n)%z / dz + 1 + offset_ocean_nzt
     942                   k = particles(n)%z / dz + 1 + offset_ocean_nzt
     943                   DO WHILE( zw(k) < particles(n)%z )
     944                      k = k + 1
     945                   ENDDO
     946                   DO WHILE( zw(k-1) > particles(n)%z )
     947                      k = k - 1
     948                   ENDDO
    932949!
    933950!--                Check if particle is within topography
  • palm/trunk/SOURCE/lpm_pack_arrays.f90

    r2609 r2628  
    2525! -----------------
    2626! $Id$
     27! Enabled particle advection with grid stretching.
     28!
     29! 2609 2017-11-14 14:14:44Z schwenkel
    2730! Integrated subroutine pack_and_sort into lpm_sort_in_subboxes
    2831!
     
    112115
    113116       USE cpulog,                                                              &
    114            ONLY:  cpu_log, log_point_s
     117          ONLY:  cpu_log, log_point_s
    115118
    116119       USE indices,                                                             &
    117            ONLY:  nxl, nxr, nys, nyn, nzb, nzt
     120          ONLY:  nxl, nxr, nys, nyn, nzb, nzt
    118121
    119122       USE kinds
    120123
    121124       USE control_parameters,                                                  &
    122            ONLY: dz
     125          ONLY: dz
    123126       
    124127       USE grid_variables,                                                      &
    125            ONLY: dx,dy,ddx, ddy
    126          
     128          ONLY: dx,dy,ddx, ddy
     129           
     130       USE arrays_3d,                                                           &
     131          ONLY:  zu
    127132       IMPLICIT NONE
    128133
     
    167172                      i = (particles(n)%x + 0.5_wp * dx) * ddx
    168173                      j = (particles(n)%y + 0.5_wp * dy) * ddy
    169                       k = ( particles(n)%z+ 0.5_wp *dz ) / dz+1 + offset_ocean_nzt
    170174                     
    171175                      IF ( i == ip )  sort_index = sort_index + 4
    172                       IF ( j == jp )  sort_index = sort_index + 2
    173                       IF ( k == kp ) sort_index = sort_index + 1
     176                      IF ( j == jp )  sort_index = sort_index + 2                     
     177                      IF ( zu(kp) > particles(n)%z ) sort_index = sort_index + 1
    174178                     
    175179                      sort_count(sort_index) = sort_count(sort_index) + 1
     
    343347
    344348
    345  END module lpm_pack_and_sort_mod
     349 END MODULE lpm_pack_and_sort_mod
Note: See TracChangeset for help on using the changeset viewer.