Ignore:
Timestamp:
Apr 11, 2014 5:15:14 PM (10 years ago)
Author:
hoffmann
Message:

new Lagrangian particle structure integrated

File:
1 edited

Legend:

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

    r1354 r1359  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! New particle structure integrated.
    2323!
    2424! Former revisions:
     
    128128
    129129    USE particle_attributes,                                                   &
    130         ONLY:  particle_advection_start, particles, prt_count,                 &
    131                prt_start_index
     130        ONLY:  grid_particles, number_of_particles, particle_advection_start,  &
     131               particles, prt_count
    132132   
    133133    USE pegrid
     
    163163    LOGICAL ::  two_d          !:
    164164   
    165     REAL(wp) ::  mean_r         !:
    166     REAL(wp) ::  s_r3           !:
    167     REAL(wp) ::  s_r4           !:
     165    REAL(wp) ::  mean_r        !:
     166    REAL(wp) ::  s_r2          !:
     167    REAL(wp) ::  s_r3          !:
    168168   
    169     REAL(wp), DIMENSION(:), ALLOCATABLE ::      level_z     !:
    170     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::    local_2d    !:
    171     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::    local_2d_l  !:
    172     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf    !:
     169    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  level_z             !:
     170    REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  local_2d            !:
     171    REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  local_2d_l          !:
     172    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf            !:
    173173    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_2d_sections   !:
    174174    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_2d_sections_l !:
     175
    175176#if defined( __parallel )
    176     REAL(wp), DIMENSION(:,:),   ALLOCATABLE ::  total_2d  !:
     177    REAL(wp), DIMENSION(:,:),   ALLOCATABLE ::  total_2d    !:
    177178#endif
    178179    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !:
     
    418419                ENDIF
    419420
    420              CASE ( 'pr_xy', 'pr_xz', 'pr_yz' )  ! mean particle radius
     421             CASE ( 'pr_xy', 'pr_xz', 'pr_yz' )  ! mean particle radius (effective radius)
    421422                IF ( av == 0 )  THEN
    422423                   IF ( simulated_time >= particle_advection_start )  THEN
     
    424425                         DO  j = nys, nyn
    425426                            DO  k = nzb, nzt+1
    426                                psi = prt_start_index(k,j,i)
     427                               number_of_particles = prt_count(k,j,i)
     428                               IF (number_of_particles <= 0)  CYCLE
     429                               particles => grid_particles(k,j,i)%particles(1:number_of_particles)
     430                               s_r2 = 0.0_wp
    427431                               s_r3 = 0.0_wp
    428                                s_r4 = 0.0_wp
    429                                DO  n = psi, psi+prt_count(k,j,i)-1
    430                                   s_r3 = s_r3 + particles(n)%radius**3 *       &
    431                                                 particles(n)%weight_factor
    432                                   s_r4 = s_r4 + particles(n)%radius**4 *       &
    433                                                 particles(n)%weight_factor
     432                               DO  n = 1, number_of_particles
     433                                  IF ( particles(n)%particle_mask )  THEN
     434                                     s_r2 = s_r2 + particles(n)%radius**2 * &
     435                                            particles(n)%weight_factor
     436                                     s_r3 = s_r3 + particles(n)%radius**3 * &
     437                                            particles(n)%weight_factor
     438                                  ENDIF
    434439                               ENDDO
    435                                IF ( s_r3 /= 0.0_wp )  THEN
    436                                   mean_r = s_r4 / s_r3
     440                               IF ( s_r2 > 0.0_wp )  THEN
     441                                  mean_r = s_r3 / s_r2
    437442                               ELSE
    438443                                  mean_r = 0.0_wp
     
    445450                   ELSE
    446451                      tend = 0.0_wp
    447                    END IF
     452                   ENDIF
    448453                   DO  i = nxlg, nxrg
    449454                      DO  j = nysg, nyng
     
    600605                         DO  j = nys, nyn
    601606                            DO  k = nzb, nzt+1
    602                                psi = prt_start_index(k,j,i)
    603                                DO  n = psi, psi+prt_count(k,j,i)-1
    604                                   tend(k,j,i) =  tend(k,j,i) +                 &
    605                                                  particles(n)%weight_factor /  &
    606                                                  prt_count(k,j,i)
     607                               number_of_particles = prt_count(k,j,i)
     608                               IF (number_of_particles <= 0)  CYCLE
     609                               particles => grid_particles(k,j,i)%particles(1:number_of_particles)
     610                               DO  n = 1, number_of_particles
     611                                  IF ( particles(n)%particle_mask )  THEN
     612                                     tend(k,j,i) =  tend(k,j,i) +                 &
     613                                                    particles(n)%weight_factor /  &
     614                                                    prt_count(k,j,i)
     615                                  ENDIF
    607616                               ENDDO
    608617                            ENDDO
     
    612621                   ELSE
    613622                      tend = 0.0_wp
    614                    END IF
     623                   ENDIF
    615624                   DO  i = nxlg, nxrg
    616625                      DO  j = nysg, nyng
Note: See TracChangeset for help on using the changeset viewer.