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/prognostic_equations.f90

    r1112 r1115  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! optimized cloud physics: calculation of microphysical tendencies transfered
     23! to microphysics.f90; qr and nr are only calculated if precipitation is required
    2324!
    2425! Former revisions:
     
    229230    IF ( ( ws_scheme_mom .OR. ws_scheme_sca )  .AND.  &
    230231         intermediate_timestep_count == 1 )  CALL ws_statistics
    231 
    232232!
    233233!-- Loop over all prognostic equations
     
    285285
    286286             CALL user_actions( i, j, 'u-tendency' )
    287 
    288287!
    289288!--          Prognostic equation for u-velocity component
     
    341340
    342341             CALL user_actions( i, j, 'v-tendency' )
    343 
    344342!
    345343!--          Prognostic equation for v-velocity component
     
    422420             ENDIF
    423421          ENDIF
    424 
    425 !
    426 !--       If required, calculate tendencies for total water content, rain water
    427 !--       content, rain drop concentration and liquid temperature
    428           IF ( cloud_physics  .AND.  icloud_scheme == 0 )  THEN
    429 
    430              tend_q(:,j,i)  = 0.0
    431              tend_qr(:,j,i) = 0.0
    432              tend_nr(:,j,i) = 0.0
    433              tend_pt(:,j,i) = 0.0
    434 !
    435 !--          Droplet size distribution (dsd) properties are needed for the
    436 !--          computation of selfcollection, breakup, evaporation and
    437 !--          sedimentation of rain
    438              IF ( precipitation )  THEN
    439                 CALL dsd_properties( i,j )
    440                 CALL autoconversion( i,j )
    441                 CALL accretion( i,j )
    442                 CALL selfcollection_breakup( i,j )
    443                 CALL evaporation_rain( i,j )
    444                 CALL sedimentation_rain( i,j )
    445              ENDIF
    446 
    447              IF ( drizzle )  CALL sedimentation_cloud( i,j )
    448 
    449           ENDIF
    450 
     422!
     423!--       If required, calculate tendencies for total water content, liquid water
     424!--       potential temperature, rain water content and rain drop concentration
     425          IF ( cloud_physics  .AND.  icloud_scheme == 0 )  CALL microphysics_control( i, j )
    451426!
    452427!--       If required, compute prognostic equation for potential temperature
     
    650625!--          If required, calculate prognostic equations for rain water content
    651626!--          and rain drop concentration
    652              IF ( cloud_physics  .AND.  icloud_scheme == 0 )  THEN
     627             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.              &
     628                  precipitation )  THEN
    653629!
    654630!--             Calculate prognostic equation for rain water content
     
    667643                ENDIF
    668644                CALL diffusion_s( i, j, qr, qrsws, qrswst, wall_qrflux )
    669 
    670645!
    671646!--             Using microphysical tendencies (autoconversion, accretion,
     
    673648                tend(:,j,i) = tend(:,j,i) + tend_qr(:,j,i)
    674649
    675 !
    676 !--             If required, compute influence of large-scale subsidence/ascent
    677                 IF ( large_scale_subsidence )  THEN
    678                    CALL subsidence( i, j, tend, qr, qr_init )
    679                 ENDIF
    680 
    681 !              CALL user_actions( i, j, 'qr-tendency' )
    682 
     650                CALL user_actions( i, j, 'qr-tendency' )
    683651!
    684652!--             Prognostic equation for rain water content
    685653                DO  k = nzb_s_inner(j,i)+1, nzt
    686                    qr_p(k,j,i) = qr(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +    &
    687                                                      tsc(3) * tqr_m(k,j,i) )     &
    688                                          - tsc(5) * rdf_sc(k) *                  &
    689                                         ( qr(k,j,i) - qr_init(k) )
    690                    IF ( qr_p(k,j,i) < 0.0 )  qr_p(k,j,i) = 0.1 * qr(k,j,i)
     654                   qr_p(k,j,i) = qr(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +  &
     655                                                       tsc(3) * tqr_m(k,j,i) ) &
     656                                           - tsc(5) * rdf_sc(k) * qr(k,j,i)
     657                   IF ( qr_p(k,j,i) < 0.0 )  qr_p(k,j,i) = 0.0
    691658                ENDDO
    692659!
     
    711678                IF ( timestep_scheme(1:5) == 'runge' )  THEN
    712679                   IF ( ws_scheme_sca )  THEN
    713                       CALL advec_s_ws( i, j, nr, 'nr', flux_s_nr,       &
    714                                        diss_s_nr, flux_l_nr, diss_l_nr, &
    715                                        i_omp_start, tn )
     680                      CALL advec_s_ws( i, j, nr, 'nr', flux_s_nr,    &
     681                                    diss_s_nr, flux_l_nr, diss_l_nr, &
     682                                    i_omp_start, tn )
    716683                   ELSE
    717684                      CALL advec_s_pw( i, j, nr )
     
    721688                ENDIF
    722689                CALL diffusion_s( i, j, nr, nrsws, nrswst, wall_nrflux )
    723 
     690!
    724691!--             Using microphysical tendencies (autoconversion, accretion,
    725692!--             selfcollection, breakup, evaporation;
     
    727694                tend(:,j,i) = tend(:,j,i) + tend_nr(:,j,i)
    728695
    729 !
    730 !--             If required, compute influence of large-scale subsidence/ascent
    731                 IF ( large_scale_subsidence )  THEN
    732                    CALL subsidence( i, j, tend, nr, nr_init )
    733                 ENDIF
    734 
    735 !                CALL user_actions( i, j, 'nr-tendency' )
    736 
     696                CALL user_actions( i, j, 'nr-tendency' )
    737697!
    738698!--             Prognostic equation for rain drop concentration
    739699                DO  k = nzb_s_inner(j,i)+1, nzt
    740                    nr_p(k,j,i) = nr(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) + &
    741                                                   tsc(3) * tnr_m(k,j,i) )     &
    742                                       - tsc(5) * rdf_sc(k) *                  &
    743                                         ( nr(k,j,i) - nr_init(k) )
    744                    IF ( nr_p(k,j,i) < 0.0 )  nr_p(k,j,i) = 0.1 * nr(k,j,i)
     700                   nr_p(k,j,i) = nr(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +  &
     701                                                       tsc(3) * tnr_m(k,j,i) ) &
     702                                           - tsc(5) * rdf_sc(k) * nr(k,j,i)
     703                   IF ( nr_p(k,j,i) < 0.0 )  nr_p(k,j,i) = 0.0
    745704                ENDDO
    746705!
     
    762721             ENDIF
    763722
    764           ENDIF
    765 
     723         ENDIF
    766724!
    767725!--       If required, compute prognostic equation for turbulent kinetic
Note: See TracChangeset for help on using the changeset viewer.