Ignore:
Timestamp:
Oct 30, 2018 7:05:21 PM (5 years ago)
Author:
suehring
Message:

Branch salsa @3446 re-integrated into trunk

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/prognostic_equations.f90

    r3458 r3467  
    2525! -----------------
    2626! $Id$
     27! Implementation of a new aerosol module salsa.
     28! Remove cpu-logs from i,j loop in cache version.
     29!
     30! 3458 2018-10-30 14:51:23Z kanani
    2731! remove duplicate USE chem_modules
    2832! from chemistry branch r3443, banzhafs, basit:
     
    368372               timestep_scheme, tsc, use_subsidence_tendencies,                &
    369373               use_upstream_for_tke, wind_turbine, ws_scheme_mom,              &
    370                ws_scheme_sca, urban_surface, land_surface
     374               ws_scheme_sca, urban_surface, land_surface,                     &
     375               time_since_reference_point
    371376
    372377    USE coriolis_mod,                                                          &
     
    407412        ONLY:  radiation, radiation_tendency,                                  &
    408413               skip_time_do_radiation
    409 
     414                         
     415    USE salsa_mod,                                                             &
     416        ONLY:  aerosol_mass, aerosol_number, dt_salsa, last_salsa_time, nbins, &
     417               ncc_tot, ngast, salsa, salsa_boundary_conds, salsa_diagnostics, &
     418               salsa_driver, salsa_gas, salsa_gases_from_chem, salsa_tendency, &
     419               skip_time_do_salsa
     420               
     421    USE salsa_util_mod,                                                        &
     422        ONLY:  sums_salsa_ws_l                             
     423   
    410424    USE statistics,                                                            &
    411425        ONLY:  hom
     
    460474
    461475    IMPLICIT NONE
    462 
     476   
     477    INTEGER(iwp) ::  b                   !< index for aerosol size bins (salsa)
     478    INTEGER(iwp) ::  c                   !< index for chemical compounds (salsa)
     479    INTEGER(iwp) ::  g                   !< index for gaseous compounds (salsa)
    463480    INTEGER(iwp) ::  i                   !<
    464481    INTEGER(iwp) ::  i_omp_start         !<
     
    523540             lsp_usr = lsp_usr +1
    524541          ENDDO
    525          
     542
     543
    526544       ENDDO
    527545       CALL cpu_log( log_point_s(84), 'chemistry exch-horiz ', 'stop' )
     
    530548
    531549    ENDIF       
     550
     551!
     552!-- Run SALSA and aerosol dynamic processes. SALSA is run with a longer time
     553!-- step. The exchange of ghost points is required after this update of the
     554!-- concentrations of aerosol number and mass
     555    IF ( salsa )  THEN
     556       
     557       IF ( time_since_reference_point >= skip_time_do_salsa )  THEN                 
     558          IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  &
     559          THEN
     560             CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
     561             !$OMP PARALLEL PRIVATE (i,j,b,c,g)
     562             !$OMP DO
     563!
     564!--          Call salsa processes
     565             DO  i = nxl, nxr
     566                DO  j = nys, nyn
     567                   CALL salsa_diagnostics( i, j )
     568                   CALL salsa_driver( i, j, 3 )
     569                   CALL salsa_diagnostics( i, j )
     570                ENDDO
     571             ENDDO
     572             
     573             CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
     574             
     575             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
     576!
     577!--          Exchange ghost points and decycle if needed.
     578             DO  b = 1, nbins
     579                CALL exchange_horiz( aerosol_number(b)%conc, nbgp )
     580                CALL salsa_boundary_conds( aerosol_number(b)%conc_p,           &
     581                                           aerosol_number(b)%init )
     582                DO  c = 1, ncc_tot
     583                   CALL exchange_horiz( aerosol_mass((c-1)*nbins+b)%conc, nbgp )
     584                   CALL salsa_boundary_conds(                                  &
     585                                           aerosol_mass((c-1)*nbins+b)%conc_p, &
     586                                           aerosol_mass((c-1)*nbins+b)%init )
     587                ENDDO
     588             ENDDO
     589             
     590             IF ( .NOT. salsa_gases_from_chem )  THEN
     591                DO  g = 1, ngast
     592                   CALL exchange_horiz( salsa_gas(g)%conc, nbgp )
     593                   CALL salsa_boundary_conds( salsa_gas(g)%conc_p,             &
     594                                              salsa_gas(g)%init )
     595                ENDDO
     596             ENDIF
     597             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
     598             
     599             !$OMP END PARALLEL
     600             last_salsa_time = time_since_reference_point
     601             
     602          ENDIF
     603         
     604       ENDIF
     605       
     606    ENDIF
    532607
    533608!
     
    549624!
    550625!-- Loop over all prognostic equations
    551     !$OMP PARALLEL PRIVATE (i,i_omp_start,j,k,loop_start,tn)
     626!-- b, c ang g added for SALSA
     627    !$OMP PARALLEL PRIVATE (i,i_omp_start,j,k,loop_start,tn,b,c,g)
    552628
    553629    !$  tn = omp_get_thread_num()
     
    13101386          IF ( air_chemistry )  THEN
    13111387             !> TODO: remove time measurement since it slows down performance because it will be called extremely often
    1312              CALL cpu_log( log_point(83), '(chem advec+diff+prog)', 'start' )
    13131388!
    13141389!--          Loop over chemical species
     
    13241399                                     chem_species(lsp)%diss_l_cs )       
    13251400             ENDDO
    1326 
    1327              CALL cpu_log( log_point(83), '(chem advec+diff+prog)', 'stop' )             
     1401         
    13281402          ENDIF   ! Chemical equations
    13291403!
     
    13321406             CALL ocean_prognostic_equations( i, j, i_omp_start, tn )
    13331407          ENDIF
     1408       
     1409          IF ( salsa )  THEN
     1410!
     1411!--          Loop over aerosol size bins: number and mass bins
     1412             IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     1413             
     1414                DO  b = 1, nbins               
     1415                   sums_salsa_ws_l = aerosol_number(b)%sums_ws_l
     1416                   CALL salsa_tendency( 'aerosol_number',                      &
     1417                                         aerosol_number(b)%conc_p,             &
     1418                                         aerosol_number(b)%conc,               &
     1419                                         aerosol_number(b)%tconc_m,            &
     1420                                         i, j, i_omp_start, tn, b, b,          &
     1421                                         aerosol_number(b)%flux_s,             &
     1422                                         aerosol_number(b)%diss_s,             &
     1423                                         aerosol_number(b)%flux_l,             &
     1424                                         aerosol_number(b)%diss_l,             &
     1425                                         aerosol_number(b)%init )
     1426                   aerosol_number(b)%sums_ws_l = sums_salsa_ws_l
     1427                   DO  c = 1, ncc_tot
     1428                      sums_salsa_ws_l = aerosol_mass((c-1)*nbins+b)%sums_ws_l
     1429                      CALL salsa_tendency( 'aerosol_mass',                     &
     1430                                            aerosol_mass((c-1)*nbins+b)%conc_p,&
     1431                                            aerosol_mass((c-1)*nbins+b)%conc,  &
     1432                                            aerosol_mass((c-1)*nbins+b)%tconc_m,&
     1433                                            i, j, i_omp_start, tn, b, c,       &
     1434                                            aerosol_mass((c-1)*nbins+b)%flux_s,&
     1435                                            aerosol_mass((c-1)*nbins+b)%diss_s,&
     1436                                            aerosol_mass((c-1)*nbins+b)%flux_l,&
     1437                                            aerosol_mass((c-1)*nbins+b)%diss_l,&
     1438                                            aerosol_mass((c-1)*nbins+b)%init )
     1439                      aerosol_mass((c-1)*nbins+b)%sums_ws_l = sums_salsa_ws_l
     1440                   ENDDO
     1441                ENDDO
     1442                IF ( .NOT. salsa_gases_from_chem )  THEN
     1443                   DO  g = 1, ngast
     1444                      sums_salsa_ws_l = salsa_gas(g)%sums_ws_l
     1445                      CALL salsa_tendency( 'salsa_gas', salsa_gas(g)%conc_p,   &
     1446                                      salsa_gas(g)%conc, salsa_gas(g)%tconc_m, &
     1447                                      i, j, i_omp_start, tn, g, g,             &
     1448                                      salsa_gas(g)%flux_s, salsa_gas(g)%diss_s,&
     1449                                      salsa_gas(g)%flux_l, salsa_gas(g)%diss_l,&
     1450                                      salsa_gas(g)%init )
     1451                      salsa_gas(g)%sums_ws_l = sums_salsa_ws_l
     1452                   ENDDO
     1453                ENDIF
     1454             
     1455             ENDIF
     1456             
     1457          ENDIF       
    13341458
    13351459       ENDDO  ! loop over j
     
    13551479    IMPLICIT NONE
    13561480
     1481    INTEGER(iwp) ::  b     !< index for aerosol size bins (salsa)
     1482    INTEGER(iwp) ::  c     !< index for chemical compounds (salsa)
     1483    INTEGER(iwp) ::  g     !< index for gaseous compounds (salsa)
    13571484    INTEGER(iwp) ::  i     !<
    13581485    INTEGER(iwp) ::  j     !<
     
    13621489    REAL(wp)     ::  sbt  !<
    13631490
     1491!
     1492!-- Run SALSA and aerosol dynamic processes. SALSA is run with a longer time
     1493!-- step. The exchange of ghost points is required after this update of the
     1494!-- concentrations of aerosol number and mass
     1495    IF ( salsa )  THEN
     1496       
     1497       IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     1498       
     1499          IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  &
     1500          THEN
     1501         
     1502             CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
     1503             !$OMP PARALLEL PRIVATE (i,j,b,c,g)
     1504             !$OMP DO
     1505!
     1506!--          Call salsa processes
     1507             DO  i = nxl, nxr
     1508                DO  j = nys, nyn
     1509                   CALL salsa_diagnostics( i, j )
     1510                   CALL salsa_driver( i, j, 3 )
     1511                   CALL salsa_diagnostics( i, j )
     1512                ENDDO
     1513             ENDDO
     1514             
     1515             CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
     1516             
     1517             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
     1518!
     1519!--          Exchange ghost points and decycle if needed.
     1520             DO  b = 1, nbins
     1521                CALL exchange_horiz( aerosol_number(b)%conc, nbgp )
     1522                CALL salsa_boundary_conds( aerosol_number(b)%conc_p,           &
     1523                                           aerosol_number(b)%init )
     1524                DO  c = 1, ncc_tot
     1525                   CALL exchange_horiz( aerosol_mass((c-1)*nbins+b)%conc, nbgp )
     1526                   CALL salsa_boundary_conds(                                  &
     1527                                           aerosol_mass((c-1)*nbins+b)%conc_p, &
     1528                                           aerosol_mass((c-1)*nbins+b)%init )
     1529                ENDDO
     1530             ENDDO
     1531             
     1532             IF ( .NOT. salsa_gases_from_chem )  THEN
     1533                DO  g = 1, ngast
     1534                   CALL exchange_horiz( salsa_gas(g)%conc, nbgp )
     1535                   CALL salsa_boundary_conds( salsa_gas(g)%conc_p,             &
     1536                                              salsa_gas(g)%init )
     1537                ENDDO
     1538             ENDIF
     1539             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
     1540             
     1541             !$OMP END PARALLEL
     1542             last_salsa_time = time_since_reference_point
     1543             
     1544          ENDIF
     1545         
     1546       ENDIF
     1547       
     1548    ENDIF
    13641549
    13651550!
     
    23922577       CALL cpu_log( log_point(83), '(chem advec+diff+prog)', 'stop' )             
    23932578    ENDIF   ! Chemicals equations
     2579       
     2580    IF ( salsa )  THEN
     2581       CALL cpu_log( log_point_s(92), 'salsa advec+diff+prog ', 'start' )
     2582!
     2583!--          Loop over aerosol size bins: number and mass bins
     2584       IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     2585       
     2586          DO  b = 1, nbins               
     2587             sums_salsa_ws_l = aerosol_number(b)%sums_ws_l
     2588             CALL salsa_tendency( 'aerosol_number', aerosol_number(b)%conc_p,  &
     2589                                   aerosol_number(b)%conc,                     &
     2590                                   aerosol_number(b)%tconc_m,                  &
     2591                                   b, b, aerosol_number(b)%init )
     2592             aerosol_number(b)%sums_ws_l = sums_salsa_ws_l
     2593             DO  c = 1, ncc_tot
     2594                sums_salsa_ws_l = aerosol_mass((c-1)*nbins+b)%sums_ws_l
     2595                CALL salsa_tendency( 'aerosol_mass',                           &
     2596                                      aerosol_mass((c-1)*nbins+b)%conc_p,      &
     2597                                      aerosol_mass((c-1)*nbins+b)%conc,        &
     2598                                      aerosol_mass((c-1)*nbins+b)%tconc_m,     &
     2599                                      b, c, aerosol_mass((c-1)*nbins+b)%init )
     2600                aerosol_mass((c-1)*nbins+b)%sums_ws_l = sums_salsa_ws_l
     2601             ENDDO
     2602          ENDDO
     2603          IF ( .NOT. salsa_gases_from_chem )  THEN
     2604             DO  g = 1, ngast
     2605                sums_salsa_ws_l = salsa_gas(g)%sums_ws_l
     2606                CALL salsa_tendency( 'salsa_gas', salsa_gas(g)%conc_p,         &
     2607                                      salsa_gas(g)%conc, salsa_gas(g)%tconc_m, &
     2608                                      g, g, salsa_gas(g)%init )
     2609                salsa_gas(g)%sums_ws_l = sums_salsa_ws_l
     2610             ENDDO
     2611          ENDIF
     2612       
     2613       ENDIF
     2614       
     2615       CALL cpu_log( log_point_s(92), 'salsa advec+diff+prog ', 'stop' )
     2616    ENDIF 
    23942617
    23952618!
Note: See TracChangeset for help on using the changeset viewer.