Changeset 3899


Ignore:
Timestamp:
Apr 16, 2019 2:05:27 PM (5 years ago)
Author:
monakurppa
Message:

corrected the OpenMP implementation for salsa and some minor bugs in salsa_mod

Location:
palm/trunk
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/EXAMPLES/test_salsa/test_salsa_p3d

    r3864 r3899  
    143143!
    144144!-- Concentration initial types: 0 = based on the parameter file, 1 = read from a NetCDF file
    145     isdtyp    = 1, ! size distribution
    146     igctyp    = 1, ! gases
    147 
    148 !
    149 !-- If isdtyp = 0, define the initial aerosol size distribution by dpg, sigmag and n_lognorm
     145    init_aerosol_type  = 1, ! size distribution
     146    init_gases_type    = 1, ! gases
     147
     148!
     149!-- If init_aerosol_type = 0, define the initial aerosol size distribution by dpg, sigmag and n_lognorm
    150150 !   dpg       = 13.5E-9, 54.0E-9, 864.1E-9, ! mean diameter per mode (in metres)
    151151 !   sigmag    =     1.8,    2.16,     2.21, ! standard deviation per mode
     
    153153
    154154!
    155 !-- If igctyp = 0, apply these initial gas concentrations                       
     155!-- If init_gases_type = 0, apply these initial gas concentrations                     
    156156 !   H2SO4_init = 5.0E12, ! sulphuric acid (#/m3)
    157157 !   HNO3_init  = 3.0E15, ! nitric acid (#/m3)
  • palm/trunk/SOURCE/prognostic_equations.f90

    r3887 r3899  
    2525! -----------------
    2626! $Id$
     27! Corrections in the OpenMP version of salsa
     28!
     29! 3887 2019-04-12 08:47:41Z schwenkel
    2730! Implicit Bugfix for chemistry model, loop for non_transport_physics over
    2831! ghost points is avoided. Instead introducing module_interface_exchange_horiz.
     
    562565          THEN
    563566             CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
    564              !$OMP PARALLEL PRIVATE (i,j,ib,ic,icc,ig)
     567             !$OMP PARALLEL PRIVATE (i,j)
     568!
     569!--          Call salsa processes
    565570             !$OMP DO
    566 !
    567 !--          Call salsa processes
    568571             DO  i = nxl, nxr
    569572                DO  j = nys, nyn
     
    573576                ENDDO
    574577             ENDDO
     578             !$OMP END PARALLEL
    575579
    576580             CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
    577              
     581
    578582             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
    579583!
     
    599603             ENDIF
    600604             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
    601              
    602              !$OMP END PARALLEL
    603605             last_salsa_time = time_since_reference_point
    604606
     
    631633!--       Tendency terms for u-velocity component. Please note, in case of
    632634!--       non-cyclic boundary conditions the grid point i=0 is excluded from
    633 !--       the prognostic equations for the u-component.   
     635!--       the prognostic equations for the u-component.
    634636          IF ( i >= nxlu )  THEN
    635637
     
    11751177          THEN
    11761178             CALL cpu_log( log_point_s(90), 'salsa processes ', 'start' )
    1177              !$OMP PARALLEL PRIVATE (i,j,ib,ic,icc,ig)
     1179             !$OMP PARALLEL PRIVATE (i,j)
    11781180             !$OMP DO
    11791181!
     
    11861188                ENDDO
    11871189             ENDDO
     1190             !$OMP END PARALLEL
    11881191
    11891192             CALL cpu_log( log_point_s(90), 'salsa processes ', 'stop' )
     
    12101213             ENDIF
    12111214             CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
    1212              !$OMP END PARALLEL
    12131215             last_salsa_time = time_since_reference_point
    12141216          ENDIF
  • palm/trunk/SOURCE/salsa_mod.f90

    r3885 r3899  
    2626! -----------------
    2727! $Id$
     28! 2018-04-11 monakurppa
     29! - remove unnecessary error / location messages
     30! - corrected some error message numbers
     31! - allocate source arrays only if emissions or dry deposition is applied.
     32! 3885 2019-04-11 11:29:34Z kanani
    2833! Changes related to global restructuring of location messages and introduction
    2934! of additional debug messages
     
    130135!> @todo Apply information from emission_stack_height to lift emission sources
    131136!> @todo emission mode "parameterized", i.e. based on street type
     137!> @todo Allow insoluble emissions
     138!> @todo two-way nesting is not working properly
    132139!------------------------------------------------------------------------------!
    133140 MODULE salsa_mod
     
    162169!
    163170!-- Local constants:
    164     INTEGER(iwp), PARAMETER ::  luc_urban = 8      !< default landuse type for urban: use desert!
     171    INTEGER(iwp), PARAMETER ::  luc_urban = 15     !< default landuse type for urban
    165172    INTEGER(iwp), PARAMETER ::  ngases_salsa   = 5 !< total number of gaseous tracers:
    166173                                                   !< 1 = H2SO4, 2 = HNO3, 3 = NH3, 4 = OCNV
     
    306313    INTEGER(iwp) ::  index_bc  = -1         !< index for black carbon (BC)
    307314    INTEGER(iwp) ::  index_du  = -1         !< index for dust
    308     INTEGER(iwp) ::  igctyp = 0             !< Initial gas concentration type
    309                                             !< 0 = uniform (read from PARIN)
    310                                             !< 1 = read vertical profile from an input file
    311315    INTEGER(iwp) ::  index_nh  = -1         !< index for NH3
    312316    INTEGER(iwp) ::  index_no  = -1         !< index for HNO3
    313317    INTEGER(iwp) ::  index_oc  = -1         !< index for organic carbon (OC)
    314     INTEGER(iwp) ::  isdtyp = 0             !< Initial size distribution type
     318    INTEGER(iwp) ::  index_so4 = -1         !< index for SO4 or H2SO4
     319    INTEGER(iwp) ::  index_ss  = -1         !< index for sea salt
     320    INTEGER(iwp) ::  init_aerosol_type = 0  !< Initial size distribution type
    315321                                            !< 0 = uniform (read from PARIN)
    316322                                            !< 1 = read vertical profile of the mode number
    317323                                            !<     concentration from an input file
    318     INTEGER(iwp) ::  index_so4 = -1         !< index for SO4 or H2SO4
    319     INTEGER(iwp) ::  index_ss  = -1         !< index for sea salt
     324    INTEGER(iwp) ::  init_gases_type = 0    !< Initial gas concentration type
     325                                            !< 0 = uniform (read from PARIN)
     326                                            !< 1 = read vertical profile from an input file
    320327    INTEGER(iwp) ::  lod_gas_emissions = 0  !< level of detail of the gaseous emission data
    321328    INTEGER(iwp) ::  nbins_aerosol = 1      !< total number of size bins
     
    357364    LOGICAL ::  decycle_lr            = .FALSE.    !< Undo cyclic boundary conditions: left and right
    358365    LOGICAL ::  decycle_ns            = .FALSE.    !< north and south boundaries
     366    LOGICAL ::  include_emission      = .FALSE.    !< include or not emissions
    359367    LOGICAL ::  feedback_to_palm      = .FALSE.    !< allow feedback due to condensation of H2O
    360368    LOGICAL ::  nest_salsa            = .FALSE.    !< apply nesting for salsa
     
    405413!-- standard deviation (sigmag) and concentration (n_lognorm, #/m3)
    406414    REAL(wp), DIMENSION(nmod) ::  dpg   = &
    407                                      (/0.013_wp, 0.054_wp, 0.86_wp, 0.2_wp, 0.2_wp, 0.2_wp, 0.2_wp/)
     415                     (/1.3E-8_wp, 5.4E-8_wp, 8.6E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp/)
    408416    REAL(wp), DIMENSION(nmod) ::  sigmag  = &
    409417                                        (/1.8_wp, 2.16_wp, 2.21_wp, 2.0_wp, 2.0_wp, 2.0_wp, 2.0_wp/)
     
    423431!-- listspec) for both a (soluble) and b (insoluble) bins.
    424432    REAL(wp), DIMENSION(nmod) ::  aerosol_flux_dpg   = &
    425                                      (/0.013_wp, 0.054_wp, 0.86_wp, 0.2_wp, 0.2_wp, 0.2_wp, 0.2_wp/)
     433                     (/1.3E-8_wp, 5.4E-8_wp, 8.6E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp, 2.0E-7_wp/)
    426434    REAL(wp), DIMENSION(nmod) ::  aerosol_flux_sigmag  = &
    427435                                        (/1.8_wp, 2.16_wp, 2.21_wp, 2.0_wp, 2.0_wp, 2.0_wp, 2.0_wp/)
    428     REAL(wp), DIMENSION(nmod) ::  surface_aerosol_flux = &
    429                              (/1.04e+11_wp, 3.23E+10_wp, 5.4E+6_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp/)
    430436    REAL(wp), DIMENSION(maxspec) ::  aerosol_flux_mass_fracs_a = &
    431437                                                               (/1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)
    432438    REAL(wp), DIMENSION(maxspec) ::  aerosol_flux_mass_fracs_b = &
    433439                                                               (/0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0/)
     440    REAL(wp), DIMENSION(nmod) ::  surface_aerosol_flux = &
     441                             (/1.04e+11_wp, 3.23E+10_wp, 5.4E+6_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp/)
    434442
    435443    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bin_low_limits     !< to deliver information about
     
    795803                                     decycle_method, decycle_ns, depo_pcm_par, depo_pcm_type,      &
    796804                                     depo_surf_par, dpg, dt_salsa, feedback_to_palm, h2so4_init,   &
    797                                      hno3_init, igctyp, isdtyp, listspec, mass_fracs_a,            &
    798                                      mass_fracs_b, n_lognorm, nbin, nest_salsa, nf2a, nh3_init,    &
    799                                      nj3, nlcnd, nlcndgas, nlcndh2oae, nlcoag, nldepo, nldepo_pcm, &
    800                                      nldepo_surf, nldistupdate, nsnucl, ocnv_init, ocsv_init,      &
    801                                      read_restart_data_salsa, reglim, salsa, salsa_emission_mode,  &
    802                                      sigmag, skip_time_do_salsa, surface_aerosol_flux,             &
    803                                      van_der_waals_coagc, write_binary_salsa
     805                                     hno3_init, init_gases_type, init_aerosol_type, listspec,      &
     806                                     mass_fracs_a, mass_fracs_b, n_lognorm, nbin, nest_salsa, nf2a,&
     807                                     nh3_init, nj3, nlcnd, nlcndgas, nlcndh2oae, nlcoag, nldepo,  &
     808                                     nldepo_pcm,  nldepo_surf, nldistupdate, nsnucl, ocnv_init,    &
     809                                     ocsv_init, read_restart_data_salsa, reglim, salsa,            &
     810                                     salsa_emission_mode, sigmag, skip_time_do_salsa,              &
     811                                     surface_aerosol_flux, van_der_waals_coagc, write_binary_salsa
    804812
    805813    line = ' '
     
    867875    ENDIF
    868876
    869     IF ( salsa_emission_mode == 'read_from_file'  .AND.  ibc_salsa_b  == 0 ) THEN
    870        message_string = 'salsa_emission_mode == read_from_file requires bc_salsa_b = "Neumann"'
     877    IF ( salsa_emission_mode /= 'no_emission'  .AND.  ibc_salsa_b  == 0 ) THEN
     878       message_string = 'salsa_emission_mode /= "no_emission" requires bc_salsa_b = "Neumann"'
    871879       CALL message( 'salsa_check_parameters','PA0598', 1, 2, 0, 6, 0 )
    872880    ENDIF
     881
     882    IF ( salsa_emission_mode /= 'no_emission' )  include_emission = .TRUE.
    873883
    874884 END SUBROUTINE salsa_check_parameters
     
    960970    ENDIF
    961971    WRITE( io, 7 )
    962     IF ( nsnucl > 0 )  THEN
    963        WRITE( io, 8 ) nsnucl, nj3
    964     ENDIF
    965     IF ( nlcoag )  THEN
    966        WRITE( io, 9 )
    967     ENDIF
    968     IF ( nlcnd )  THEN
    969        WRITE( io, 10 ) nlcndgas, nlcndh2oae
    970     ENDIF
    971     IF ( lspartition )  THEN
    972        WRITE( io, 11 )
    973     ENDIF
    974     IF ( nldepo )  THEN
    975        WRITE( io, 12 ) nldepo_pcm, nldepo_surf
    976     ENDIF
     972    IF ( nsnucl > 0 )   WRITE( io, 8 ) nsnucl, nj3
     973    IF ( nlcoag )       WRITE( io, 9 )
     974    IF ( nlcnd )        WRITE( io, 10 ) nlcndgas, nlcndh2oae
     975    IF ( lspartition )  WRITE( io, 11 )
     976    IF ( nldepo )       WRITE( io, 12 ) nldepo_pcm, nldepo_surf
    977977    WRITE( io, 13 )  reglim, nbin, bin_low_limits
    978     IF ( isdtyp == 0 )  WRITE( io, 14 ) nsect
     978    IF ( init_aerosol_type == 0 )  WRITE( io, 14 ) nsect
    979979    WRITE( io, 15 ) ncc, listspec, mass_fracs_a, mass_fracs_b
    980980    IF ( .NOT. salsa_gases_from_chem )  THEN
    981981       WRITE( io, 16 ) ngases_salsa, h2so4_init, hno3_init, nh3_init, ocnv_init, ocsv_init
    982982    ENDIF
    983     WRITE( io, 17 )  isdtyp, igctyp
    984     IF ( isdtyp == 0 )  THEN
     983    WRITE( io, 17 )  init_aerosol_type, init_gases_type
     984    IF ( init_aerosol_type == 0 )  THEN
    985985       WRITE( io, 18 )  dpg, sigmag, n_lognorm
    986986    ELSE
     
    989989    IF ( nest_salsa )  WRITE( io, 20 )  nest_salsa
    990990    WRITE( io, 21 ) salsa_emission_mode
    991 
     991    IF ( salsa_emission_mode == 'uniform' )  THEN
     992       WRITE( io, 22 ) surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag,                &
     993                       aerosol_flux_mass_fracs_a
     994    ENDIF
     995    IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp  .OR. salsa_emission_mode == 'read_from_file' ) &
     996    THEN
     997       WRITE( io, 23 )
     998    ENDIF
    992999
    99310001   FORMAT (//' SALSA information:'/                                                               &
     
    10241031              '       OCSV:  ',ES12.4E3, ' #/m**3')
    1025103217   FORMAT (/'   Initialising concentrations: ', /                                                &
    1026               '      Aerosol size distribution: isdtyp = ', I1,/                                   &
    1027               '      Gas concentrations: igctyp = ', I1 )
     1033              '      Aerosol size distribution: init_aerosol_type = ', I1,/                        &
     1034              '      Gas concentrations: init_gases_type = ', I1 )
    1028103518   FORMAT ( '      Mode diametres: dpg(nmod) = ', 7(F7.3), ' (m)', /                             &
    10291036              '      Standard deviation: sigmag(nmod) = ', 7(F7.2),/                               &
     
    1032103920   FORMAT (/'   Nesting for salsa variables: ', L1 )
    1033104021   FORMAT (/'   Emissions: salsa_emission_mode = ', A )
     104122   FORMAT (/'      surface_aerosol_flux = ', ES12.4E3, ' #/m**2/s', /                            &
     1042              '      aerosol_flux_dpg     =  ', 7(F7.3), ' (m)', /                                 &
     1043              '      aerosol_flux_sigmag  =  ', 7(F7.2), /                                         &
     1044              '      aerosol_mass_fracs_a =  ', 7(ES12.4E3) )
     104523   FORMAT (/'      (currently all emissions are soluble!)')
    10341046
    10351047 END SUBROUTINE salsa_header
     
    10881100!-- Allocate:
    10891101    ALLOCATE( aero(nbins_aerosol), bc_am_t_val(nbins_aerosol*ncomponents_mass),                    &
    1090               bc_an_t_val(ngases_salsa), bc_gt_t_val(nbins_aerosol), bin_low_limits(nbins_aerosol),&
     1102              bc_an_t_val(nbins_aerosol), bc_gt_t_val(ngases_salsa), bin_low_limits(nbins_aerosol),&
    10911103              nsect(nbins_aerosol), massacc(nbins_aerosol) )
    10921104    ALLOCATE( k_topo_top(nysg:nyng,nxlg:nxrg) )
     
    11081120       aerosol_number(i)%conc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  => nconc_2(:,:,:,i)
    11091121       aerosol_number(i)%tconc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) => nconc_3(:,:,:,i)
    1110        ALLOCATE( aerosol_number(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),     &
    1111                  aerosol_number(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),     &
    1112                  aerosol_number(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),&
    1113                  aerosol_number(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),&
    1114                  aerosol_number(i)%init(nzb:nzt+1),                            &
     1122       ALLOCATE( aerosol_number(i)%flux_s(nzb+1:nzt,0:threads_per_task-1),                         &
     1123                 aerosol_number(i)%diss_s(nzb+1:nzt,0:threads_per_task-1),                         &
     1124                 aerosol_number(i)%flux_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                 &
     1125                 aerosol_number(i)%diss_l(nzb+1:nzt,nys:nyn,0:threads_per_task-1),                 &
     1126                 aerosol_number(i)%init(nzb:nzt+1),                                                &
    11151127                 aerosol_number(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1) )
     1128       IF ( include_emission  .OR.  ( nldepo  .AND.  nldepo_surf ) )  THEN
     1129          ALLOCATE( aerosol_number(i)%source(nys:nyn,nxl:nxr) )
     1130       ENDIF
    11161131    ENDDO
    11171132
     
    11361151                 aerosol_mass(i)%init(nzb:nzt+1),                                                  &
    11371152                 aerosol_mass(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1)  )
     1153       IF ( include_emission  .OR.  ( nldepo  .AND.  nldepo_surf ) )  THEN
     1154          ALLOCATE( aerosol_mass(i)%source(nys:nyn,nxl:nxr) )
     1155       ENDIF
    11381156    ENDDO
    11391157
     
    12371255                    salsa_gas(i)%init(nzb:nzt+1),                              &
    12381256                    salsa_gas(i)%sums_ws_l(nzb:nzt+1,0:threads_per_task-1) )
     1257          IF ( include_emission )  ALLOCATE( salsa_gas(i)%source(nys:nys,nxl:nxr) )
    12391258       ENDDO
    12401259!
     
    14341453    IF ( nldepo )  CALL init_deposition
    14351454
    1436     IF ( salsa_emission_mode /= 'no_emission' )  THEN
     1455    IF ( include_emission )  THEN
    14371456!
    14381457!--    Read in and initialize emissions
    14391458       CALL salsa_emission_setup( .TRUE. )
    1440        IF ( .NOT. salsa_gases_from_chem  .AND.  salsa_emission_mode == 'read_from_file' )  THEN
     1459       IF ( .NOT. salsa_gases_from_chem  .AND.  include_emission )  THEN
    14411460          CALL salsa_gas_emission_setup( .TRUE. )
    14421461       ENDIF
     
    15981617    pmfoc1a(:)   = 0.0_wp
    15991618
    1600     IF ( isdtyp == 1 )  THEN
     1619    IF ( init_aerosol_type == 1 )  THEN
    16011620!
    16021621!--    Read input profiles from PIDS_DYNAMIC_SALSA
     
    16081627!
    16091628!--       Open file in read-only mode
    1610           CALL open_read_file( input_file_dynamic // TRIM( coupling_char ), id_dyn )
     1629          CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), id_dyn )
    16111630!
    16121631!--       Inquire dimensions:
     
    16711690!--       Aerosol concentrations: lod=1 (total PM) or lod=2 (sectional number size distribution)
    16721691          CALL get_attribute( id_dyn, 'lod', lod_aero, .FALSE., 'init_atmosphere_aerosol' )
    1673           IF ( lod_aero /= 2 )  THEN
    1674              message_string = 'Currently only lod=2 accepted for init_atmosphere_aerosol'
     1692          IF ( lod_aero /= 1 )  THEN
     1693             message_string = 'Currently only lod=1 accepted for init_atmosphere_aerosol'
    16751694             CALL message( 'salsa_mod: aerosol_init', 'PA0603', 2, 2, 0, 6, 0 )
    16761695          ELSE
     
    16931712             IF ( ANY( ABS( ( aero(1:nbins_aerosol)%dmid - pr_dmid ) /                             &
    16941713                              aero(1:nbins_aerosol)%dmid )  > 0.1_wp )  ) THEN
    1695                 message_string = 'Mean diameters of the aerosol size bins ' // TRIM(               &
    1696                                  input_file_dynamic ) // ' in do not conform to the sectional '//  &
     1714                message_string = 'Mean diameters of the aerosol size bins in ' // TRIM(            &
     1715                                 input_file_dynamic ) // ' do not match with the sectional '//     &
    16971716                                 'representation of the model.'
    16981717                CALL message( 'salsa_mod: aerosol_init', 'PA0605', 2, 2, 0, 6, 0 )
     
    17631782
    17641783#else
    1765        message_string = 'isdtyp = 1 but preprocessor directive __netcdf is not used in compiling!'
     1784       message_string = 'init_aerosol_type = 1 but preprocessor directive __netcdf is not used '// &
     1785                        'in compiling!'
    17661786       CALL message( 'salsa_mod: aerosol_init', 'PA0608', 1, 2, 0, 6, 0 )
    17671787
    17681788#endif
    17691789
    1770     ELSEIF ( isdtyp == 0 )  THEN
     1790    ELSEIF ( init_aerosol_type == 0 )  THEN
    17711791!
    17721792!--    Mass fractions for species in a and b-bins
     
    18131833    ENDIF
    18141834
    1815     IF ( igctyp == 1 )  THEN
     1835    IF ( init_gases_type == 1 )  THEN
    18161836!
    18171837!--    Read input profiles from PIDS_CHEM
     
    18231843!
    18241844!--       Open file in read-only mode
    1825           CALL open_read_file( input_file_dynamic // TRIM( coupling_char ), id_dyn )
     1845          CALL open_read_file( TRIM( input_file_dynamic ) // TRIM( coupling_char ), id_dyn )
    18261846!
    18271847!--       Inquire dimensions:
     
    18551875       ENDIF   ! netcdf_extend
    18561876#else
    1857        message_string = 'igctyp = 1 but preprocessor directive __netcdf is not used in compiling!'
     1877       message_string = 'init_gases_type = 1 but preprocessor directive __netcdf is not used in '//&
     1878                        'compiling!'
    18581879       CALL message( 'salsa_mod: aerosol_init', 'PA0611', 1, 2, 0, 6, 0 )
    18591880
     
    25082529    REAL(wp), DIMENSION(nzb:nzt+1,nbins_aerosol) ::  vd           !< particle fall seed (m/s)
    25092530
    2510     TYPE(t_section), DIMENSION(nbins_aerosol) ::  aero_old !< helper array
     2531    TYPE(t_section), DIMENSION(nbins_aerosol) ::  lo_aero   !< additional variable for OpenMP
     2532    TYPE(t_section), DIMENSION(nbins_aerosol) ::  aero_old  !< helper array
    25112533
    25122534    aero_old(:)%numc = 0.0_wp
     
    25142536    in_u             = 0.0_wp
    25152537    kvis             = 0.0_wp
     2538    lo_aero          = aero
    25162539    schmidt_num      = 0.0_wp
    25172540    vd               = 0.0_wp
     
    25242547!-- Aerosol number is always set, but mass can be uninitialized
    25252548    DO ib = 1, nbins_aerosol
    2526        aero(ib)%volc(:)     = 0.0_wp
     2549       lo_aero(ib)%volc(:)  = 0.0_wp
    25272550       aero_old(ib)%volc(:) = 0.0_wp
    25282551    ENDDO
     
    25732596          ic = 1
    25742597          DO ss = str, endi
    2575              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2so4
     2598             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2so4
    25762599             ic = ic+1
    25772600          ENDDO
    2578           aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2601          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    25792602       ENDIF
    25802603!
     
    25862609          ic = 1
    25872610          DO ss = str, endi
    2588              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhooc
     2611             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhooc
    25892612             ic = ic+1
    25902613          ENDDO
    2591           aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2614          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    25922615       ENDIF
    25932616!
     
    25992622          ic = 1 + end_subrange_1a
    26002623          DO ss = str, endi
    2601              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhobc
     2624             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhobc
    26022625             ic = ic+1
    26032626          ENDDO
    2604           aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2627          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    26052628       ENDIF
    26062629!
     
    26122635          ic = 1 + end_subrange_1a
    26132636          DO ss = str, endi
    2614              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhodu
     2637             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhodu
    26152638             ic = ic+1
    26162639          ENDDO
    2617           aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2640          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    26182641       ENDIF
    26192642!
     
    26252648          ic = 1 + end_subrange_1a
    26262649          DO ss = str, endi
    2627              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoss
     2650             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoss
    26282651             ic = ic+1
    26292652          ENDDO
    2630           aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2653          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    26312654       ENDIF
    26322655!
     
    26382661          ic = 1
    26392662          DO ss = str, endi
    2640              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhohno3
     2663             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhohno3
    26412664             ic = ic+1
    26422665          ENDDO
    2643           aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2666          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    26442667       ENDIF
    26452668!
     
    26512674          ic = 1
    26522675          DO ss = str, endi
    2653              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhonh3
     2676             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhonh3
    26542677             ic = ic+1
    26552678          ENDDO
    2656           aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2679          aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    26572680       ENDIF
    26582681!
     
    26652688       IF ( advect_particle_water )  THEN
    26662689          DO ss = str, endi
    2667              aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2o
     2690             lo_aero(ic)%volc(vc) = aerosol_mass(ss)%conc(k,j,i) / arhoh2o
    26682691             ic = ic+1
    26692692          ENDDO
    26702693       ELSE
    2671          aero(1:nbins_aerosol)%volc(vc) = mclim
    2672        ENDIF
    2673        aero_old(1:nbins_aerosol)%volc(vc) = aero(1:nbins_aerosol)%volc(vc)
     2694         lo_aero(1:nbins_aerosol)%volc(vc) = mclim
     2695       ENDIF
     2696       aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    26742697!
    26752698!--    Number concentrations (numc) and particle sizes
    26762699!--    (dwet = wet diameter, core = dry volume)
    26772700       DO  ib = 1, nbins_aerosol
    2678           aero(ib)%numc = aerosol_number(ib)%conc(k,j,i)
    2679           aero_old(ib)%numc = aero(ib)%numc
    2680           IF ( aero(ib)%numc > nclim )  THEN
    2681              aero(ib)%dwet = ( SUM( aero(ib)%volc(:) ) / aero(ib)%numc / api6 )**0.33333333_wp
    2682              aero(ib)%core = SUM( aero(ib)%volc(1:7) ) / aero(ib)%numc
     2701          lo_aero(ib)%numc = aerosol_number(ib)%conc(k,j,i)
     2702          aero_old(ib)%numc = lo_aero(ib)%numc
     2703          IF ( lo_aero(ib)%numc > nclim )  THEN
     2704             lo_aero(ib)%dwet = ( SUM( lo_aero(ib)%volc(:) ) / lo_aero(ib)%numc / api6 )**0.33333333_wp
     2705             lo_aero(ib)%core = SUM( lo_aero(ib)%volc(1:7) ) / lo_aero(ib)%numc
    26832706          ELSE
    2684              aero(ib)%dwet = aero(ib)%dmid
    2685              aero(ib)%core = api6 * ( aero(ib)%dwet )**3
     2707             lo_aero(ib)%dwet = lo_aero(ib)%dmid
     2708             lo_aero(ib)%core = api6 * ( lo_aero(ib)%dwet )**3
    26862709          ENDIF
    26872710       ENDDO
     
    26922715       in_rh = in_cw(k) / in_cs(k)
    26932716       IF ( prunmode==1  .OR.  .NOT. advect_particle_water )  THEN
    2694           CALL equilibration( in_rh, in_t(k), aero, .TRUE. )
     2717          CALL equilibration( in_rh, in_t(k), lo_aero, .TRUE. )
    26952718       ENDIF
    26962719!
     
    27172740!--    Coagulation
    27182741       IF ( lscoag )   THEN
    2719           CALL coagulation( aero, dt_salsa, in_t(k), in_p(k) )
     2742          CALL coagulation( lo_aero, dt_salsa, in_t(k), in_p(k) )
    27202743       ENDIF
    27212744!
    27222745!--    Condensation
    27232746       IF ( lscnd )   THEN
    2724           CALL condensation( aero, zgso4, zgocnv, zgocsv,  zghno3, zgnh3, in_cw(k), in_cs(k),      &
     2747          CALL condensation( lo_aero, zgso4, zgocnv, zgocsv,  zghno3, zgnh3, in_cw(k), in_cs(k),      &
    27252748                             in_t(k), in_p(k), dt_salsa, prtcl )
    27262749       ENDIF
     
    27282751!--    Deposition
    27292752       IF ( lsdepo )  THEN
    2730           CALL deposition( aero, in_t(k), in_adn(k), in_u(k), in_lad, kvis(k), schmidt_num(k,:),   &
     2753          CALL deposition( lo_aero, in_t(k), in_adn(k), in_u(k), in_lad, kvis(k), schmidt_num(k,:),   &
    27312754                           vd(k,:) )
    27322755       ENDIF
     
    27342757!--    Size distribution bin update
    27352758       IF ( lsdistupdate )   THEN
    2736           CALL distr_update( aero )
     2759          CALL distr_update( lo_aero )
    27372760       ENDIF
    27382761!--    *********************************************************************************************
     
    27422765!--    Calculate changes in concentrations
    27432766       DO ib = 1, nbins_aerosol
    2744           aerosol_number(ib)%conc(k,j,i) = aerosol_number(ib)%conc(k,j,i) + ( aero(ib)%numc -      &
     2767          aerosol_number(ib)%conc(k,j,i) = aerosol_number(ib)%conc(k,j,i) + ( lo_aero(ib)%numc -      &
    27452768                                           aero_old(ib)%numc ) * flag
    27462769       ENDDO
     
    27522775          ic = 1
    27532776          DO ss = str, endi
    2754              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2777             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    27552778                                            aero_old(ic)%volc(vc) ) * arhoh2so4 * flag
    27562779             ic = ic+1
     
    27642787          ic = 1
    27652788          DO ss = str, endi
    2766              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2789             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    27672790                                            aero_old(ic)%volc(vc) ) * arhooc * flag
    27682791             ic = ic+1
     
    27762799          ic = 1 + end_subrange_1a
    27772800          DO ss = str, endi
    2778              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2801             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    27792802                                            aero_old(ic)%volc(vc) ) * arhobc * flag
    27802803             ic = ic+1
     
    27882811          ic = 1 + end_subrange_1a
    27892812          DO ss = str, endi
    2790              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2813             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    27912814                                            aero_old(ic)%volc(vc) ) * arhodu * flag
    27922815             ic = ic+1
     
    28002823          ic = 1 + end_subrange_1a
    28012824          DO ss = str, endi
    2802              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2825             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    28032826                                            aero_old(ic)%volc(vc) ) * arhoss * flag
    28042827             ic = ic+1
     
    28122835          ic = 1
    28132836          DO ss = str, endi
    2814              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2837             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    28152838                                            aero_old(ic)%volc(vc) ) * arhohno3 * flag
    28162839             ic = ic+1
     
    28242847          ic = 1
    28252848          DO ss = str, endi
    2826              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2849             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    28272850                                            aero_old(ic)%volc(vc) ) * arhonh3 * flag
    28282851             ic = ic+1
     
    28372860          ic = 1
    28382861          DO ss = str, endi
    2839              aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( aero(ic)%volc(vc) -   &
     2862             aerosol_mass(ss)%conc(k,j,i) = aerosol_mass(ss)%conc(k,j,i) + ( lo_aero(ic)%volc(vc) -   &
    28402863                                            aero_old(ic)%volc(vc) ) * arhoh2o * flag
    28412864             IF ( prunmode == 1 )  THEN
     
    29182941
    29192942    ENDDO   ! k
     2943
    29202944!
    29212945!-- Set surfaces and wall fluxes due to deposition
     
    29372961       ENDIF
    29382962    ENDIF
     2963
     2964    IF ( prunmode < 3 )  THEN
     2965       !$OMP MASTER
     2966       aero = lo_aero
     2967       !$OMP END MASTER
     2968    END IF
    29392969
    29402970 END SUBROUTINE salsa_driver
     
    36553685!
    36563686!--       Calculate changes in surface fluxes due to dry deposition
    3657           IF ( aero_emission_att%lod == 2  .OR.  salsa_emission_mode ==  'no_emission' )  THEN
    3658              surf%answs(m,ib) = -depo * norm_fac * aerosol_number(ib)%conc(k,j,i)
    3659              DO  ic = 1, ncomponents_mass
    3660                 icc = ( ic - 1 ) * nbins_aerosol + ib
    3661                 surf%amsws(m,icc) = -depo *  norm_fac * aerosol_mass(icc)%conc(k,j,i)
    3662              ENDDO    ! ic
    3663           ELSE
     3687          IF ( include_emission )  THEN
    36643688             surf%answs(m,ib) = aerosol_number(ib)%source(j,i) -                                   &
    36653689                                MAX( 0.0_wp, depo * norm_fac * aerosol_number(ib)%conc(k,j,i) )
     
    36693693                                    MAX( 0.0_wp, depo *  norm_fac * aerosol_mass(icc)%conc(k,j,i) )
    36703694             ENDDO  ! ic
     3695          ELSE
     3696             surf%answs(m,ib) = -depo * norm_fac * aerosol_number(ib)%conc(k,j,i)
     3697             DO  ic = 1, ncomponents_mass
     3698                icc = ( ic - 1 ) * nbins_aerosol + ib
     3699                surf%amsws(m,icc) = -depo *  norm_fac * aerosol_mass(icc)%conc(k,j,i)
     3700             ENDDO    ! ic
    36713701          ENDIF
    36723702       ENDDO    ! ib
     
    49755005    IF ( ptemp < 240.0_wp  .OR.  ptemp > 300.0_wp )  THEN
    49765006       message_string = 'Invalid input value: ptemp'
    4977        CALL message( 'salsa_mod: ternucl', 'PA0619', 1, 2, 0, 6, 0 )
     5007       CALL message( 'salsa_mod: ternucl', 'PA0648', 1, 2, 0, 6, 0 )
    49785008    ENDIF
    49795009    IF ( prh < 0.05_wp  .OR.  prh > 0.95_wp )  THEN
    49805010       message_string = 'Invalid input value: prh'
    4981        CALL message( 'salsa_mod: ternucl', 'PA0620', 1, 2, 0, 6, 0 )
     5011       CALL message( 'salsa_mod: ternucl', 'PA0649', 1, 2, 0, 6, 0 )
    49825012    ENDIF
    49835013    IF ( pc_sa < 1.0E+4_wp  .OR.  pc_sa > 1.0E+9_wp )  THEN
    49845014       message_string = 'Invalid input value: pc_sa'
    4985        CALL message( 'salsa_mod: ternucl', 'PA0621', 1, 2, 0, 6, 0 )
     5015       CALL message( 'salsa_mod: ternucl', 'PA0650', 1, 2, 0, 6, 0 )
    49865016    ENDIF
    49875017    IF ( pc_nh3 < 0.1_wp  .OR.  pc_nh3 > 100.0_wp )  THEN
    49885018       message_string = 'Invalid input value: pc_nh3'
    4989        CALL message( 'salsa_mod: ternucl', 'PA0622', 1, 2, 0, 6, 0 )
     5019       CALL message( 'salsa_mod: ternucl', 'PA0651', 1, 2, 0, 6, 0 )
    49905020    ENDIF
    49915021
     
    69336963
    69346964          IF ( paero(ib)%numc > nclim )   THEN
    6935              zvpart = SUM( paero(ib)%volc(:) ) / paero(ib)%numc
     6965             zvpart = SUM( paero(ib)%volc(1:7) ) / paero(ib)%numc  ! Note: dry volume!
    69366966             within_bins = ( paero(ib)%vlolim < zvpart  .AND. zvpart < paero(ib)%vhilim )
    69376967          ENDIF
     
    69917021    zvol         = 0.0_wp
    69927022
     7023    !$OMP MASTER
    69937024    CALL cpu_log( log_point_s(94), 'salsa diagnostics ', 'start' )
     7025    !$OMP END MASTER
     7026
    69947027!
    69957028!-- Calculate thermodynamic quantities needed in SALSA
     
    70097042!--    Calculate total mass concentration per bin
    70107043       mcsum = 0.0_wp
    7011        DO  ic = 1, ncomponents_mass
     7044       DO  ic = 1, ncc
    70127045          icc = ( ic - 1 ) * nbins_aerosol + ib
    70137046          mcsum = mcsum + aerosol_mass(icc)%conc(:,j,i) * flag
     
    70157048!
    70167049!--    Check that number and mass concentration match qualitatively
    7017        IF ( ANY ( aerosol_number(ib)%conc(:,j,i) > nclim  .AND. mcsum <= 0.0_wp ) )  THEN
     7050       IF ( ANY ( aerosol_number(ib)%conc(:,j,i) >= nclim  .AND. mcsum <= 0.0_wp ) )  THEN
    70187051          DO  k = nzb+1, nzt
    7019              IF ( aerosol_number(ib)%conc(k,j,i) > nclim  .AND. mcsum(k) <= 0.0_wp )  THEN
     7052             IF ( aerosol_number(ib)%conc(k,j,i) >= nclim  .AND. mcsum(k) <= 0.0_wp )  THEN
    70207053                aerosol_number(ib)%conc(k,j,i) = nclim * flag(k)
    70217054                DO  ic = 1, ncomponents_mass
     
    71037136    ENDIF
    71047137
     7138   !$OMP MASTER
    71057139    CALL cpu_log( log_point_s(94), 'salsa diagnostics ', 'stop' )
     7140   !$OMP END MASTER
    71067141
    71077142 END SUBROUTINE salsa_diagnostics
     
    71857220    INTEGER(iwp) ::  tn           !<
    71867221
    7187     LOGICAL ::  sedim  !< calculate sedimentation only for aerosols (number and mass)
     7222    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     7223!
     7224!--    Aerosol number
     7225       DO  ib = 1, nbins_aerosol
     7226!kk          sums_salsa_ws_l = aerosol_number(ib)%sums_ws_l
     7227          CALL salsa_tendency( 'aerosol_number', aerosol_number(ib)%conc_p, aerosol_number(ib)%conc,&
     7228                               aerosol_number(ib)%tconc_m, i, j, i_omp_start, tn, ib, ib,          &
     7229                               aerosol_number(ib)%flux_s, aerosol_number(ib)%diss_s,               &
     7230                               aerosol_number(ib)%flux_l, aerosol_number(ib)%diss_l,               &
     7231                               aerosol_number(ib)%init, .TRUE. )
     7232!kk          aerosol_number(ib)%sums_ws_l = sums_salsa_ws_l
     7233!
     7234!--       Aerosol mass
     7235          DO  ic = 1, ncomponents_mass
     7236             icc = ( ic - 1 ) * nbins_aerosol + ib
     7237!kk             sums_salsa_ws_l = aerosol_mass(icc)%sums_ws_l
     7238             CALL salsa_tendency( 'aerosol_mass', aerosol_mass(icc)%conc_p, aerosol_mass(icc)%conc,&
     7239                                  aerosol_mass(icc)%tconc_m, i, j, i_omp_start, tn, ib, ic,        &
     7240                                  aerosol_mass(icc)%flux_s, aerosol_mass(icc)%diss_s,              &
     7241                                  aerosol_mass(icc)%flux_l, aerosol_mass(icc)%diss_l,              &
     7242                                  aerosol_mass(icc)%init, .TRUE. )
     7243!kk             aerosol_mass(icc)%sums_ws_l = sums_salsa_ws_l
     7244
     7245          ENDDO  ! ic
     7246       ENDDO  ! ib
     7247!
     7248!--    Gases
     7249       IF ( .NOT. salsa_gases_from_chem )  THEN
     7250
     7251          DO  ig = 1, ngases_salsa
     7252!kk             sums_salsa_ws_l = salsa_gas(ig)%sums_ws_l
     7253             CALL salsa_tendency( 'salsa_gas', salsa_gas(ig)%conc_p, salsa_gas(ig)%conc,           &
     7254                                  salsa_gas(ig)%tconc_m, i, j, i_omp_start, tn, ig, ig,            &
     7255                                  salsa_gas(ig)%flux_s, salsa_gas(ig)%diss_s, salsa_gas(ig)%flux_l,&
     7256                                  salsa_gas(ig)%diss_l, salsa_gas(ig)%init, .FALSE. )
     7257!kk             salsa_gas(ig)%sums_ws_l = sums_salsa_ws_l
     7258
     7259          ENDDO  ! ig
     7260
     7261       ENDIF
     7262
     7263    ENDIF
     7264
     7265 END SUBROUTINE salsa_prognostic_equations_ij
     7266!
     7267!------------------------------------------------------------------------------!
     7268! Description:
     7269! ------------
     7270!> Calculate the prognostic equation for aerosol number and mass, and gas
     7271!> concentrations. Cache-optimized.
     7272!------------------------------------------------------------------------------!
     7273 SUBROUTINE salsa_prognostic_equations()
     7274
     7275    USE control_parameters,                                                                        &
     7276        ONLY:  time_since_reference_point
     7277
     7278    IMPLICIT NONE
     7279
     7280    INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
     7281    INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
     7282    INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
     7283    INTEGER(iwp) ::  ig           !< loop index for salsa gases
    71887284
    71897285    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     
    71937289          sums_salsa_ws_l = aerosol_number(ib)%sums_ws_l
    71947290          CALL salsa_tendency( 'aerosol_number', aerosol_number(ib)%conc_p, aerosol_number(ib)%conc,&
    7195                                aerosol_number(ib)%tconc_m, i, j, i_omp_start, tn, ib, ib,          &
    7196                                aerosol_number(ib)%flux_s, aerosol_number(ib)%diss_s,               &
    7197                                aerosol_number(ib)%flux_l, aerosol_number(ib)%diss_l,               &
    7198                                aerosol_number(ib)%init, sedim )
     7291                               aerosol_number(ib)%tconc_m, ib, ib, aerosol_number(ib)%init, .TRUE. )
    71997292          aerosol_number(ib)%sums_ws_l = sums_salsa_ws_l
    72007293!
     
    72047297             sums_salsa_ws_l = aerosol_mass(icc)%sums_ws_l
    72057298             CALL salsa_tendency( 'aerosol_mass', aerosol_mass(icc)%conc_p, aerosol_mass(icc)%conc,&
    7206                                   aerosol_mass(icc)%tconc_m, i, j, i_omp_start, tn, ib, ic,        &
    7207                                   aerosol_mass(icc)%flux_s, aerosol_mass(icc)%diss_s,              &
    7208                                   aerosol_mass(icc)%flux_l, aerosol_mass(icc)%diss_l,              &
    7209                                   aerosol_mass(icc)%init, sedim )
     7299                                  aerosol_mass(icc)%tconc_m, ib, ic, aerosol_mass(icc)%init, .TRUE. )
    72107300             aerosol_mass(icc)%sums_ws_l = sums_salsa_ws_l
    72117301
     
    72197309             sums_salsa_ws_l = salsa_gas(ig)%sums_ws_l
    72207310             CALL salsa_tendency( 'salsa_gas', salsa_gas(ig)%conc_p, salsa_gas(ig)%conc,           &
    7221                                   salsa_gas(ig)%tconc_m, i, j, i_omp_start, tn, ig, ig,            &
    7222                                   salsa_gas(ig)%flux_s, salsa_gas(ig)%diss_s, salsa_gas(ig)%flux_l,&
    7223                                   salsa_gas(ig)%diss_l, salsa_gas(ig)%init, sedim )
    7224              salsa_gas(ig)%sums_ws_l = sums_salsa_ws_l
    7225 
    7226           ENDDO  ! ig
    7227 
    7228        ENDIF
    7229 
    7230     ENDIF
    7231 
    7232  END SUBROUTINE salsa_prognostic_equations_ij
    7233 !
    7234 !------------------------------------------------------------------------------!
    7235 ! Description:
    7236 ! ------------
    7237 !> Calculate the prognostic equation for aerosol number and mass, and gas
    7238 !> concentrations. Cache-optimized.
    7239 !------------------------------------------------------------------------------!
    7240  SUBROUTINE salsa_prognostic_equations()
    7241 
    7242     USE control_parameters,                                                                        &
    7243         ONLY:  time_since_reference_point
    7244 
    7245     IMPLICIT NONE
    7246 
    7247     INTEGER(iwp) ::  ib           !< loop index for aerosol number bin OR gas index
    7248     INTEGER(iwp) ::  ic           !< loop index for aerosol mass bin
    7249     INTEGER(iwp) ::  icc          !< (c-1)*nbins_aerosol+b
    7250     INTEGER(iwp) ::  ig           !< loop index for salsa gases
    7251 
    7252     LOGICAL ::  sedim  !< calculate sedimentation only for aerosols (number and mass)
    7253 
    7254     IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    7255 !
    7256 !--    Aerosol number
    7257        DO  ib = 1, nbins_aerosol
    7258           sums_salsa_ws_l = aerosol_number(ib)%sums_ws_l
    7259           CALL salsa_tendency( 'aerosol_number', aerosol_number(ib)%conc_p, aerosol_number(ib)%conc,&
    7260                                aerosol_number(ib)%tconc_m, ib, ib, aerosol_number(ib)%init, sedim )
    7261           aerosol_number(ib)%sums_ws_l = sums_salsa_ws_l
    7262 !
    7263 !--       Aerosol mass
    7264           DO  ic = 1, ncomponents_mass
    7265              icc = ( ic - 1 ) * nbins_aerosol + ib
    7266              sums_salsa_ws_l = aerosol_mass(icc)%sums_ws_l
    7267              CALL salsa_tendency( 'aerosol_mass', aerosol_mass(icc)%conc_p, aerosol_mass(icc)%conc,&
    7268                                   aerosol_mass(icc)%tconc_m, ib, ic, aerosol_mass(icc)%init, sedim )
    7269              aerosol_mass(icc)%sums_ws_l = sums_salsa_ws_l
    7270 
    7271           ENDDO  ! ic
    7272        ENDDO  ! ib
    7273 !
    7274 !--    Gases
    7275        IF ( .NOT. salsa_gases_from_chem )  THEN
    7276 
    7277           DO  ig = 1, ngases_salsa
    7278              sums_salsa_ws_l = salsa_gas(ig)%sums_ws_l
    7279              CALL salsa_tendency( 'salsa_gas', salsa_gas(ig)%conc_p, salsa_gas(ig)%conc,           &
    7280                                   salsa_gas(ig)%tconc_m, ig, ig, salsa_gas(ig)%init, sedim )
     7311                                  salsa_gas(ig)%tconc_m, ig, ig, salsa_gas(ig)%init, .FALSE. )
    72817312             salsa_gas(ig)%sums_ws_l = sums_salsa_ws_l
    72827313
     
    79557986    ELSE
    79567987       message_string = 'Error in itype!'
    7957        CALL message( 'salsa_mod: bin_mixrat', 'PA0628', 2, 2, 0, 6, 0 )
     7988       CALL message( 'bin_mixrat', 'PA0628', 2, 2, 0, 6, 0 )
    79587989    ENDIF
    79597990
     
    79788009    IMPLICIT NONE
    79798010
    7980     IF ( time_since_reference_point >= skip_time_do_salsa  )  THEN
    7981 
    7982        IF ( next_aero_emission_update <= time_since_reference_point )  THEN
    7983           CALL salsa_emission_setup( .FALSE. )
    7984        ENDIF
    7985 
    7986        IF ( next_gas_emission_update <= time_since_reference_point )  THEN
    7987           IF ( salsa_emission_mode == 'read_from_file'  .AND.  .NOT. salsa_gases_from_chem )  THEN
    7988              CALL salsa_gas_emission_setup( .FALSE. )
     8011    IF ( include_emission )  THEN
     8012
     8013       IF ( time_since_reference_point >= skip_time_do_salsa  )  THEN
     8014
     8015          IF ( next_aero_emission_update <= time_since_reference_point )  THEN
     8016             CALL salsa_emission_setup( .FALSE. )
    79898017          ENDIF
    7990        ENDIF
    7991 
     8018
     8019          IF ( next_gas_emission_update <= time_since_reference_point )  THEN
     8020             IF ( salsa_emission_mode == 'read_from_file'  .AND.  .NOT. salsa_gases_from_chem )    &
     8021             THEN
     8022                CALL salsa_gas_emission_setup( .FALSE. )
     8023             ENDIF
     8024          ENDIF
     8025
     8026       ENDIF
    79928027    ENDIF
    79938028
     
    80418076
    80428077!
    8043 !-- Allocate source arrays:
     8078!-- Set source arrays to zero:
    80448079    DO  ib = 1, nbins_aerosol
    8045        IF ( init )  ALLOCATE( aerosol_number(ib)%source(nys:nyn,nxl:nxr) )
    80468080       aerosol_number(ib)%source = 0.0_wp
    80478081    ENDDO
    80488082
    80498083    DO  ic = 1, ncomponents_mass * nbins_aerosol
    8050        IF ( init )  ALLOCATE( aerosol_mass(ic)%source(nys:nyn,nxl:nxr) )
    80518084       aerosol_mass(ic)%source = 0.0_wp
    80528085    ENDDO
     
    80898122!--          Set uniform fluxes of default horizontal surfaces
    80908123             CALL set_flux( surf_def_h(0), cc_i2m, aerosol_flux_mass_fracs_a, source_array )
    8091 !
    8092 !--          Subrange 2b:
    8093 !--          todo: this information should go to HEADER/RUN_CONTROL, it doesn't belong to the job log,
    8094 !--          and actually, aerosol_flux_mass_fracs_b is not used anywhere else except for this message,
    8095 !--          hence, what do we need it for?
    8096              IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp )  THEN
    8097                 CALL debug_message( '   salsa_emission_setup: emissions are soluble!', 'info' )
    8098              ENDIF
    80998124
    81008125             DEALLOCATE( nsect_emission, source_array )
     
    81198144!
    81208145!--          Check existence of PIDS_SALSA file
    8121              INQUIRE( FILE = input_file_salsa // TRIM( coupling_char ), EXIST = netcdf_extend )
     8146             INQUIRE( FILE = TRIM( input_file_salsa ) // TRIM( coupling_char ),                    &
     8147                      EXIST = netcdf_extend )
    81228148             IF ( .NOT. netcdf_extend )  THEN
    81238149                message_string = 'Input file '// TRIM( input_file_salsa ) //  TRIM( coupling_char )&
     
    81278153!
    81288154!--          Open file in read-only mode
    8129              CALL open_read_file( input_file_salsa // TRIM( coupling_char ), id_salsa )
     8155             CALL open_read_file( TRIM( input_file_salsa ) // TRIM( coupling_char ), id_salsa )
    81308156!
    81318157!--          Read the index and name of chemical components
     
    86868712                                    aero(ib)%core * prho * rho_air_zw(k-1)
    86878713       aerosol_mass(ic)%source(j,i) = aerosol_mass(ic)%source(j,i) + surface%amsws(surf_num,ic)
    8688 !
    8689 !--    Subrange 2b:
    8690 !--          todo: this information should go to HEADER/RUN_CONTROL, it doesn't belong to the job log
    8691 !        IF ( .NOT. no_insoluble )  THEN
    8692 !           CALL location_message( '    salsa_mass_flux: All emissions are soluble!', .TRUE. )
    8693 !        ENDIF
    86948714
    86958715    END SUBROUTINE set_mass_flux
     
    87848804          END SELECT
    87858805       ENDDO
    8786 !--          todo: this information should go to HEADER/RUN_CONTROL, it doesn't belong to the job log
    8787 !        IF ( SUM( emission_index_chem ) == 0 )  THEN
    8788 !           CALL location_message( '    salsa_gas_emission_setup: no gas emissions', .TRUE. )
    8789 !        ENDIF
    87908806!
    87918807!--    Inquire the fill value
Note: See TracChangeset for help on using the changeset viewer.