Ignore:
Timestamp:
Mar 26, 2013 6:16:16 PM (11 years ago)
Author:
hoffmann
Message:

optimization of two-moments cloud physics

File:
1 edited

Legend:

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

    r1114 r1115  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! boundary conditions of two-moment cloud scheme are restricted to Neumann-
     23! boundary-conditions
    2324
    2425! Former revisions:
     
    246247       q_p(nzt+1,:,:) = q_p(nzt,:,:)   + bc_q_t_val * dzu(nzt+1)
    247248
    248        IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     249       IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
     250            precipitation )  THEN
    249251!             
    250 !--       Surface conditions for constant_humidity_flux
    251           IF ( ibc_qr_b == 0 ) THEN
    252              DO  i = nxlg, nxrg
    253                 DO  j = nysg, nyng
    254                    qr_p(nzb_s_inner(j,i),j,i) = qr(nzb_s_inner(j,i),j,i)
    255                 ENDDO
    256              ENDDO
    257           ELSE
    258              DO  i = nxlg, nxrg
    259                 DO  j = nysg, nyng
    260                    qr_p(nzb_s_inner(j,i),j,i) = qr_p(nzb_s_inner(j,i)+1,j,i)
    261                 ENDDO
    262              ENDDO
    263           ENDIF
    264 !
    265 !--       Top boundary
    266           qr_p(nzt+1,:,:) = qr_p(nzt,:,:) + bc_qr_t_val * dzu(nzt+1)
    267 !             
    268 !--       Surface conditions for constant_humidity_flux
    269           IF ( ibc_nr_b == 0 ) THEN
    270              DO  i = nxlg, nxrg
    271                 DO  j = nysg, nyng
    272                    nr_p(nzb_s_inner(j,i),j,i) = nr(nzb_s_inner(j,i),j,i)
    273                 ENDDO
    274              ENDDO
    275           ELSE
    276              DO  i = nxlg, nxrg
    277                 DO  j = nysg, nyng
    278                    nr_p(nzb_s_inner(j,i),j,i) = nr_p(nzb_s_inner(j,i)+1,j,i)
    279                 ENDDO
    280              ENDDO
    281           ENDIF
    282 !
    283 !--       Top boundary
    284           nr_p(nzt+1,:,:) = nr_p(nzt,:,:) + bc_nr_t_val * dzu(nzt+1)
     252!--       Surface conditions rain water (Neumann)
     253          DO  i = nxlg, nxrg
     254             DO  j = nysg, nyng
     255                qr_p(nzb_s_inner(j,i),j,i) = qr_p(nzb_s_inner(j,i)+1,j,i)
     256                nr_p(nzb_s_inner(j,i),j,i) = nr_p(nzb_s_inner(j,i)+1,j,i)
     257             ENDDO
     258          ENDDO
     259!
     260!--       Top boundary condition for rain water (Neumann)
     261          qr_p(nzt+1,:,:) = qr_p(nzt,:,:)
     262          nr_p(nzt+1,:,:) = nr_p(nzt,:,:)
     263           
    285264       ENDIF
    286 
    287265!
    288266!--    In case of inflow at the south boundary the boundary for v is at nys
     
    308286          pt_p(:,nys-1,:)     = pt_p(:,nys,:)
    309287          IF ( .NOT. constant_diffusion     )  e_p(:,nys-1,:) = e_p(:,nys,:)
    310           IF ( humidity .OR. passive_scalar )  THEN
     288          IF ( humidity  .OR. passive_scalar )  THEN
    311289             q_p(:,nys-1,:) = q_p(:,nys,:)
    312              IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     290             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
     291                  precipitation)  THEN
    313292                qr_p(:,nys-1,:) = qr_p(:,nys,:)
    314293                nr_p(:,nys-1,:) = nr_p(:,nys,:)
     
    318297          pt_p(:,nyn+1,:)     = pt_p(:,nyn,:)
    319298          IF ( .NOT. constant_diffusion     )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
    320           IF ( humidity .OR. passive_scalar )  THEN
     299          IF ( humidity  .OR. passive_scalar )  THEN
    321300             q_p(:,nyn+1,:) = q_p(:,nyn,:)
    322              IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     301             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
     302                  precipitation )  THEN
    323303                qr_p(:,nyn+1,:) = qr_p(:,nyn,:)
    324304                nr_p(:,nyn+1,:) = nr_p(:,nyn,:)
     
    328308          pt_p(:,:,nxl-1)     = pt_p(:,:,nxl)
    329309          IF ( .NOT. constant_diffusion     )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
    330           IF ( humidity .OR. passive_scalar )  THEN
     310          IF ( humidity  .OR. passive_scalar )  THEN
    331311             q_p(:,:,nxl-1) = q_p(:,:,nxl)
    332              IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     312             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  &
     313                  precipitation )  THEN
    333314                qr_p(:,:,nxl-1) = qr_p(:,:,nxl)
    334315                nr_p(:,:,nxl-1) = nr_p(:,:,nxl)
     
    340321          IF ( humidity .OR. passive_scalar )  THEN
    341322             q_p(:,:,nxr+1) = q_p(:,:,nxr)
    342              IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     323             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  precipitation )  THEN
    343324                qr_p(:,:,nxr+1) = qr_p(:,:,nxr)
    344325                nr_p(:,:,nxr+1) = nr_p(:,:,nxr)
Note: See TracChangeset for help on using the changeset viewer.