Changeset 2547 for palm/trunk


Ignore:
Timestamp:
Oct 16, 2017 12:41:56 PM (7 years ago)
Author:
schwenkel
Message:

extended by cloud_droplets option

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

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

    r2532 r2547  
    2525! -----------------
    2626! $Id$
     27! extended by cloud_droplets option
     28!
     29! 2532 2017-10-11 16:00:46Z scharf
    2730! bugfixes in data_output_3d
    2831!
     
    281284
    282285    USE control_parameters,                                                    &
    283         ONLY:  cloud_physics, coupling_start_time, dt_3d, end_time, humidity,  &
    284                intermediate_timestep_count,                                    &
     286        ONLY:  cloud_droplets, cloud_physics, coupling_start_time, dt_3d,      &
     287               end_time, humidity, intermediate_timestep_count,                &
    285288               initializing_actions, intermediate_timestep_count_max,          &
    286289               land_surface, max_masks, precipitation, pt_surface,             &
     
    15311534          pt1 = pt(k,j,i) + l_d_cp * pt_d_t(k) * ql(k,j,i)
    15321535          qv1 = q(k,j,i) - ql(k,j,i)
     1536       ELSEIF ( cloud_droplets ) THEN
     1537          pt1 = pt(k,j,i) + l_d_cp * pt_d_t(k) * ql(k,j,i)
     1538          qv1 = q(k,j,i)
    15331539       ELSE
    15341540          pt1 = pt(k,j,i)
     
    19501956!
    19511957!--       Calculate specific humidity at saturation
    1952           q_s = 0.622_wp * e_s / surface_pressure
     1958          q_s = 0.622_wp * e_s / surface_pressure - e_s
    19531959
    19541960          resistance = surf%r_a(m) / ( surf%r_a(m) + surf%r_s(m) )
     
    24912497             ENDIF
    24922498             
    2493              IF ( cloud_physics )  THEN
     2499             IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    24942500                pt1 = pt(k,j,i) + l_d_cp * pt_d_t(k) * ql(k,j,i)
    24952501             ELSE
     
    25852591                k   = surf_lsm_v(l)%k(m)
    25862592
    2587                 IF ( cloud_physics )  THEN
     2593                IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    25882594                   pt1 = pt(k,j,i) + l_d_cp * pt_d_t(k) * ql(k,j,i)
    25892595                ELSE
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r2544 r2547  
    2525! -----------------
    2626! $Id$
     27! extended by cloud_droplets option, minor bugfix and correct calculation of
     28! cloud droplet number concentration
     29!
     30! 2544 2017-10-13 18:09:32Z maronga
    2731! Moved date and time quantitis to separate module date_and_time_mod
    2832!
     
    173177 
    174178    USE arrays_3d,                                                             &
    175         ONLY:  dzw, hyp, pt, q, ql, zu, zw
     179        ONLY:  dzw, hyp, nc, pt, q, ql, zu, zw
    176180
    177181    USE cloud_parameters,                                                      &
     
    183187    USE control_parameters,                                                    &
    184188        ONLY:  cloud_droplets, cloud_physics, g, initializing_actions,         &
    185                large_scale_forcing, lsf_surf, phi, pt_surface, rho_surface,    &
    186                surface_pressure, time_since_reference_point
     189               large_scale_forcing, lsf_surf, microphysics_morrison, phi,      &
     190               pt_surface, rho_surface, surface_pressure,                      &
     191               time_since_reference_point
    187192
    188193    USE date_and_time_mod,                                                     &
     
    12521257             rad_lw_out(0,j,i) = emis(j,i) * sigma_sb * (pt(k,j,i) * exn)**4
    12531258
    1254              IF ( cloud_physics )  THEN
     1259             IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    12551260                pt1 = pt(k+1,j,i) + l_d_cp / exn1 * ql(k+1,j,i)
    12561261                rad_lw_in(0,j,i)  = 0.8_wp * sigma_sb * (pt1 * exn1)**4
     
    13031308             exn1 = (hyp(k+1) / 100000.0_wp )**0.286_wp
    13041309
    1305              IF ( cloud_physics )  THEN
     1310             IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    13061311                pt1 = pt(k+1,j,i) + l_d_cp / exn1 * ql(k+1,j,i)
    13071312                rad_lw_in(0,j,i)  = 0.8_wp * sigma_sb * (pt1 * exn1)**4
     
    14501455       INTEGER(iwp) :: i, j, k, n !< loop indices
    14511456
    1452        REAL(wp)     ::  s_r2, &   !< weighted sum over all droplets with r^2
    1453                         s_r3      !< weighted sum over all droplets with r^3
     1457       REAL(wp)     ::  nc_rad, &    !< number concentration of cloud droplets
     1458                        s_r2,   &    !< weighted sum over all droplets with r^2
     1459                        s_r3         !< weighted sum over all droplets with r^3
    14541460
    14551461!
     
    14901496                   rrtm_h2ovmr(0,k) = mol_mass_air_d_wv * (q(k,j,i) - ql(k,j,i))
    14911497                ENDDO
     1498             ELSEIF ( cloud_droplets ) THEN
     1499                DO k = nzb+1, nzt+1
     1500                   rrtm_tlay(0,k) = pt(k,j,i) * ( (hyp(k) ) / 100000.0_wp      &
     1501                                    )**0.286_wp + l_d_cp * ql(k,j,i)
     1502                   rrtm_h2ovmr(0,k) = mol_mass_air_d_wv * q(k,j,i)
     1503                ENDDO     
    14921504             ELSE
    14931505                DO k = nzb+1, nzt+1
     
    15311543             rrtm_icld   = 0
    15321544
    1533              IF ( cloud_physics )  THEN
     1545             IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    15341546                DO k = nzb+1, nzt+1
    15351547                   rrtm_cliqwp(0,k) =  ql(k,j,i) * 1000.0_wp *                 &
     
    15441556!--                   Calculate cloud droplet effective radius
    15451557                      IF ( cloud_physics )  THEN
     1558                         nc_rad = MERGE( nc(k,j,i), nc_const, microphysics_morrison )
    15461559                         rrtm_reliq(0,k) = 1.0E6_wp * ( 3.0_wp * ql(k,j,i)     &
    15471560                                           * rho_surface                       &
    1548                                            / ( 4.0_wp * pi * nc_const * rho_l )&
     1561                                           / ( 4.0_wp * pi * nc_rad * rho_l )&
    15491562                                           )**0.33333333333333_wp              &
    15501563                                           * EXP( LOG( sigma_gc )**2 )
  • palm/trunk/SOURCE/surface_layer_fluxes_mod.f90

    r2321 r2547  
    2525! -----------------
    2626! $Id$
     27! extended by cloud_droplets option
     28!
     29! 2321 2017-07-24 15:57:07Z schwenkel
    2730! Bugfix: Correct index in lookup table for Obukhov length
    2831!
     
    201204
    202205    USE control_parameters,                                                    &
    203         ONLY:  cloud_physics, constant_heatflux, constant_scalarflux,          &
    204                constant_waterflux, coupling_mode, g, humidity, ibc_e_b,        &
    205                ibc_pt_b, initializing_actions, kappa,                          &
     206        ONLY:  cloud_droplets, cloud_physics, constant_heatflux,               &
     207               constant_scalarflux, constant_waterflux, coupling_mode, g,      &
     208               humidity, ibc_e_b, ibc_pt_b, initializing_actions, kappa,       &
    206209               intermediate_timestep_count, intermediate_timestep_count_max,   &
    207210               land_surface, large_scale_forcing, lsf_surf,                    &
     
    291294!--    temperature and specific humidity at first grid level from the fields pt
    292295!--    and q
    293        IF ( cloud_physics )  THEN
     296       IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    294297!
    295298!--       First call for horizontal default-type surfaces (l=0 - upward facing,
     
    13961399
    13971400             ENDDO
    1398           ELSEIF ( cloud_physics )  THEN
     1401          ELSEIF ( cloud_physics  .OR.  cloud_droplets )  THEN
    13991402             !$OMP PARALLEL DO PRIVATE( i, j, k, z_mo )
    14001403             DO  m = 1, surf%ns
     
    15291532          k   = surf%k(m)
    15301533
    1531           surf%pt1(m) = pt(k,j,i) + l_d_cp * pt_d_t(k) * ql(k,j,i)
    1532           surf%qv1(m) = q(k,j,i) - ql(k,j,i)
     1534          IF ( cloud_physics ) THEN
     1535             surf%pt1(m) = pt(k,j,i) + l_d_cp * pt_d_t(k) * ql(k,j,i)
     1536             surf%qv1(m) = q(k,j,i) - ql(k,j,i)
     1537          ELSEIF( cloud_droplets ) THEN
     1538             surf%pt1(m) = pt(k,j,i) + l_d_cp * pt_d_t(k) * ql(k,j,i)
     1539             surf%qv1(m) = q(k,j,i)
     1540          ENDIF
    15331541
    15341542       ENDDO
     
    15841592          ENDIF
    15851593
    1586           IF ( cloud_physics )  THEN
     1594          IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    15871595             !$OMP PARALLEL DO PRIVATE( i, j, k, z_mo )
    15881596             DO  m = 1, surf%ns   
     
    16851693             ENDIF
    16861694
    1687              IF ( cloud_physics )  THEN
     1695             IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    16881696               !$OMP PARALLEL DO PRIVATE( i, j, k, z_mo )
    16891697                DO  m = 1, surf%ns   
  • palm/trunk/SOURCE/surface_mod.f90

    r2508 r2547  
    2525! -----------------
    2626! $Id$
     27! extended by cloud_droplets option
     28!
     29! 2508 2017-10-02 08:57:09Z suehring
    2730! Minor formatting adjustment
    2831!
     
    139142       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0q       !< roughness length for humidity
    140143
    141        REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt1       !< Specific humidity at first grid level (required for cloud_physics = .T.)
    142        REAL(wp), DIMENSION(:), ALLOCATABLE ::  qv1       !< Potential temperature at first grid level (required for cloud_physics = .T.)
     144       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt1       !< Specific humidity at first grid level (required for cloud_physics = .T. or cloud_droplets = .T.)
     145       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qv1       !< Potential temperature at first grid level (required for cloud_physics = .T. or cloud_droplets = .T.)
    143146!
    144147!--    Define arrays for surface fluxes
     
    745748!--    When cloud physics is used, arrays for storing potential temperature and
    746749!--    specific humidity at first grid level are required.
    747        IF ( cloud_physics )  THEN
     750       IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    748751          ALLOCATE ( surfaces%pt1(1:surfaces%ns) )
    749752          ALLOCATE ( surfaces%qv1(1:surfaces%ns) )
Note: See TracChangeset for help on using the changeset viewer.