Ignore:
Timestamp:
Apr 16, 2014 3:17:48 PM (11 years ago)
Author:
hoffmann
Message:

improved version of two-moment cloud physics

File:
1 edited

Legend:

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

    r1354 r1361  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Two-moment microphysics moved to the start of prognostic equations. This makes
     23! the 3d arrays for tend_q, tend_qr, tend_pt and tend_pt redundant.
     24! Additionally, it is allowed to call the microphysics just once during the time
     25! step (not at each sub-time step).
     26!
     27! Two-moment cloud physics added for vector and accelerator optimization.
    2328!
    2429! Former revisions:
     
    126131               nrswst, pt, ptdf_x, ptdf_y, pt_init, pt_p, prho, q, q_init,     &
    127132               q_p, qsws, qswst, qr, qr_p, qrsws, qrswst, rdf, rdf_sc, rho,    &
    128                sa, sa_init, sa_p, saswsb, saswst, shf, tend, tend_nr,          &
    129                tend_pt, tend_q, tend_qr, te_m, tnr_m, tpt_m, tq_m, tqr_m,      &
    130                tsa_m, tswst, tu_m, tv_m, tw_m, u, ug, u_p, v, vg, vpt, v_p,    &
    131                w, w_p
     133               sa, sa_init, sa_p, saswsb, saswst, shf, tend, te_m, tnr_m,      &
     134               tpt_m, tq_m, tqr_m, tsa_m, tswst, tu_m, tv_m, tw_m, u, ug, u_p, &
     135               v, vg, vpt, v_p, w, w_p
    132136       
    133137    USE control_parameters,                                                    &
    134         ONLY:  cloud_physics, constant_diffusion, cthf, dp_external,           &
     138        ONLY:  call_microphysics_at_all_substeps, cloud_physics,               &
     139               constant_diffusion, cthf, dp_external,                          &
    135140               dp_level_ind_b, dp_smooth_factor, dpdxy, dt_3d, humidity,       &
    136141               icloud_scheme, inflow_l, intermediate_timestep_count,           &
     
    301306 
    302307       DO  j = nys, nyn
     308!
     309!--       If required, calculate cloud microphysical impacts (two-moment scheme)
     310          IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                 &
     311               ( intermediate_timestep_count == 1  .OR.                        &
     312                 call_microphysics_at_all_substeps )                           &
     313             )  THEN
     314             CALL microphysics_control( i, j )
     315          ENDIF
    303316!
    304317!--       Tendency terms for u-velocity component
     
    481494             ENDIF
    482495          ENDIF
    483 !
    484 !--       If required, calculate tendencies for total water content, liquid water
    485 !--       potential temperature, rain water content and rain drop concentration
    486           IF ( cloud_physics  .AND.  icloud_scheme == 0 )  CALL microphysics_control( i, j )
     496
    487497!
    488498!--       If required, compute prognostic equation for potential temperature
     
    511521
    512522!
    513 !--          Using microphysical tendencies (latent heat)
    514              IF ( cloud_physics )  THEN
    515                 IF ( icloud_scheme == 0 )  THEN
    516                    tend(:,j,i) = tend(:,j,i) + tend_pt(:,j,i)
    517                 ELSEIF ( icloud_scheme == 1  .AND.  precipitation )  THEN
    518                    CALL impact_of_latent_heat( i, j )
    519                 ENDIF
     523!--          If required compute impact of latent heat due to precipitation
     524             IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.              &
     525                  precipitation )  THEN
     526                CALL impact_of_latent_heat( i, j )
    520527             ENDIF
    521528
     
    641648     
    642649!
    643 !--          Using microphysical tendencies
    644              IF ( cloud_physics )  THEN
    645                 IF ( icloud_scheme == 0 )  THEN
    646                    tend(:,j,i) = tend(:,j,i) + tend_q(:,j,i)
    647                 ELSEIF ( icloud_scheme == 1  .AND.  precipitation )  THEN
    648                    CALL calc_precipitation( i, j )
    649                 ENDIF
     650!--          If required compute decrease of total water content due to
     651!--          precipitation
     652             IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.              &
     653                  precipitation )  THEN
     654                CALL calc_precipitation( i, j )             
    650655             ENDIF
    651656!
     
    712717                ENDIF
    713718                CALL diffusion_s( i, j, qr, qrsws, qrswst, wall_qrflux )
    714 !
    715 !--             Using microphysical tendencies (autoconversion, accretion,
    716 !--             evaporation; if required: sedimentation)
    717                 tend(:,j,i) = tend(:,j,i) + tend_qr(:,j,i)
    718719
    719720                CALL user_actions( i, j, 'qr-tendency' )
     
    757758                ENDIF
    758759                CALL diffusion_s( i, j, nr, nrsws, nrswst, wall_nrflux )
    759 !
    760 !--             Using microphysical tendencies (autoconversion, accretion,
    761 !--             selfcollection, breakup, evaporation;
    762 !--             if required: sedimentation)
    763                 tend(:,j,i) = tend(:,j,i) + tend_nr(:,j,i)
    764760
    765761                CALL user_actions( i, j, 'nr-tendency' )
     
    883879
    884880!
     881!-- If required, calculate cloud microphysical impacts (two-moment scheme)
     882    IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                       &
     883         ( intermediate_timestep_count == 1  .OR.                              &
     884           call_microphysics_at_all_substeps )                                 &
     885       )  THEN
     886       CALL cpu_log( log_point(51), 'microphysics', 'start' )
     887       CALL microphysics_control
     888       CALL cpu_log( log_point(51), 'microphysics', 'stop' )
     889    ENDIF
     890
     891!
    885892!-- u-velocity component
    886893    CALL cpu_log( log_point(5), 'u-equation', 'start' )
     
    11561163!
    11571164!--    If required compute impact of latent heat due to precipitation
    1158        IF ( precipitation )  THEN
     1165       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
    11591166          CALL impact_of_latent_heat
    11601167       ENDIF
     
    13481355!--    If required compute decrease of total water content due to
    13491356!--    precipitation
    1350        IF ( precipitation )  THEN
     1357       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
    13511358          CALL calc_precipitation
    13521359       ENDIF
     
    14061413
    14071414       CALL cpu_log( log_point(29), 'q/s-equation', 'stop' )
     1415
     1416!
     1417!--    If required, calculate prognostic equations for rain water content
     1418!--    and rain drop concentration
     1419       IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  precipitation )  THEN
     1420
     1421          CALL cpu_log( log_point(52), 'qr-equation', 'start' )
     1422
     1423!
     1424!--       Calculate prognostic equation for rain water content
     1425          sbt = tsc(2)
     1426          IF ( scalar_advec == 'bc-scheme' )  THEN
     1427
     1428             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     1429!
     1430!--             Bott-Chlond scheme always uses Euler time step. Thus:
     1431                sbt = 1.0_wp
     1432             ENDIF
     1433             tend = 0.0_wp
     1434             CALL advec_s_bc( qr, 'qr' )
     1435
     1436          ENDIF
     1437
     1438!
     1439!--       qr-tendency terms with no communication
     1440          IF ( scalar_advec /= 'bc-scheme' )  THEN
     1441             tend = 0.0_wp
     1442             IF ( timestep_scheme(1:5) == 'runge' )  THEN
     1443                IF ( ws_scheme_sca )  THEN
     1444                   CALL advec_s_ws( qr, 'qr' )
     1445                ELSE
     1446                   CALL advec_s_pw( qr )
     1447                ENDIF
     1448             ELSE
     1449                CALL advec_s_up( qr )
     1450             ENDIF
     1451          ENDIF
     1452
     1453          CALL diffusion_s( qr, qrsws, qrswst, wall_qrflux )
     1454
     1455          CALL user_actions( 'qr-tendency' )
     1456
     1457!
     1458!--       Prognostic equation for rain water content
     1459          DO  i = nxl, nxr
     1460             DO  j = nys, nyn
     1461                DO  k = nzb_s_inner(j,i)+1, nzt
     1462                   qr_p(k,j,i) = qr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
     1463                                                     tsc(3) * tqr_m(k,j,i) )   &
     1464                                           - tsc(5) * rdf_sc(k) * qr(k,j,i)
     1465                   IF ( qr_p(k,j,i) < 0.0_wp )  qr_p(k,j,i) = 0.0_wp
     1466                ENDDO
     1467             ENDDO
     1468          ENDDO
     1469
     1470!
     1471!--       Calculate tendencies for the next Runge-Kutta step
     1472          IF ( timestep_scheme(1:5) == 'runge' )  THEN
     1473             IF ( intermediate_timestep_count == 1 )  THEN
     1474                DO  i = nxl, nxr
     1475                   DO  j = nys, nyn
     1476                      DO  k = nzb_s_inner(j,i)+1, nzt
     1477                         tqr_m(k,j,i) = tend(k,j,i)
     1478                      ENDDO
     1479                   ENDDO
     1480                ENDDO
     1481             ELSEIF ( intermediate_timestep_count < &
     1482                      intermediate_timestep_count_max )  THEN
     1483                DO  i = nxl, nxr
     1484                   DO  j = nys, nyn
     1485                      DO  k = nzb_s_inner(j,i)+1, nzt
     1486                         tqr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * &
     1487                                                                   tqr_m(k,j,i)
     1488                      ENDDO
     1489                   ENDDO
     1490                ENDDO
     1491             ENDIF
     1492          ENDIF
     1493
     1494          CALL cpu_log( log_point(52), 'qr-equation', 'stop' )
     1495          CALL cpu_log( log_point(53), 'nr-equation', 'start' )
     1496
     1497!
     1498!--       Calculate prognostic equation for rain drop concentration
     1499          sbt = tsc(2)
     1500          IF ( scalar_advec == 'bc-scheme' )  THEN
     1501
     1502             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     1503!
     1504!--             Bott-Chlond scheme always uses Euler time step. Thus:
     1505                sbt = 1.0_wp
     1506             ENDIF
     1507             tend = 0.0_wp
     1508             CALL advec_s_bc( nr, 'nr' )
     1509
     1510          ENDIF
     1511
     1512!
     1513!--       nr-tendency terms with no communication
     1514          IF ( scalar_advec /= 'bc-scheme' )  THEN
     1515             tend = 0.0_wp
     1516             IF ( timestep_scheme(1:5) == 'runge' )  THEN
     1517                IF ( ws_scheme_sca )  THEN
     1518                   CALL advec_s_ws( nr, 'nr' )
     1519                ELSE
     1520                   CALL advec_s_pw( nr )
     1521                ENDIF
     1522             ELSE
     1523                CALL advec_s_up( nr )
     1524             ENDIF
     1525          ENDIF
     1526
     1527          CALL diffusion_s( nr, nrsws, nrswst, wall_nrflux )
     1528
     1529          CALL user_actions( 'nr-tendency' )
     1530
     1531!
     1532!--       Prognostic equation for rain drop concentration
     1533          DO  i = nxl, nxr
     1534             DO  j = nys, nyn
     1535                DO  k = nzb_s_inner(j,i)+1, nzt
     1536                   nr_p(k,j,i) = nr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
     1537                                                     tsc(3) * tnr_m(k,j,i) )   &
     1538                                           - tsc(5) * rdf_sc(k) * nr(k,j,i)
     1539                   IF ( nr_p(k,j,i) < 0.0_wp )  nr_p(k,j,i) = 0.0_wp
     1540                ENDDO
     1541             ENDDO
     1542          ENDDO
     1543
     1544!
     1545!--       Calculate tendencies for the next Runge-Kutta step
     1546          IF ( timestep_scheme(1:5) == 'runge' )  THEN
     1547             IF ( intermediate_timestep_count == 1 )  THEN
     1548                DO  i = nxl, nxr
     1549                   DO  j = nys, nyn
     1550                      DO  k = nzb_s_inner(j,i)+1, nzt
     1551                         tnr_m(k,j,i) = tend(k,j,i)
     1552                      ENDDO
     1553                   ENDDO
     1554                ENDDO
     1555             ELSEIF ( intermediate_timestep_count < &
     1556                      intermediate_timestep_count_max )  THEN
     1557                DO  i = nxl, nxr
     1558                   DO  j = nys, nyn
     1559                      DO  k = nzb_s_inner(j,i)+1, nzt
     1560                         tnr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * &
     1561                                                                   tnr_m(k,j,i)
     1562                      ENDDO
     1563                   ENDDO
     1564                ENDDO
     1565             ENDIF
     1566          ENDIF
     1567
     1568          CALL cpu_log( log_point(53), 'nr-equation', 'stop' )
     1569
     1570       ENDIF
    14081571
    14091572    ENDIF
     
    15101673    ENDIF
    15111674
    1512 
    15131675 END SUBROUTINE prognostic_equations_vector
    15141676
     
    15391701          runge_step = 2
    15401702       ENDIF
     1703    ENDIF
     1704
     1705!
     1706!-- If required, calculate cloud microphysical impacts (two-moment scheme)
     1707    IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                       &
     1708         ( intermediate_timestep_count == 1  .OR.                              &
     1709           call_microphysics_at_all_substeps )                                 &
     1710       )  THEN
     1711       CALL cpu_log( log_point(51), 'microphysics', 'start' )
     1712       CALL microphysics_control
     1713       CALL cpu_log( log_point(51), 'microphysics', 'stop' )
    15411714    ENDIF
    15421715
     
    17911964!
    17921965!--    If required compute impact of latent heat due to precipitation
    1793        IF ( precipitation )  THEN
     1966       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
    17941967          CALL impact_of_latent_heat
    17951968       ENDIF
     
    19572130!--    If required compute decrease of total water content due to
    19582131!--    precipitation
    1959        IF ( precipitation )  THEN
     2132       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
    19602133          CALL calc_precipitation
    19612134       ENDIF
     
    19992172
    20002173       CALL cpu_log( log_point(29), 'q/s-equation', 'stop' )
     2174
     2175!
     2176!--    If required, calculate prognostic equations for rain water content
     2177!--    and rain drop concentration
     2178       IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  precipitation )  THEN
     2179
     2180          CALL cpu_log( log_point(52), 'qr-equation', 'start' )
     2181!
     2182!--       qr-tendency terms with communication
     2183          sbt = tsc(2)
     2184          IF ( scalar_advec == 'bc-scheme' )  THEN
     2185
     2186             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     2187!
     2188!--             Bott-Chlond scheme always uses Euler time step. Thus:
     2189                sbt = 1.0_wp
     2190             ENDIF
     2191             tend = 0.0_wp
     2192             CALL advec_s_bc( qr, 'qr' )
     2193
     2194          ENDIF
     2195
     2196!
     2197!--       qr-tendency terms with no communication
     2198          IF ( scalar_advec /= 'bc-scheme' )  THEN
     2199             tend = 0.0_wp
     2200             IF ( timestep_scheme(1:5) == 'runge' )  THEN
     2201                IF ( ws_scheme_sca )  THEN
     2202                   CALL advec_s_ws( qr, 'qr' )
     2203                ELSE
     2204                   CALL advec_s_pw( qr )
     2205                ENDIF
     2206             ELSE
     2207                CALL advec_s_up( qr )
     2208             ENDIF
     2209          ENDIF
     2210
     2211          CALL diffusion_s( qr, qrsws, qrswst, wall_qrflux )
     2212
     2213          CALL user_actions( 'qr-tendency' )
     2214
     2215!
     2216!--       Prognostic equation for rain water content
     2217          DO  i = i_left, i_right
     2218             DO  j = j_south, j_north
     2219                DO  k = nzb_s_inner(j,i)+1, nzt
     2220                   qr_p(k,j,i) = qr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
     2221                                                       tsc(3) * tqr_m(k,j,i) ) &
     2222                                           - tsc(5) * rdf_sc(k) * qr(k,j,i)
     2223                   IF ( qr_p(k,j,i) < 0.0_wp )  qr_p(k,j,i) = 0.0_wp
     2224!
     2225!--                Tendencies for the next Runge-Kutta step
     2226                   IF ( runge_step == 1 )  THEN
     2227                      tqr_m(k,j,i) = tend(k,j,i)
     2228                   ELSEIF ( runge_step == 2 )  THEN
     2229                      tqr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp *    &
     2230                                                                tqr_m(k,j,i)
     2231                   ENDIF
     2232                ENDDO
     2233             ENDDO
     2234          ENDDO
     2235
     2236          CALL cpu_log( log_point(52), 'qr-equation', 'stop' )
     2237          CALL cpu_log( log_point(53), 'nr-equation', 'start' )
     2238
     2239!
     2240!--       nr-tendency terms with communication
     2241          sbt = tsc(2)
     2242          IF ( scalar_advec == 'bc-scheme' )  THEN
     2243
     2244             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
     2245!
     2246!--             Bott-Chlond scheme always uses Euler time step. Thus:
     2247                sbt = 1.0_wp
     2248             ENDIF
     2249             tend = 0.0_wp
     2250             CALL advec_s_bc( nr, 'nr' )
     2251
     2252          ENDIF
     2253
     2254!
     2255!--       nr-tendency terms with no communication
     2256          IF ( scalar_advec /= 'bc-scheme' )  THEN
     2257             tend = 0.0_wp
     2258             IF ( timestep_scheme(1:5) == 'runge' )  THEN
     2259                IF ( ws_scheme_sca )  THEN
     2260                   CALL advec_s_ws( nr, 'nr' )
     2261                ELSE
     2262                   CALL advec_s_pw( nr )
     2263                ENDIF
     2264             ELSE
     2265                CALL advec_s_up( nr )
     2266             ENDIF
     2267          ENDIF
     2268
     2269          CALL diffusion_s( nr, nrsws, nrswst, wall_nrflux )
     2270
     2271          CALL user_actions( 'nr-tendency' )
     2272
     2273!
     2274!--       Prognostic equation for rain drop concentration
     2275          DO  i = i_left, i_right
     2276             DO  j = j_south, j_north
     2277                DO  k = nzb_s_inner(j,i)+1, nzt
     2278                   nr_p(k,j,i) = nr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
     2279                                                       tsc(3) * tnr_m(k,j,i) ) &
     2280                                           - tsc(5) * rdf_sc(k) * nr(k,j,i)
     2281                   IF ( nr_p(k,j,i) < 0.0_wp )  nr_p(k,j,i) = 0.0_wp
     2282!
     2283!--                Tendencies for the next Runge-Kutta step
     2284                   IF ( runge_step == 1 )  THEN
     2285                      tnr_m(k,j,i) = tend(k,j,i)
     2286                   ELSEIF ( runge_step == 2 )  THEN
     2287                      tnr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp *    &
     2288                                                                tnr_m(k,j,i)
     2289                   ENDIF
     2290                ENDDO
     2291             ENDDO
     2292          ENDDO
     2293
     2294          CALL cpu_log( log_point(53), 'nr-equation', 'stop' )
     2295
     2296       ENDIF
    20012297
    20022298    ENDIF
     
    20952391    ENDIF
    20962392
    2097 
    20982393 END SUBROUTINE prognostic_equations_acc
    20992394
Note: See TracChangeset for help on using the changeset viewer.