Ignore:
Timestamp:
Apr 5, 2019 9:01:56 AM (5 years ago)
Author:
monakurppa
Message:

major changes in salsa: data input, format and performance

  • Time-dependent emissions enabled: lod=1 for yearly PM emissions that are normalised depending on the time, and lod=2 for preprocessed emissions (similar to the chemistry module).
  • Additionally, 'uniform' emissions allowed. This emission is set constant on all horisontal upward facing surfaces and it is created based on parameters surface_aerosol_flux, aerosol_flux_dpg/sigmag/mass_fracs_a/mass_fracs_b.
  • All emissions are now implemented as surface fluxes! No 3D sources anymore.
  • Update the emission information by calling salsa_emission_update if skip_time_do_salsa >= time_since_reference_point and next_aero_emission_update <= time_since_reference_point
  • Aerosol background concentrations read from PIDS_DYNAMIC. The vertical grid must match the one applied in the model.
  • Gas emissions and background concentrations can be also read in in salsa_mod if the chemistry module is not applied.
  • In deposition, information on the land use type can be now imported from the land use model
  • Use SI units in PARIN, i.e. n_lognorm given in #/m3 and dpg in metres.
  • Apply 100 character line limit
  • Change all variable names from capital to lowercase letter
  • Change real exponents to integer if possible. If not, precalculate the value of exponent
  • Rename in1a to start_subrange_1a, fn2a to end_subrange_1a etc.
  • Rename nbins --> nbins_aerosol, ncc_tot --> ncomponents_mass and ngast --> ngases_salsa
  • Rename ibc to index_bc, idu to index_du etc.
  • Renamed loop indices b, c and sg to ib, ic and ig
  • run_salsa subroutine removed
  • Corrected a bud in salsa_driver: falsely applied ino instead of inh
  • Call salsa_tendency within salsa_prognostic_equations which is called in module_interface_mod instead of prognostic_equations_mod
  • Removed tailing white spaces and unused variables
  • Change error message to start by PA instead of SA
File:
1 edited

