Ignore:
Timestamp:
Nov 13, 2017 2:04:26 PM (6 years ago)
Author:
schwenkel
Message:

Inital revision of diagnostic_quantities_mod allows unified calculation of magnus equation and saturion mixing ratio

File:
1 edited

Legend:

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

    r2522 r2608  
    2525! -----------------
    2626! $Id$
     27! Calculation of supersaturation in external module (diagnostic_quantities_mod).
     28! Change: correct calculation of saturation specific humidity to saturation
     29! mixing ratio (the factor of 0.378 vanishes).
     30!
     31! 2522 2017-10-05 14:20:37Z schwenkel
    2732! Minor bugfix
    2833!
     
    548553           ONLY:  cpu_log, log_point_s
    549554
     555       USE diagnostic_quantities_mod,                                          &
     556           ONLY: e_s, magnus, q_s, sat, supersaturation, t_l
     557
    550558       USE indices,                                                            &
    551559           ONLY:  nxlg, nxrg, nysg, nyng, nzb, nzt
     
    564572       REAL(wp)     ::  activ             !<
    565573       REAL(wp)     ::  afactor           !<
    566        REAL(wp)     ::  alpha             !<
    567574       REAL(wp)     ::  beta_act          !<
    568575       REAL(wp)     ::  bfactor           !<
    569        REAL(wp)     ::  e_s               !<
    570576       REAL(wp)     ::  k_act             !<
    571577       REAL(wp)     ::  n_act             !<
    572578       REAL(wp)     ::  n_ccn             !<
    573        REAL(wp)     ::  q_s               !<
    574579       REAL(wp)     ::  s_0               !<
    575        REAL(wp)     ::  sat               !<
    576580       REAL(wp)     ::  sat_max           !<
    577581       REAL(wp)     ::  sigma             !<
    578582       REAL(wp)     ::  sigma_act         !<
    579        REAL(wp)     ::  t_int             !<
    580        REAL(wp)     ::  t_l               !<
    581583
    582584       CALL cpu_log( log_point_s(65), 'activation', 'start' )
     
    587589
    588590!
    589 !--             Actual liquid water temperature:
    590                 t_l = t_d_pt(k) * pt(k,j,i)
    591 
    592 !
    593 !--             Calculate actual temperature
    594                 t_int = pt(k,j,i) * ( hyp(k) / 100000.0_wp )**0.286_wp
    595 !
    596 !--             Saturation vapor pressure at t_l:
    597                 e_s = 610.78_wp * EXP( 17.269_wp * ( t_l - 273.16_wp ) /    &
    598                                        ( t_l - 35.86_wp )                   &
    599                                      )
    600 !
    601 !--             Computation of saturation humidity:
    602                 q_s   = 0.622_wp * e_s / ( hyp(k) - 0.378_wp * e_s )
    603                 alpha = 0.622_wp * l_d_r * l_d_cp / ( t_l * t_l )
    604                 q_s   = q_s * ( 1.0_wp + alpha * q(k,j,i) ) /               &
    605                         ( 1.0_wp + alpha * q_s )
    606 
    607 !--             Supersaturation:
    608                 sat   = ( q(k,j,i) - qr(k,j,i) - qc(k,j,i) ) / q_s - 1.0_wp
    609 
     591!--             Call calculation of supersaturation located
     592!--             in diagnostic_quantities_mod
     593                CALL supersaturation ( i, j, k )
    610594!
    611595!--             Prescribe parameters for activation
     
    636620!--                Curvature effect (afactor) with surface tension
    637621!--                parameterization by Straka (2009)
    638                    sigma = 0.0761_wp - 0.000155_wp * ( t_int - 273.15_wp )
    639                    afactor = 2.0_wp * sigma / ( rho_l * r_v * t_int )
     622                   sigma = 0.0761_wp - 0.000155_wp * ( t_l - 273.15_wp )
     623                   afactor = 2.0_wp * sigma / ( rho_l * r_v * t_l )
    640624!
    641625!--                Solute effect (bfactor)
     
    695679           ONLY:  cpu_log, log_point_s
    696680
     681       USE diagnostic_quantities_mod,                                          &
     682           ONLY: e_s, magnus, q_s, sat, supersaturation, t_l
     683
    697684       USE indices,                                                            &
    698685           ONLY:  nxlg, nxrg, nysg, nyng, nzb, nzt
     
    709696       INTEGER(iwp) ::  k                 !<
    710697
    711        REAL(wp)     ::  alpha             !<
    712698       REAL(wp)     ::  cond              !<
    713699       REAL(wp)     ::  cond_max          !<
    714700       REAL(wp)     ::  dc                !<
    715        REAL(wp)     ::  e_s               !<
    716701       REAL(wp)     ::  evap              !<
    717702       REAL(wp)     ::  evap_nc           !<
    718703       REAL(wp)     ::  g_fac             !<
    719704       REAL(wp)     ::  nc_0              !<
    720        REAL(wp)     ::  q_s               !<
    721        REAL(wp)     ::  sat               !<
    722        REAL(wp)     ::  t_l               !<
    723705       REAL(wp)     ::  temp              !<
    724706       REAL(wp)     ::  xc                !<
     
    730712             DO  k = nzb+1, nzt
    731713!
    732 !--             Actual liquid water temperature:
    733                 t_l = t_d_pt(k) * pt(k,j,i)
    734 !
    735 !--             Saturation vapor pressure at t_l:
    736                 e_s = 610.78_wp * EXP( 17.269_wp * ( t_l - 273.16_wp ) /       &
    737                                        ( t_l - 35.86_wp )                      &
    738                                      )
    739 !
    740 !--             Computation of saturation humidity:
    741                 q_s   = 0.622_wp * e_s / ( hyp(k) - 0.378_wp * e_s )
    742                 alpha = 0.622_wp * l_d_r * l_d_cp / ( t_l * t_l )
    743                 q_s   = q_s * ( 1.0_wp + alpha * q(k,j,i) ) /                  &
    744                         ( 1.0_wp + alpha * q_s )
    745 
    746 !--             Supersaturation:
    747                 sat   = ( q(k,j,i) - qr(k,j,i) - qc(k,j,i) ) / q_s - 1.0_wp
    748 
     714!--             Call calculation of supersaturation located
     715!--             in diagnostic_quantities_mod
     716                CALL supersaturation ( i, j, k )
    749717!
    750718!--             Actual temperature:
     
    12001168           ONLY:  cpu_log, log_point_s
    12011169
     1170       USE diagnostic_quantities_mod,                                          &
     1171           ONLY: e_s, magnus, q_s, sat, supersaturation, t_l
     1172
    12021173       USE indices,                                                            &
    12031174           ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzt, wall_flags_0
     
    12111182       INTEGER(iwp) ::  k                 !<
    12121183
    1213        REAL(wp)     ::  alpha             !<
    12141184       REAL(wp)     ::  dr                !<
    1215        REAL(wp)     ::  e_s               !<
    12161185       REAL(wp)     ::  evap              !<
    12171186       REAL(wp)     ::  evap_nr           !<
     
    12241193       REAL(wp)     ::  mu_r_5d2          !<
    12251194       REAL(wp)     ::  nr_0              !<
    1226        REAL(wp)     ::  q_s               !<
    1227        REAL(wp)     ::  sat               !<
    1228        REAL(wp)     ::  t_l               !<
    12291195       REAL(wp)     ::  temp              !<
    12301196       REAL(wp)     ::  xr                !<
     
    12401206
    12411207                IF ( qr(k,j,i) > eps_sb )  THEN
    1242 !
    1243 !--                Actual liquid water temperature:
    1244                    t_l = t_d_pt(k) * pt(k,j,i)
    1245 !
    1246 !--                Saturation vapor pressure at t_l:
    1247                    e_s = 610.78_wp * EXP( 17.269_wp * ( t_l - 273.16_wp ) /    &
    1248                                           ( t_l - 35.86_wp )                   &
    1249                                         )
    1250 !
    1251 !--                Computation of saturation humidity:
    1252                    q_s   = 0.622_wp * e_s / ( hyp(k) - 0.378_wp * e_s )
    1253                    alpha = 0.622_wp * l_d_r * l_d_cp / ( t_l * t_l )
    1254                    q_s   = q_s * ( 1.0_wp + alpha * q(k,j,i) ) /               &
    1255                            ( 1.0_wp + alpha * q_s )
    1256 !
    1257 !--                Supersaturation:
    1258                    sat   = ( q(k,j,i) - qr(k,j,i) - qc(k,j,i) ) / q_s - 1.0_wp
     1208
     1209!
     1210!--                Call calculation of supersaturation located
     1211!--                in diagnostic_quantities_mod
     1212                   CALL supersaturation ( i, j, k )
    12591213!
    12601214!--                Evaporation needs only to be calculated in subsaturated regions
Note: See TracChangeset for help on using the changeset viewer.