Ignore:
Timestamp:
Sep 19, 2012 2:30:36 PM (12 years ago)
Author:
franke
Message:

Bugfixes


Missing calculation of mean particle weighting factor for output added. (data_output_2d, data_output_3d, data_output_mask, sum_up_3d_data)
Calculation of mean particle radius for output now considers the weighting factor. (data_output_mask)
Calculation of sugrid-scale buoyancy flux for humidity and cloud droplets corrected. (flow_statistics)
Factor in calculation of enhancement factor for collision efficencies corrected. (lpm_collision_kernels)
Calculation of buoyancy production now considers the liquid water mixing ratio in case of cloud droplets. (production_e)

Changes


Calculation of buoyancy flux for humidity in case of WS-scheme is now using turbulent fluxes of WS-scheme. (flow_statistics)
Calculation of the collision kernels now in SI units. (lpm_collision_kernels)

File:
1 edited

Legend:

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

    r979 r1007  
    44! Current revisions:
    55! -----------------
    6 !
     6! Bugfix: missing calculation of ql_vp added
    77!
    88! Former revisions:
     
    428428             CASE ( 'ql_vp_xy', 'ql_vp_xz', 'ql_vp_yz' )
    429429                IF ( av == 0 )  THEN
     430                   IF ( simulated_time >= particle_advection_start )  THEN
     431                      DO  i = nxl, nxr
     432                         DO  j = nys, nyn
     433                            DO  k = nzb, nzt+1
     434                               psi = prt_start_index(k,j,i)
     435                               DO  n = psi, psi+prt_count(k,j,i)-1
     436                                  tend(k,j,i) =  tend(k,j,i) + &
     437                                                 particles(n)%weight_factor / &
     438                                                 prt_count(k,j,i)
     439                               ENDDO
     440                            ENDDO
     441                         ENDDO
     442                      ENDDO
     443                      CALL exchange_horiz( tend, nbgp )
     444                   ELSE
     445                      tend = 0.0
     446                   END IF
     447                   DO  i = nxlg, nxrg
     448                      DO  j = nysg, nyng
     449                         DO  k = nzb, nzt+1
     450                            local_pf(i,j,k) = tend(k,j,i)
     451                         ENDDO
     452                      ENDDO
     453                   ENDDO
     454                   resorted = .TRUE.
     455                ELSE
     456                   CALL exchange_horiz( ql_vp_av, nbgp )
    430457                   to_be_resorted => ql_vp
    431                 ELSE
    432                    to_be_resorted => ql_vp_av
    433458                ENDIF
    434459                IF ( mode == 'xy' )  level_z = zu
Note: See TracChangeset for help on using the changeset viewer.