Ignore:
Timestamp:
Jun 20, 2017 9:51:42 AM (7 years ago)
Author:
schwenkel
Message:

implementation of new bulk microphysics scheme

File:
1 edited

Legend:

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

    r2233 r2292  
    2525! -----------------
    2626! $Id$
     27! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
     28! includes two more prognostic equations for cloud drop concentration (nc) 
     29! and cloud water content (qc).
     30!
     31! 2233 2017-05-30 18:08:54Z suehring
    2732!
    2833! 2232 2017-05-30 17:47:52Z suehring
     
    151156    USE arrays_3d,                                                             &
    152157        ONLY:  c_u, c_u_m, c_u_m_l, c_v, c_v_m, c_v_m_l, c_w, c_w_m, c_w_m_l,  &
    153                dzu, e_p, nr_p, pt, pt_p, q, q_p, qr_p, s, s_p, sa, sa_p,       &
    154                u, ug, u_init, u_m_l, u_m_n, u_m_r, u_m_s, u_p,                 &
     158               dzu, e_p, nc_p, nr_p, pt, pt_p, q, q_p, qc_p, qr_p, s, s_p, sa, &
     159               sa_p, u, ug, u_init, u_m_l, u_m_n, u_m_r, u_m_s, u_p,           &
    155160               v, vg, v_init, v_m_l, v_m_n, v_m_r, v_m_s, v_p,                 &
    156161               w, w_p, w_m_l, w_m_n, w_m_r, w_m_s, pt_init
    157 
     162               
    158163    USE control_parameters,                                                    &
    159164        ONLY:  bc_pt_t_val, bc_q_t_val, bc_s_t_val, constant_diffusion,        &
     
    162167               ibc_sa_t, ibc_uv_b, ibc_uv_t, inflow_l, inflow_n, inflow_r,     &
    163168               inflow_s, intermediate_timestep_count, large_scale_forcing,     &
    164                microphysics_seifert, nest_domain, nest_bound_l, nest_bound_s,  &
    165                nudging, ocean, outflow_l, outflow_n, outflow_r, outflow_s,     &
    166                passive_scalar, tsc, use_cmax
     169               microphysics_morrison, microphysics_seifert, nest_domain,       &
     170               nest_bound_l, nest_bound_s, nudging, ocean, outflow_l,          &
     171               outflow_n, outflow_r, outflow_s, passive_scalar, tsc, use_cmax
    167172
    168173    USE grid_variables,                                                        &
     
    393398       ELSEIF ( ibc_q_t == 1 ) THEN
    394399          q_p(nzt+1,:,:) = q_p(nzt,:,:) + bc_q_t_val * dzu(nzt+1)
     400       ENDIF
     401
     402       IF ( cloud_physics  .AND.  microphysics_morrison )  THEN
     403!             
     404!--       Surface conditions cloud water (Dirichlet)
     405!--       Run loop over all non-natural and natural walls. Note, in wall-datatype
     406!--       the k coordinate belongs to the atmospheric grid point, therefore, set
     407!--       qr_p and nr_p at k-1
     408          !$OMP PARALLEL DO PRIVATE( i, j, k )
     409          DO  m = 1, bc_h(0)%ns
     410             i = bc_h(0)%i(m)           
     411             j = bc_h(0)%j(m)
     412             k = bc_h(0)%k(m)
     413             qc_p(k-1,j,i) = 0.0_wp
     414             nc_p(k-1,j,i) = 0.0_wp
     415          ENDDO
     416!
     417!--       Top boundary condition for cloud water (Dirichlet)
     418          qc_p(nzt+1,:,:) = 0.0_wp
     419          nc_p(nzt+1,:,:) = 0.0_wp
     420           
    395421       ENDIF
    396422
     
    514540       IF ( humidity )  THEN
    515541          q_p(:,nys-1,:) = q_p(:,nys,:)
     542          IF ( cloud_physics  .AND.  microphysics_morrison )  THEN
     543             qc_p(:,nys-1,:) = qc_p(:,nys,:)
     544             nc_p(:,nys-1,:) = nc_p(:,nys,:)
     545          ENDIF
    516546          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
    517547             qr_p(:,nys-1,:) = qr_p(:,nys,:)
     
    525555       IF ( humidity )  THEN
    526556          q_p(:,nyn+1,:) = q_p(:,nyn,:)
     557          IF ( cloud_physics  .AND.  microphysics_morrison )  THEN
     558             qc_p(:,nyn+1,:) = qc_p(:,nyn,:)
     559             nc_p(:,nyn+1,:) = nc_p(:,nyn,:)
     560          ENDIF
    527561          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
    528562             qr_p(:,nyn+1,:) = qr_p(:,nyn,:)
     
    536570       IF ( humidity )  THEN
    537571          q_p(:,:,nxl-1) = q_p(:,:,nxl)
     572          IF ( cloud_physics  .AND.  microphysics_morrison )  THEN
     573             qc_p(:,:,nxl-1) = qc_p(:,:,nxl)
     574             nc_p(:,:,nxl-1) = nc_p(:,:,nxl)
     575          ENDIF
    538576          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
    539577             qr_p(:,:,nxl-1) = qr_p(:,:,nxl)
     
    547585       IF ( humidity )  THEN
    548586          q_p(:,:,nxr+1) = q_p(:,:,nxr)
     587          IF ( cloud_physics  .AND.  microphysics_morrison )  THEN
     588             qc_p(:,:,nxr+1) = qc_p(:,:,nxr)
     589             nc_p(:,:,nxr+1) = nc_p(:,:,nxr)
     590          ENDIF
    549591          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
    550592             qr_p(:,:,nxr+1) = qr_p(:,:,nxr)
Note: See TracChangeset for help on using the changeset viewer.