Ignore:
Timestamp:
Nov 13, 2012 5:11:03 PM (11 years ago)
Author:
hoffmann
Message:

two-moment cloud physics implemented

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/init_3d_model.f90

    r1037 r1053  
    2323! Current revisions:
    2424! ------------------
    25 !
     25! allocation and initialisation of necessary data arrays for the two-moment
     26! cloud physics scheme the two new prognostic equations (nr, qr):
     27! +dr, lambda_r, mu_r, sed_*, xr, *s, *sws, *swst, *, *_p, t*_m, *_1, *_2, *_3,
     28! +tend_*, prr
    2629!
    2730! Former revisions:
     
    353356
    354357          IF ( cloud_physics ) THEN
     358
    355359!
    356360!--          Liquid water content
     
    364368             ALLOCATE( precipitation_amount(nysg:nyng,nxlg:nxrg), &
    365369                       precipitation_rate(nysg:nyng,nxlg:nxrg) )
     370
     371             IF ( icloud_scheme == 0 )  THEN
     372!
     373!--             1D-rain sedimentation fluxes and rain drop size distribution
     374!--             properties
     375                ALLOCATE ( dr(nzb:nzt+1), lambda_r(nzb:nzt+1),  &
     376                           mu_r(nzb:nzt+1), sed_q(nzb:nzt+1),   &
     377                           sed_qr(nzb:nzt+1), sed_nr(nzb:nzt+1),&
     378                           xr(nzb:nzt+1) )
     379!
     380!--             2D-rain water content and rain drop concentration arrays
     381                ALLOCATE ( qrs(nysg:nyng,nxlg:nxrg),   &
     382                   qrsws(nysg:nyng,nxlg:nxrg),         &
     383                   qrswst(nysg:nyng,nxlg:nxrg),        &
     384                   nrs(nysg:nyng,nxlg:nxrg),           &
     385                   nrsws(nysg:nyng,nxlg:nxrg),         &
     386                   nrswst(nysg:nyng,nxlg:nxrg) )
     387!
     388!--             3D-rain water content, rain drop concentration arrays
     389#if defined( __nopointer )
     390                ALLOCATE( nr(nzb:nzt+1,nysg:nyng,nxlg:nxrg),         &
     391                          nr_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
     392                          qr(nzb:nzt+1,nysg:nyng,nxlg:nxrg),         &
     393                          qr_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
     394                          tnr_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),      &
     395                          tqr_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     396#else
     397                ALLOCATE( nr_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
     398                          nr_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
     399                          nr_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
     400                          qr_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
     401                          qr_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),       &
     402                          qr_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     403#endif
     404!
     405!--             3D-tendency arrays
     406                ALLOCATE( tend_nr(nzb:nzt+1,nysg:nyng,nxlg:nxrg),    &
     407                          tend_pt(nzb:nzt+1,nysg:nyng,nxlg:nxrg),    &
     408                          tend_q(nzb:nzt+1,nysg:nyng,nxlg:nxrg),     &
     409                          tend_qr(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     410!
     411!--             3d-precipitation rate
     412                IF ( precipitation )  THEN
     413                   ALLOCATE( prr(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     414                ENDIF
     415
     416             ENDIF
    366417          ENDIF
    367418
     
    508559    IF ( humidity  .OR.  passive_scalar )  THEN
    509560       q => q_1;  q_p => q_2;  tq_m => q_3
    510        IF ( humidity )        vpt  => vpt_1
    511        IF ( cloud_physics )   ql   => ql_1
     561       IF ( humidity )  THEN
     562          vpt  => vpt_1   
     563          IF ( cloud_physics )  THEN
     564             ql => ql_1
     565             IF ( icloud_scheme == 0 )  THEN
     566                qr => qr_1;  qr_p  => qr_2;  tqr_m  => qr_3
     567                nr => nr_1;  nr_p  => nr_2;  tnr_m  => nr_3
     568             ENDIF
     569          ENDIF
     570       ENDIF
    512571       IF ( cloud_droplets )  THEN
    513572          ql   => ql_1
     
    564623                ENDDO
    565624             ENDDO
     625             IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     626                DO  i = nxlg, nxrg
     627                   DO  j = nysg, nyng
     628                      qr(:,j,i) = qr_init
     629                      nr(:,j,i) = nr_init
     630                   ENDDO
     631                ENDDO
     632             ENDIF
    566633          ENDIF
    567634
     
    606673!--       This could actually be computed more accurately in the 1D model.
    607674!--       Update when opportunity arises!
    608           IF ( humidity  .OR.  passive_scalar )  qs = 0.0
     675          IF ( humidity  .OR.  passive_scalar )  THEN
     676             qs = 0.0
     677             IF ( cloud_physics  .AND.  icloud_scheme == 0 )  THEN
     678                qrs = 0.0
     679                nrs = 0.0
     680             ENDIF
     681          ENDIF
    609682
    610683!
     
    671744                ENDDO
    672745             ENDDO
     746             IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     747                DO  i = nxlg, nxrg
     748                   DO  j = nysg, nyng
     749                      qr(:,j,i) = qr_init
     750                      nr(:,j,i) = nr_init
     751                   ENDDO
     752                ENDDO
     753             ENDIF
    673754          ENDIF
    674755
     
    811892!--       Determine the near-surface water flux
    812893          IF ( humidity  .OR.  passive_scalar )  THEN
     894             IF ( cloud_physics .AND. icloud_scheme )  THEN
     895                IF ( constant_waterflux_qr )  THEN
     896                   qrsws = surface_waterflux_qr
     897                ENDIF
     898                IF (constant_waterflux_nr )  THEN
     899                   nrsws = surface_waterflux_nr
     900                ENDIF
     901             ENDIF
    813902             IF ( constant_waterflux )  THEN
    814903                qsws   = surface_waterflux
     
    842931             tswst = top_heatflux
    843932
    844              IF ( humidity  .OR.  passive_scalar )  qswst = 0.0
     933             IF ( humidity  .OR.  passive_scalar )  THEN
     934                qswst = 0.0
     935                IF ( cloud_physics  .AND.  icloud_scheme == 0 ) THEN
     936                   nrswst = 0.0
     937                   qrswst = 0.0
     938                ENDIF
     939             ENDIF
    845940
    846941             IF ( ocean )  THEN
     
    877972          IF ( humidity  .OR.  passive_scalar )  THEN
    878973             IF ( .NOT. constant_waterflux )  qsws   = 0.0
     974             IF ( cloud_physics  .AND.  icloud_scheme == 0 )  THEN
     975                IF ( .NOT. constant_waterflux_qr )  THEN
     976                   qrsws = 0.0
     977                ENDIF
     978                IF ( .NOT. constant_waterflux_nr )  THEN
     979                   nrsws = 0.0
     980                ENDIF
     981             ENDIF
    879982          ENDIF
    880983
     
    9251028            q_surface_initial_change /= 0.0 )  THEN
    9261029          q(nzb,:,:) = q(nzb,:,:) + q_surface_initial_change
     1030          IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     1031             IF ( qr_surface_initial_change /= 0.0 )  THEN
     1032                qr(nzb,:,:) = qr(nzb,:,:) + qr_surface_initial_change
     1033             ELSEIF ( nr_surface_initial_change /= 0.0 ) THEN
     1034                nr(nzb,:,:) = nr(nzb,:,:) + nr_surface_initial_change
     1035             ENDIF
     1036          ENDIF
    9271037       ENDIF
    9281038
     
    9391049          tq_m = 0.0
    9401050          q_p = q
     1051          IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     1052             tqr_m = 0.0
     1053             qr_p = qr
     1054             tnr_m = 0.0
     1055             nr_p = nr
     1056          ENDIF
    9411057       ENDIF
    9421058
     
    11091225!--    including ghost points)
    11101226       e_p = e; pt_p = pt; u_p = u; v_p = v; w_p = w
    1111        IF ( humidity  .OR.  passive_scalar )  q_p = q
     1227       IF ( humidity  .OR.  passive_scalar )  THEN
     1228          q_p = q
     1229          IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     1230             qr_p = qr
     1231             nr_p = nr
     1232          ENDIF
     1233       ENDIF
    11121234       IF ( ocean )  sa_p = sa
    11131235
     
    11171239!--    there before they are set.
    11181240       te_m = 0.0; tpt_m = 0.0; tu_m = 0.0; tv_m = 0.0; tw_m = 0.0
    1119        IF ( humidity  .OR.  passive_scalar )  tq_m = 0.0
     1241       IF ( humidity  .OR.  passive_scalar )  THEN
     1242          tq_m = 0.0
     1243          IF ( cloud_physics .AND. icloud_scheme == 0 )  THEN
     1244             tqr_m = 0.0
     1245             tnr_m = 0.0
     1246          ENDIF
     1247       ENDIF
    11201248       IF ( ocean )  tsa_m = 0.0
    11211249
Note: See TracChangeset for help on using the changeset viewer.