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_3d.f90

    r791 r1007  
    44! Current revisions:
    55! -----------------
    6 !
     6! Bugfix: missing calculation of ql_vp added
    77!
    88! Former revisions:
     
    295295          CASE ( 'ql_vp' )
    296296             IF ( av == 0 )  THEN
    297                 to_be_resorted => ql_vp
    298              ELSE
     297                DO  i = nxl, nxr
     298                   DO  j = nys, nyn
     299                      DO  k = nzb, nz_do3d
     300                         psi = prt_start_index(k,j,i)
     301                         DO  n = psi, psi+prt_count(k,j,i)-1
     302                            tend(k,j,i) = tend(k,j,i) + &
     303                                          particles(n)%weight_factor / &
     304                                          prt_count(k,j,i)
     305                         ENDDO
     306                      ENDDO
     307                   ENDDO
     308                ENDDO
     309                CALL exchange_horiz( tend, nbgp )
     310                DO  i = nxlg, nxrg
     311                   DO  j = nysg, nyng
     312                      DO  k = nzb, nz_do3d
     313                         local_pf(i,j,k) = tend(k,j,i)
     314                      ENDDO
     315                   ENDDO
     316                ENDDO
     317                resorted = .TRUE.
     318             ELSE
     319                CALL exchange_horiz( ql_vp_av, nbgp )
    299320                to_be_resorted => ql_vp_av
    300321             ENDIF
Note: See TracChangeset for help on using the changeset viewer.