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

    r3833 r3864  
    2525! -----------------
    2626! $Id$
     27! Modifications made for salsa:
     28! - Call salsa_emission_update at each time step but do the checks within
     29!   salsa_emission_update (i.e. skip_time_do_salsa >= time_since_reference_point
     30!   and next_aero_emission_update <= time_since_reference_point ).
     31! - Renamed nbins --> nbins_aerosol, ncc_tot --> ncomponents_mass and
     32!   ngast --> ngases_salsa and loop indices b, c and sg to ib, ic and ig
     33! - Apply nesting for salsa variables
     34! - Removed cpu_log calls speciffic for salsa.
     35!
     36! 3833 2019-03-28 15:04:04Z forkel
    2737! added USE chem_gasphase_mod, replaced nspec by nvar since fixed compounds are not integrated
    2838!
     
    567577    USE nesting_offl_mod,                                                                          &
    568578        ONLY:  nesting_offl_bc, nesting_offl_mass_conservation
    569        
     579
    570580    USE netcdf_data_input_mod,                                                                     &
    571581        ONLY:  chem_emis, chem_emis_att, nest_offl, netcdf_data_input_offline_nesting
     
    591601        ONLY: dt_radiation, force_radiation_call, radiation, radiation_control,                    &
    592602              radiation_interaction, radiation_interactions, skip_time_do_radiation, time_radiation
    593          
     603
    594604    USE salsa_mod,                                                                                 &
    595         ONLY: aerosol_number, aerosol_mass, nbins, ncc_tot, ngast, salsa_boundary_conds,           &
    596               salsa_gas, salsa_gases_from_chem, skip_time_do_salsa
     605        ONLY: aerosol_number, aerosol_mass, bc_am_t_val, bc_an_t_val, bc_gt_t_val,                 &
     606              nbins_aerosol, ncomponents_mass, ngases_salsa, salsa_boundary_conds,                 &
     607              salsa_emission_update, salsa_gas, salsa_gases_from_chem, skip_time_do_salsa
    597608
    598609    USE spectra_mod,                                                                               &
     
    629640               vnest_boundary_conds_khkm, vnest_deallocate, vnest_init, vnest_init_fine,           &
    630641               vnest_start_time
    631                
     642
    632643    USE virtual_measurement_mod,                                                                   &
    633644        ONLY:  vm_data_output, vm_sampling, vm_time_start
     
    667678
    668679    CHARACTER (LEN=9) ::  time_to_string   !<
    669    
    670     INTEGER(iwp)      ::  b !< index for aerosol size bins   
    671     INTEGER(iwp)      ::  c !< index for chemical compounds in aerosol size bins
    672     INTEGER(iwp)      ::  g !< index for gaseous compounds
     680
     681    INTEGER(iwp)      ::  ib        !< index for aerosol size bins
     682    INTEGER(iwp)      ::  ic        !< index for aerosol mass bins
     683    INTEGER(iwp)      ::  icc       !< additional index for aerosol mass bins
     684    INTEGER(iwp)      ::  ig        !< index for salsa gases
    673685    INTEGER(iwp)      ::  lsp
    674686    INTEGER(iwp)      ::  lsp_usr   !<
     
    856868              ENDDO
    857869           ENDIF
     870           IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     871              DO  ib = 1, nbins_aerosol
     872                 bc_an_t_val = ( aerosol_number(ib)%init(nzt+1) - aerosol_number(ib)%init(nzt) ) / &
     873                               dzu(nzt+1)
     874                 DO  ic = 1, ncomponents_mass
     875                    icc = ( ic - 1 ) * nbins_aerosol + ib
     876                    bc_am_t_val = ( aerosol_mass(icc)%init(nzt+1) - aerosol_mass(icc)%init(nzt) ) /&
     877                                  dzu(nzt+1)
     878                 ENDDO
     879              ENDDO
     880              IF ( .NOT. salsa_gases_from_chem )  THEN
     881                 DO  ig = 1, ngases_salsa
     882                    bc_gt_t_val = ( salsa_gas(ig)%init(nzt+1) - salsa_gas(ig)%init(nzt) ) /        &
     883                                  dzu(nzt+1)
     884                 ENDDO
     885              ENDIF
     886           ENDIF
    858887       ENDIF
    859888!
     
    10281057          ENDIF
    10291058
    1030           IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )&
    1031           THEN
    1032              CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'start' )
    1033              DO  b = 1, nbins
    1034                 CALL exchange_horiz( aerosol_number(b)%conc_p, nbgp )
    1035                 CALL cpu_log( log_point_s(93), 'salsa decycle', 'start' )
    1036                 CALL salsa_boundary_conds( aerosol_number(b)%conc_p, aerosol_number(b)%init )
    1037                 CALL cpu_log( log_point_s(93), 'salsa decycle', 'stop' )
    1038                 DO  c = 1, ncc_tot
    1039                    CALL exchange_horiz( aerosol_mass((c-1)*nbins+b)%conc_p, nbgp )
    1040                    CALL cpu_log( log_point_s(93), 'salsa decycle', 'start' )
    1041                    CALL salsa_boundary_conds( aerosol_mass((c-1)*nbins+b)%conc_p,                  &
    1042                                               aerosol_mass((c-1)*nbins+b)%init )
    1043                    CALL cpu_log( log_point_s(93), 'salsa decycle', 'stop' )
     1059          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     1060!
     1061!--          Exchange ghost points and decycle boundary concentrations if needed
     1062             DO  ib = 1, nbins_aerosol
     1063                CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp )
     1064                CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
     1065                DO  ic = 1, ncomponents_mass
     1066                   icc = ( ic - 1 ) * nbins_aerosol + ib
     1067                   CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp )
     1068                   CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
    10441069                ENDDO
    10451070             ENDDO
    10461071             IF ( .NOT. salsa_gases_from_chem )  THEN
    1047                 DO  g = 1, ngast
    1048                    CALL exchange_horiz( salsa_gas(g)%conc_p, nbgp )
    1049                    CALL cpu_log( log_point_s(93), 'salsa decycle', 'start' )
    1050                    CALL salsa_boundary_conds( salsa_gas(g)%conc_p, salsa_gas(g)%init )
    1051                    CALL cpu_log( log_point_s(93), 'salsa decycle', 'stop' )
    1052              ENDDO
     1072                DO  ig = 1, ngases_salsa
     1073                   CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp )
     1074                   CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
     1075                ENDDO
    10531076             ENDIF
    1054              CALL cpu_log( log_point_s(91), 'salsa exch-horiz ', 'stop' )
    1055           ENDIF         
     1077          ENDIF
    10561078          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
    10571079
     
    11081130
    11091131                IF ( passive_scalar )  CALL exchange_horiz( s, nbgp ) 
    1110                
     1132
    11111133                IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e, nbgp )
    11121134
     
    11201142                   ENDDO
    11211143                ENDIF
     1144
     1145                IF ( salsa  .AND. time_since_reference_point >= skip_time_do_salsa )  THEN
     1146                   DO  ib = 1, nbins_aerosol
     1147                      CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
     1148                      CALL salsa_boundary_conds( aerosol_number(ib)%conc, aerosol_number(ib)%init )
     1149                      DO  ic = 1, ncomponents_mass
     1150                         icc = ( ic - 1 ) * nbins_aerosol + ib
     1151                         CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
     1152                         CALL salsa_boundary_conds( aerosol_mass(icc)%conc, aerosol_mass(icc)%init )
     1153                      ENDDO
     1154                   ENDDO
     1155                   IF ( .NOT. salsa_gases_from_chem )  THEN
     1156                      DO  ig = 1, ngases_salsa
     1157                         CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
     1158                         CALL salsa_boundary_conds( salsa_gas(ig)%conc, salsa_gas(ig)%init )
     1159                      ENDDO
     1160                   ENDIF
     1161                ENDIF
     1162                CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
    11221163
    11231164             ENDIF
     
    14071448          ENDIF
    14081449       ENDIF
    1409 
     1450!
     1451!--    If required, consider aerosol emissions for the salsa model
     1452       IF ( salsa )  THEN
     1453!
     1454!--       Call emission routine to update emissions if needed
     1455          CALL salsa_emission_update
     1456
     1457       ENDIF
    14101458!
    14111459!--    If required, calculate indoor temperature, waste heat, heat flux
Note: See TracChangeset for help on using the changeset viewer.