Changeset 2609


Ignore:
Timestamp:
Nov 14, 2017 2:14:44 PM (6 years ago)
Author:
schwenkel
Message:

Integrated subroutine pack_and_sort into lpm_sort_in_subboxes

File:
1 edited

Legend:

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

    r2606 r2609  
    2525! -----------------
    2626! $Id$
     27! Integrated subroutine pack_and_sort into lpm_sort_in_subboxes
     28!
     29! 2606 2017-11-10 10:36:31Z schwenkel
    2730! Changed particle box locations: center of particle box now coincides
    2831! with scalar grid point of same index.
     
    124127       IMPLICIT NONE
    125128
     129       INTEGER(iwp) ::  i  !<
    126130       INTEGER(iwp) ::  ip !<
     131       INTEGER(iwp) ::  is !<
     132       INTEGER(iwp) ::  j  !<
    127133       INTEGER(iwp) ::  jp !<
     134       INTEGER(iwp) ::  k  !<
    128135       INTEGER(iwp) ::  kp !<
     136       INTEGER(iwp) ::  m  !<
     137       INTEGER(iwp) ::  n  !<
     138       INTEGER(iwp) ::  nn !<
     139       INTEGER(iwp) ::  sort_index  !<
     140
     141       INTEGER(iwp), DIMENSION(0:7) ::  sort_count  !<
     142
     143       TYPE(particle_type), DIMENSION(:,:), ALLOCATABLE ::  sort_particles  !<
    129144
    130145       CALL cpu_log( log_point_s(51), 'lpm_sort_in_subboxes', 'start' )
     
    135150                IF ( number_of_particles <= 0 )  CYCLE
    136151                particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
     152                     
     153                nn = 0
     154                sort_count = 0
     155                ALLOCATE( sort_particles(number_of_particles, 0:7) )
    137156               
    138                 CALL lpm_pack_and_sort(ip,jp,kp)
    139                
     157                DO  n = 1, number_of_particles
     158                   sort_index = 0
     159
     160                   IF ( particles(n)%particle_mask )  THEN
     161                      nn = nn + 1
     162!
     163!--                   Sorting particles with a binary scheme
     164!--                   sort_index=111_2=7_10 -> particle at the left,south,bottom subgridbox
     165!--                   sort_index=000_2=0_10 -> particle at the right,north,top subgridbox
     166!--                   For this the center of the gridbox is calculated
     167                      i = (particles(n)%x + 0.5_wp * dx) * ddx
     168                      j = (particles(n)%y + 0.5_wp * dy) * ddy
     169                      k = ( particles(n)%z+ 0.5_wp *dz ) / dz+1 + offset_ocean_nzt
     170                     
     171                      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
     174                     
     175                      sort_count(sort_index) = sort_count(sort_index) + 1
     176                      m = sort_count(sort_index)
     177                      sort_particles(m,sort_index) = particles(n)
     178                      sort_particles(m,sort_index)%block_nr = sort_index
     179                   ENDIF
     180                ENDDO
     181
     182                nn = 0
     183                DO is = 0,7
     184                   grid_particles(kp,jp,ip)%start_index(is) = nn + 1
     185                   DO n = 1,sort_count(is)
     186                      nn = nn + 1
     187                      particles(nn) = sort_particles(n,is)
     188                   ENDDO
     189                   grid_particles(kp,jp,ip)%end_index(is) = nn
     190                ENDDO
     191
     192                number_of_particles = nn   
    140193                prt_count(kp,jp,ip) = number_of_particles
     194                DEALLOCATE(sort_particles)
    141195             ENDDO
    142196          ENDDO
     
    190244
    191245    END SUBROUTINE lpm_pack
    192 
    193     SUBROUTINE lpm_pack_and_sort (ip,jp,kp)
    194 
    195        USE control_parameters,                                                 &
    196            ONLY: dz
    197 
    198        USE kinds
    199 
    200        USE grid_variables,                                                     &
    201            ONLY: dx,dy,ddx, ddy
    202 
    203        IMPLICIT NONE
    204 
    205        INTEGER(iwp), INTENT(IN) :: ip
    206        INTEGER(iwp), INTENT(IN) :: jp
    207        INTEGER(iwp), INTENT(IN) :: kp
    208 
    209        INTEGER(iwp)             :: i
    210        INTEGER(iwp)             :: is
    211        INTEGER(iwp)             :: j
    212        INTEGER(iwp)             :: k
    213        INTEGER(iwp)             :: n
    214        INTEGER(iwp)             :: nn
    215        INTEGER(iwp)             :: m
    216        INTEGER(iwp)             :: sort_index
    217 
    218        INTEGER(iwp), DIMENSION(0:7) :: sort_count
    219 
    220        TYPE(particle_type), DIMENSION(number_of_particles,0:7) :: sort_particles
    221      
    222        nn = 0
    223        sort_count = 0
    224                
    225        DO  n = 1, number_of_particles
    226           sort_index = 0
    227 
    228           IF ( particles(n)%particle_mask )  THEN
    229              nn = nn + 1
    230 !
    231 !--          Sorting particles with a binary scheme
    232 !--          sort_index=111_2=7_10 -> particle at the left,south,bottom subgridbox
    233 !--          sort_index=000_2=0_10 -> particle at the right,north,top subgridbox
    234 !--          For this the center of the gridbox is calculated
    235              i = (particles(n)%x + 0.5_wp * dx) * ddx
    236              j = (particles(n)%y + 0.5_wp * dy) * ddy
    237              k = ( particles(n)%z+ 0.5_wp *dz ) / dz+1 + offset_ocean_nzt
    238                      
    239              IF ( i == ip )  sort_index = sort_index + 4
    240              IF ( j == jp )  sort_index = sort_index + 2
    241              IF ( k == kp )  sort_index = sort_index + 1
    242                      
    243              sort_count(sort_index) = sort_count(sort_index) + 1
    244              m = sort_count(sort_index)
    245              sort_particles(m,sort_index) = particles(n)
    246              sort_particles(m,sort_index)%block_nr = sort_index
    247           ENDIF
    248 
    249        ENDDO
    250 
    251        nn = 0
    252 
    253        DO is = 0,7
    254           grid_particles(kp,jp,ip)%start_index(is) = nn + 1
    255           DO n = 1,sort_count(is)
    256              nn = nn + 1
    257              particles(nn) = sort_particles(n,is)
    258              ENDDO
    259              grid_particles(kp,jp,ip)%end_index(is) = nn
    260        ENDDO
    261 
    262        number_of_particles = nn   
    263                
    264     END SUBROUTINE lpm_pack_and_sort
    265246               
    266247!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.