Ignore:
Timestamp:
Jan 18, 2017 12:22:54 PM (8 years ago)
Author:
hoffmann
Message:

introduction of a particle ID, improvement of equilibrium radius calculation, and reformatting

File:
1 edited

Legend:

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

    r2101 r2122  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! DVRP routine removed
    2323!
    2424! Former revisions:
     
    397397    ENDIF
    398398
    399 !
    400 !-- Set particle size for dvrp graphics
    401     IF ( particle_dvrpsize == 'absw' )  THEN
    402 
    403        DO  ip = nxl, nxr
    404           DO  jp = nys, nyn
    405              DO  kp = nzb+1, nzt
    406 
    407                 number_of_particles = prt_count(kp,jp,ip)
    408                 particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
    409                 IF ( number_of_particles <= 0 )  CYCLE
    410                 start_index = grid_particles(kp,jp,ip)%start_index
    411                 end_index   = grid_particles(kp,jp,ip)%end_index
    412 
    413                 ALLOCATE( xv(1:number_of_particles), &
    414                           yv(1:number_of_particles) )
    415 
    416                 xv = particles(1:number_of_particles)%x
    417                 yv = particles(1:number_of_particles)%y
    418                 zv = particles(1:number_of_particles)%z
    419 
    420                 DO  nb = 0,7
    421 
    422                    i = ip + block_offset(nb)%i_off
    423                    j = jp + block_offset(nb)%j_off
    424                    k = kp-1
    425 
    426                    DO  n = start_index(nb), end_index(nb)
    427 !
    428 !--                   Interpolate w-component to the current particle position
    429                       x  = xv(n) - i * dx
    430                       y  = yv(n) - j * dy
    431                       aa = x**2          + y**2
    432                       bb = ( dx - x )**2 + y**2
    433                       cc = x**2          + ( dy - y )**2
    434                       dd = ( dx - x )**2 + ( dy - y )**2
    435                       gg = aa + bb + cc + dd
    436 
    437                       w_int_l = ( ( gg - aa ) * w(k,j,i)   + ( gg - bb ) *     &
    438                                   w(k,j,i+1) + ( gg - cc ) * w(k,j+1,i) +      &
    439                                   ( gg - dd ) * w(k,j+1,i+1)                   &
    440                                 ) / ( 3.0_wp * gg )
    441 
    442                       IF ( k+1 == nzt+1 )  THEN
    443                          w_int = w_int_l
    444                       ELSE
    445                          w_int_u = ( ( gg - aa ) * w(k+1,j,i)   + ( gg - bb ) *  &
    446                                      w(k+1,j,i+1) + ( gg - cc ) * w(k+1,j+1,i) + &
    447                                      ( gg - dd ) * w(k+1,j+1,i+1)                &
    448                                    ) / ( 3.0_wp * gg )
    449                          w_int = w_int_l + ( zv(n) - zw(k) ) / dz *     &
    450                                            ( w_int_u - w_int_l )
    451                       ENDIF
    452 
    453 !
    454 !--                   Limit values by the given interval and normalize to
    455 !--                   interval [0,1]
    456                       w_int = ABS( w_int )
    457                       w_int = MIN( w_int, dvrpsize_interval(2) )
    458                       w_int = MAX( w_int, dvrpsize_interval(1) )
    459 
    460                       w_int = ( w_int - dvrpsize_interval(1) ) / &
    461                               ( dvrpsize_interval(2) - dvrpsize_interval(1) )
    462 
    463                       particles(n)%dvrp_psize = ( 0.25_wp + w_int * 0.6_wp ) * &
    464                                                 dx
    465 
    466                    ENDDO
    467                 ENDDO
    468 
    469                 DEALLOCATE( xv, yv, zv )
    470 
    471              ENDDO
    472           ENDDO
    473        ENDDO
    474 
    475     ENDIF
    476 
    477399    CALL cpu_log( log_point_s(49), 'lpm_set_attributes', 'stop' )
    478400
Note: See TracChangeset for help on using the changeset viewer.