Legend:

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

    r3840 r3864  
    2525! -----------------
    2626! $Id$
     27! Modifications made for salsa:
     28! - salsa_prognostic_equations moved to salsa_mod (and the call to
     29!   module_interface_mod)
     30! - Renamed nbins --> nbins_aerosol, ncc_tot --> ncomponents_mass and
     31!   ngast --> ngases_salsa and loop indices b, c and sg to ib, ic and ig
     32!
     33! 3840 2019-03-29 10:35:52Z knoop
    2734! added USE chem_gasphase_mod for nvar, nspec and spc_names
    2835!
     
    376383    USE buoyancy_mod,                                                          &
    377384        ONLY:  buoyancy
    378            
     385
    379386    USE chem_modules,                                                          &
    380387        ONLY:  call_chem_at_all_substeps, chem_gasphase_on, cs_name,           &
     
    447454               skip_time_do_radiation
    448455#endif
    449                          
     456
    450457    USE salsa_mod,                                                             &
    451         ONLY:  aerosol_mass, aerosol_number, dt_salsa, last_salsa_time, nbins, &
    452                ncc_tot, ngast, salsa_boundary_conds, salsa_diagnostics,        &
    453                salsa_driver, salsa_gas, salsa_gases_from_chem, salsa_tendency, &
    454                skip_time_do_salsa
    455                
     458        ONLY:  aerosol_mass, aerosol_number, dt_salsa, last_salsa_time,       &
     459               nbins_aerosol, ncomponents_mass, ngases_salsa,                  &
     460               salsa_boundary_conds, salsa_diagnostics, salsa_driver,          &
     461               salsa_gas, salsa_gases_from_chem, skip_time_do_salsa
     462
    456463    USE salsa_util_mod,                                                        &
    457         ONLY:  sums_salsa_ws_l                             
    458    
     464        ONLY:  sums_salsa_ws_l
     465
    459466    USE statistics,                                                            &
    460467        ONLY:  hom
     
    506513
    507514    IMPLICIT NONE
    508    
    509     INTEGER(iwp) ::  b                   !< index for aerosol size bins (salsa)
    510     INTEGER(iwp) ::  c                   !< index for chemical compounds (salsa)
    511     INTEGER(iwp) ::  g                   !< index for gaseous compounds (salsa)
     515
    512516    INTEGER(iwp) ::  i                   !<
    513517    INTEGER(iwp) ::  i_omp_start         !<
     518    INTEGER(iwp) ::  ib                  !< index for aerosol size bins (salsa)
     519    INTEGER(iwp) ::  ic                  !< index for chemical compounds (salsa)
     520    INTEGER(iwp) ::  icc                 !< additional index for chemical compounds (salsa)
     521    INTEGER(iwp) ::  ig                  !< index for gaseous compounds (salsa)
    514522    INTEGER(iwp) ::  j                   !<
    515523    INTEGER(iwp) ::  k                   !<
     
    587595       CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
    588596
    589     ENDIF       
     597    ENDIF
    590598!
    591599!-- Run SALSA and aerosol dynamic processes. SALSA is run with a longer time
     
    593601!-- concentrations of aerosol number and mass
    594602    IF ( salsa )  THEN
    595        
    596        IF ( time_since_reference_point >= skip_time_do_salsa )  THEN                 
     603
     604       IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    597605          IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  &
    598606          THEN
    599607             CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
    600              !$OMP PARALLEL PRIVATE (i,j,b,c,g)
     608             !$OMP PARALLEL PRIVATE (i,j,ib,ic,icc,ig)
    601609             !$OMP DO
    602610!
     
    609617                ENDDO
    610618             ENDDO
    611              
     619
    612620             CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
    613621             
     
    615623!
    616624!--          Exchange ghost points and decycle if needed.
    617              DO  b = 1, nbins
    618                 CALL exchange_horiz( aerosol_number(b)%conc, nbgp )
    619                 CALL salsa_boundary_conds( aerosol_number(b)%conc_p,           &
    620                                            aerosol_number(b)%init )
    621                 DO  c = 1, ncc_tot
    622                    CALL exchange_horiz( aerosol_mass((c-1)*nbins+b)%conc, nbgp )
    623                    CALL salsa_boundary_conds(                                  &
    624                                            aerosol_mass((c-1)*nbins+b)%conc_p, &
    625                                            aerosol_mass((c-1)*nbins+b)%init )
    626                 ENDDO
    627              ENDDO
    628              
     625             DO  ib = 1, nbins_aerosol
     626                CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
     627                CALL salsa_boundary_conds( aerosol_number(ib)%conc,            &
     628                                           aerosol_number(ib)%init )
     629                DO  ic = 1, ncomponents_mass
     630                   icc = ( ic - 1 ) * nbins_aerosol + ib
     631                   CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
     632                   CALL salsa_boundary_conds( aerosol_mass(icc)%conc,          &
     633                                              aerosol_mass(icc)%init )
     634                ENDDO
     635             ENDDO
     636
    629637             IF ( .NOT. salsa_gases_from_chem )  THEN
    630                 DO  g = 1, ngast
    631                    CALL exchange_horiz( salsa_gas(g)%conc, nbgp )
    632                    CALL salsa_boundary_conds( salsa_gas(g)%conc_p,             &
    633                                               salsa_gas(g)%init )
     638                DO  ig = 1, ngases_salsa
     639                   CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
     640                   CALL salsa_boundary_conds( salsa_gas(ig)%conc,              &
     641                                              salsa_gas(ig)%init )
    634642                ENDDO
    635643             ENDIF
     
    638646             !$OMP END PARALLEL
    639647             last_salsa_time = time_since_reference_point
    640              
    641           ENDIF
    642          
    643        ENDIF
    644        
     648
     649          ENDIF
     650
     651       ENDIF
     652
    645653    ENDIF
    646654
     
    14421450                                     chem_species(lsp)%diss_l_cs )       
    14431451             ENDDO
    1444          
     1452
    14451453          ENDIF   ! Chemical equations
    1446        
    1447           IF ( salsa )  THEN
    1448 !
    1449 !--          Loop over aerosol size bins: number and mass bins
    1450              IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    1451              
    1452                 DO  b = 1, nbins               
    1453                    sums_salsa_ws_l = aerosol_number(b)%sums_ws_l
    1454                    CALL salsa_tendency( 'aerosol_number',                      &
    1455                                          aerosol_number(b)%conc_p,             &
    1456                                          aerosol_number(b)%conc,               &
    1457                                          aerosol_number(b)%tconc_m,            &
    1458                                          i, j, i_omp_start, tn, b, b,          &
    1459                                          aerosol_number(b)%flux_s,             &
    1460                                          aerosol_number(b)%diss_s,             &
    1461                                          aerosol_number(b)%flux_l,             &
    1462                                          aerosol_number(b)%diss_l,             &
    1463                                          aerosol_number(b)%init )
    1464                    aerosol_number(b)%sums_ws_l = sums_salsa_ws_l
    1465                    DO  c = 1, ncc_tot
    1466                       sums_salsa_ws_l = aerosol_mass((c-1)*nbins+b)%sums_ws_l
    1467                       CALL salsa_tendency( 'aerosol_mass',                     &
    1468                                             aerosol_mass((c-1)*nbins+b)%conc_p,&
    1469                                             aerosol_mass((c-1)*nbins+b)%conc,  &
    1470                                             aerosol_mass((c-1)*nbins+b)%tconc_m,&
    1471                                             i, j, i_omp_start, tn, b, c,       &
    1472                                             aerosol_mass((c-1)*nbins+b)%flux_s,&
    1473                                             aerosol_mass((c-1)*nbins+b)%diss_s,&
    1474                                             aerosol_mass((c-1)*nbins+b)%flux_l,&
    1475                                             aerosol_mass((c-1)*nbins+b)%diss_l,&
    1476                                             aerosol_mass((c-1)*nbins+b)%init )
    1477                       aerosol_mass((c-1)*nbins+b)%sums_ws_l = sums_salsa_ws_l
    1478                    ENDDO
    1479                 ENDDO
    1480                 IF ( .NOT. salsa_gases_from_chem )  THEN
    1481                    DO  g = 1, ngast
    1482                       sums_salsa_ws_l = salsa_gas(g)%sums_ws_l
    1483                       CALL salsa_tendency( 'salsa_gas', salsa_gas(g)%conc_p,   &
    1484                                       salsa_gas(g)%conc, salsa_gas(g)%tconc_m, &
    1485                                       i, j, i_omp_start, tn, g, g,             &
    1486                                       salsa_gas(g)%flux_s, salsa_gas(g)%diss_s,&
    1487                                       salsa_gas(g)%flux_l, salsa_gas(g)%diss_l,&
    1488                                       salsa_gas(g)%init )
    1489                       salsa_gas(g)%sums_ws_l = sums_salsa_ws_l
    1490                    ENDDO
    1491                 ENDIF
    1492              
    1493              ENDIF
    1494              
    1495           ENDIF       
    14961454
    14971455       ENDDO  ! loop over j
     
    15171475    IMPLICIT NONE
    15181476
    1519     INTEGER(iwp) ::  b     !< index for aerosol size bins (salsa)
    1520     INTEGER(iwp) ::  c     !< index for chemical compounds (salsa)
    1521     INTEGER(iwp) ::  g     !< index for gaseous compounds (salsa)
    15221477    INTEGER(iwp) ::  i     !<
     1478    INTEGER(iwp) ::  ib    !< index for aerosol size bins (salsa)
     1479    INTEGER(iwp) ::  ic    !< index for chemical compounds (salsa)
     1480    INTEGER(iwp) ::  icc   !< additional index for chemical compounds (salsa)
     1481    INTEGER(iwp) ::  ig    !< index for gaseous compounds (salsa)
    15231482    INTEGER(iwp) ::  j     !<
    15241483    INTEGER(iwp) ::  k     !<
     
    15321491!-- concentrations of aerosol number and mass
    15331492    IF ( salsa )  THEN
    1534        
    15351493       IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    1536        
    15371494          IF ( ( time_since_reference_point - last_salsa_time ) >= dt_salsa )  &
    15381495          THEN
    1539          
    15401496             CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
    1541              !$OMP PARALLEL PRIVATE (i,j,b,c,g)
     1497             !$OMP PARALLEL PRIVATE (i,j,ib,ic,icc,ig)
    15421498             !$OMP DO
    15431499!
     
    15501506                ENDDO
    15511507             ENDDO
    1552              
     1508
    15531509             CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
    1554              
    15551510             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
    15561511!
    15571512!--          Exchange ghost points and decycle if needed.
    1558              DO  b = 1, nbins
    1559                 CALL exchange_horiz( aerosol_number(b)%conc, nbgp )
    1560                 CALL salsa_boundary_conds( aerosol_number(b)%conc_p,           &
    1561                                            aerosol_number(b)%init )
    1562                 DO  c = 1, ncc_tot
    1563                    CALL exchange_horiz( aerosol_mass((c-1)*nbins+b)%conc, nbgp )
    1564                    CALL salsa_boundary_conds(                                  &
    1565                                            aerosol_mass((c-1)*nbins+b)%conc_p, &
    1566                                            aerosol_mass((c-1)*nbins+b)%init )
    1567                 ENDDO
    1568              ENDDO
    1569              
     1513             DO  ib = 1, nbins_aerosol
     1514                CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
     1515                CALL salsa_boundary_conds( aerosol_number(ib)%conc,            &
     1516                                           aerosol_number(ib)%init )
     1517                DO  ic = 1, ncomponents_mass
     1518                   icc = ( ic - 1 ) * nbins_aerosol + ib
     1519                   CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
     1520                   CALL salsa_boundary_conds( aerosol_mass(icc)%conc,          &
     1521                                              aerosol_mass(icc)%init )
     1522                ENDDO
     1523             ENDDO
    15701524             IF ( .NOT. salsa_gases_from_chem )  THEN
    1571                 DO  g = 1, ngast
    1572                    CALL exchange_horiz( salsa_gas(g)%conc, nbgp )
    1573                    CALL salsa_boundary_conds( salsa_gas(g)%conc_p,             &
    1574                                               salsa_gas(g)%init )
     1525                DO  ig = 1, ngases_salsa
     1526                   CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
     1527                   CALL salsa_boundary_conds( salsa_gas(ig)%conc,              &
     1528                                              salsa_gas(ig)%init )
    15751529                ENDDO
    15761530             ENDIF
    15771531             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
    1578              
    15791532             !$OMP END PARALLEL
    15801533             last_salsa_time = time_since_reference_point
    1581              
    1582           ENDIF
    1583          
    1584        ENDIF
    1585        
     1534          ENDIF
     1535       ENDIF
    15861536    ENDIF
    15871537
     
    26612611       CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'stop' )             
    26622612    ENDIF   ! Chemicals equations
    2663        
    2664     IF ( salsa )  THEN
    2665        CALL cpu_log( log_point_s(92), 'salsa advec+diff+prog ', 'start' )
    2666 !
    2667 !--          Loop over aerosol size bins: number and mass bins
    2668        IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    2669        
    2670           DO  b = 1, nbins               
    2671              sums_salsa_ws_l = aerosol_number(b)%sums_ws_l
    2672              CALL salsa_tendency( 'aerosol_number', aerosol_number(b)%conc_p,  &
    2673                                    aerosol_number(b)%conc,                     &
    2674                                    aerosol_number(b)%tconc_m,                  &
    2675                                    b, b, aerosol_number(b)%init )
    2676              aerosol_number(b)%sums_ws_l = sums_salsa_ws_l
    2677              DO  c = 1, ncc_tot
    2678                 sums_salsa_ws_l = aerosol_mass((c-1)*nbins+b)%sums_ws_l
    2679                 CALL salsa_tendency( 'aerosol_mass',                           &
    2680                                       aerosol_mass((c-1)*nbins+b)%conc_p,      &
    2681                                       aerosol_mass((c-1)*nbins+b)%conc,        &
    2682                                       aerosol_mass((c-1)*nbins+b)%tconc_m,     &
    2683                                       b, c, aerosol_mass((c-1)*nbins+b)%init )
    2684                 aerosol_mass((c-1)*nbins+b)%sums_ws_l = sums_salsa_ws_l
    2685              ENDDO
    2686           ENDDO
    2687           IF ( .NOT. salsa_gases_from_chem )  THEN
    2688              DO  g = 1, ngast
    2689                 sums_salsa_ws_l = salsa_gas(g)%sums_ws_l
    2690                 CALL salsa_tendency( 'salsa_gas', salsa_gas(g)%conc_p,         &
    2691                                       salsa_gas(g)%conc, salsa_gas(g)%tconc_m, &
    2692                                       g, g, salsa_gas(g)%init )
    2693                 salsa_gas(g)%sums_ws_l = sums_salsa_ws_l
    2694              ENDDO
    2695           ENDIF
    2696        
    2697        ENDIF
    2698        
    2699        CALL cpu_log( log_point_s(92), 'salsa advec+diff+prog ', 'stop' )
    2700     ENDIF
    2701 
    27022613
    27032614 END SUBROUTINE prognostic_equations_vector
Note: See TracChangeset for help on using the changeset viewer.