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/production_e.f90

    r941 r1007  
    44! Current revisions:
    55! -----------------
    6 !
     6! Bugfix: calculation of buoyancy production has to consider the liquid water
     7! mixing ratio in case of cloud droplets
    78!
    89! Former revisions:
     
    164165
    165166                tend(k,j,i) = tend(k,j,i) + km(k,j,i) * def
    166                
     167
    167168             ENDDO
    168169          ENDDO
     
    189190
    190191                   IF ( wall_e_y(j,i) /= 0.0 )  THEN
    191 !                     
     192!
    192193!--                   Inconsistency removed: as the thermal stratification is
    193194!--                   not taken into account for the evaluation of the wall
     
    219220
    220221                   IF ( wall_e_x(j,i) /= 0.0 )  THEN
    221 !                     
     222!
    222223!--                   Inconsistency removed: as the thermal stratification is
    223224!--                   not taken into account for the evaluation of the wall
     
    275276
    276277                      IF ( wall_e_y(j,i) /= 0.0 )  THEN
    277 !                     
     278!
    278279!--                      Inconsistency removed: as the thermal stratification
    279280!--                      is not taken into account for the evaluation of the
     
    301302
    302303                      IF ( wall_e_x(j,i) /= 0.0 )  THEN
    303 !                     
     304!
    304305!--                      Inconsistency removed: as the thermal stratification
    305306!--                      is not taken into account for the evaluation of the
     
    416417
    417418                   tend(k,j,i) = tend(k,j,i) + km(k,j,i) * def
    418                
     419
    419420                ENDIF
    420421
     
    551552                   DO  k = nzb_diff_s_inner(j,i), nzt_diff
    552553
    553                       IF ( .NOT. cloud_physics ) THEN
     554                      IF ( .NOT. cloud_physics .AND. .NOT. cloud_droplets ) THEN
    554555                         k1 = 1.0 + 0.61 * q(k,j,i)
    555556                         k2 = 0.61 * pt(k,j,i)
    556                       ELSE
     557                         tend(k,j,i) = tend(k,j,i) - kh(k,j,i) *               &
     558                                         g / vpt(k,j,i) *                      &
     559                                         ( k1 * ( pt(k+1,j,i)-pt(k-1,j,i) ) +  &
     560                                           k2 * ( q(k+1,j,i) - q(k-1,j,i) )    &
     561                                         ) * dd2zu(k)
     562                      ELSE IF ( cloud_physics )  THEN
    557563                         IF ( ql(k,j,i) == 0.0 )  THEN
    558564                            k1 = 1.0 + 0.61 * q(k,j,i)
     
    568574                            k2 = theta * ( l_d_cp / temp * k1 - 1.0 )
    569575                         ENDIF
    570                       ENDIF
    571 
    572                       tend(k,j,i) = tend(k,j,i) - kh(k,j,i) * g / vpt(k,j,i) * &
     576                         tend(k,j,i) = tend(k,j,i) - kh(k,j,i) *               &
     577                                         g / vpt(k,j,i) *                      &
    573578                                         ( k1 * ( pt(k+1,j,i)-pt(k-1,j,i) ) +  &
    574579                                           k2 * ( q(k+1,j,i) - q(k-1,j,i) )    &
    575580                                         ) * dd2zu(k)
     581                      ELSE IF ( cloud_droplets )  THEN
     582                         k1 = 1.0 + 0.61 * q(k,j,i) - ql(k,j,i)
     583                         k2 = 0.61 * pt(k,j,i)
     584                         tend(k,j,i) = tend(k,j,i) -                          &
     585                                       kh(k,j,i) * g / vpt(k,j,i) *           &
     586                                       ( k1 * ( pt(k+1,j,i)- pt(k-1,j,i) ) +  &
     587                                         k2 * ( q(k+1,j,i) -  q(k-1,j,i) ) -  &
     588                                         pt(k,j,i) * ( ql(k+1,j,i) -          &
     589                                         ql(k-1,j,i) ) ) * dd2zu(k)
     590                      ENDIF
     591
    576592                   ENDDO
    577593
     
    584600                      k = nzb_diff_s_inner(j,i)-1
    585601
    586                       IF ( .NOT. cloud_physics ) THEN
     602                      IF ( .NOT. cloud_physics .AND. .NOT. cloud_droplets ) THEN
    587603                         k1 = 1.0 + 0.61 * q(k,j,i)
    588604                         k2 = 0.61 * pt(k,j,i)
    589                       ELSE
     605                      ELSE IF ( cloud_physics )  THEN
    590606                         IF ( ql(k,j,i) == 0.0 )  THEN
    591607                            k1 = 1.0 + 0.61 * q(k,j,i)
     
    601617                            k2 = theta * ( l_d_cp / temp * k1 - 1.0 )
    602618                         ENDIF
     619                      ELSE IF ( cloud_droplets )  THEN
     620                         k1 = 1.0 + 0.61 * q(k,j,i) - ql(k,j,i)
     621                         k2 = 0.61 * pt(k,j,i)
    603622                      ENDIF
    604623
     
    615634                      k = nzt
    616635
    617                       IF ( .NOT. cloud_physics ) THEN
     636                      IF ( .NOT. cloud_physics .AND. .NOT. cloud_droplets ) THEN
    618637                         k1 = 1.0 + 0.61 * q(k,j,i)
    619638                         k2 = 0.61 * pt(k,j,i)
    620                       ELSE
     639                      ELSE IF ( cloud_physics )  THEN
    621640                         IF ( ql(k,j,i) == 0.0 )  THEN
    622641                            k1 = 1.0 + 0.61 * q(k,j,i)
     
    632651                            k2 = theta * ( l_d_cp / temp * k1 - 1.0 )
    633652                         ENDIF
     653                      ELSE IF ( cloud_droplets )  THEN
     654                         k1 = 1.0 + 0.61 * q(k,j,i) - ql(k,j,i)
     655                         k2 = 0.61 * pt(k,j,i)
    634656                      ENDIF
    635657
     
    699721
    700722          tend(k,j,i) = tend(k,j,i) + km(k,j,i) * def
    701                
     723
    702724       ENDDO
    703725
     
    721743
    722744             IF ( wall_e_y(j,i) /= 0.0 )  THEN
    723 !                     
     745!
    724746!--             Inconsistency removed: as the thermal stratification
    725747!--             is not taken into account for the evaluation of the
     
    751773
    752774             IF ( wall_e_x(j,i) /= 0.0 )  THEN
    753 !                     
     775!
    754776!--             Inconsistency removed: as the thermal stratification
    755777!--             is not taken into account for the evaluation of the
     
    805827
    806828                IF ( wall_e_y(j,i) /= 0.0 )  THEN
    807 !                     
     829!
    808830!--                Inconsistency removed: as the thermal stratification
    809831!--                is not taken into account for the evaluation of the
     
    831853
    832854                IF ( wall_e_x(j,i) /= 0.0 )  THEN
    833 !                     
     855!
    834856!--                Inconsistency removed: as the thermal stratification
    835857!--                is not taken into account for the evaluation of the
     
    10411063             DO  k = nzb_diff_s_inner(j,i), nzt_diff
    10421064
    1043                 IF ( .NOT. cloud_physics )  THEN
     1065                IF ( .NOT. cloud_physics .AND. .NOT. cloud_droplets )  THEN
    10441066                   k1 = 1.0 + 0.61 * q(k,j,i)
    10451067                   k2 = 0.61 * pt(k,j,i)
    1046                 ELSE
     1068                   tend(k,j,i) = tend(k,j,i) - kh(k,j,i) * g / vpt(k,j,i) *   &
     1069                                         ( k1 * ( pt(k+1,j,i)-pt(k-1,j,i) ) + &
     1070                                           k2 * ( q(k+1,j,i) - q(k-1,j,i) )   &
     1071                                         ) * dd2zu(k)
     1072                ELSE IF ( cloud_physics )  THEN
    10471073                   IF ( ql(k,j,i) == 0.0 )  THEN
    10481074                      k1 = 1.0 + 0.61 * q(k,j,i)
     
    10581084                      k2 = theta * ( l_d_cp / temp * k1 - 1.0 )
    10591085                   ENDIF
    1060                 ENDIF
    1061 
    1062                 tend(k,j,i) = tend(k,j,i) - kh(k,j,i) * g / vpt(k,j,i) *      &
     1086                   tend(k,j,i) = tend(k,j,i) - kh(k,j,i) * g / vpt(k,j,i) *   &
    10631087                                         ( k1 * ( pt(k+1,j,i)-pt(k-1,j,i) ) + &
    10641088                                           k2 * ( q(k+1,j,i) - q(k-1,j,i) )   &
    10651089                                         ) * dd2zu(k)
     1090                ELSE IF ( cloud_droplets )  THEN
     1091                   k1 = 1.0 + 0.61 * q(k,j,i) - ql(k,j,i)
     1092                   k2 = 0.61 * pt(k,j,i)
     1093                   tend(k,j,i) = tend(k,j,i) - kh(k,j,i) * g / vpt(k,j,i) *  &
     1094                                     ( k1 * ( pt(k+1,j,i)-pt(k-1,j,i) ) +    &
     1095                                       k2 * ( q(k+1,j,i) - q(k-1,j,i) ) -    &
     1096                                       pt(k,j,i) * ( ql(k+1,j,i) -           &
     1097                                                     ql(k-1,j,i) ) ) * dd2zu(k)
     1098                ENDIF
    10661099             ENDDO
    10671100
     
    10691102                k = nzb_diff_s_inner(j,i)-1
    10701103
    1071                 IF ( .NOT. cloud_physics ) THEN
     1104                IF ( .NOT. cloud_physics .AND. .NOT. cloud_droplets ) THEN
    10721105                   k1 = 1.0 + 0.61 * q(k,j,i)
    10731106                   k2 = 0.61 * pt(k,j,i)
    1074                 ELSE
     1107                ELSE IF ( cloud_physics )  THEN
    10751108                   IF ( ql(k,j,i) == 0.0 )  THEN
    10761109                      k1 = 1.0 + 0.61 * q(k,j,i)
     
    10861119                      k2 = theta * ( l_d_cp / temp * k1 - 1.0 )
    10871120                   ENDIF
     1121                ELSE IF ( cloud_droplets )  THEN
     1122                   k1 = 1.0 + 0.61 * q(k,j,i) - ql(k,j,i)
     1123                   k2 = 0.61 * pt(k,j,i)
    10881124                ENDIF
    10891125
     
    10951131                k = nzt
    10961132
    1097                 IF ( .NOT. cloud_physics ) THEN
     1133                IF ( .NOT. cloud_physics .AND. .NOT. cloud_droplets ) THEN
    10981134                   k1 = 1.0 + 0.61 * q(k,j,i)
    10991135                   k2 = 0.61 * pt(k,j,i)
    1100                 ELSE
     1136                ELSE IF ( cloud_physics )  THEN
    11011137                   IF ( ql(k,j,i) == 0.0 )  THEN
    11021138                      k1 = 1.0 + 0.61 * q(k,j,i)
     
    11121148                      k2 = theta * ( l_d_cp / temp * k1 - 1.0 )
    11131149                   ENDIF
     1150                ELSE IF ( cloud_droplets )  THEN
     1151                   k1 = 1.0 + 0.61 * q(k,j,i) - ql(k,j,i)
     1152                   k2 = 0.61 * pt(k,j,i)
    11141153                ENDIF
    11151154
Note: See TracChangeset for help on using the changeset viewer.