Ignore:
Timestamp:
Jan 14, 2021 10:42:28 AM (4 years ago)
Author:
raasch
Message:

reading of namelist file and actions in case of namelist errors revised so that statement labels and goto statements are not required any more, deprecated namelists removed

File:
1 edited

Legend:

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

    r4828 r4842  
    33! This file is part of PALM-4U.
    44!
    5 ! PALM-4U is free software: you can redistribute it and/or modify it under the 
    6 ! terms of the GNU General Public License as published by the Free Software 
    7 ! Foundation, either version 3 of the License, or (at your option) any later 
     5! PALM-4U is free software: you can redistribute it and/or modify it under the
     6! terms of the GNU General Public License as published by the Free Software
     7! Foundation, either version 3 of the License, or (at your option) any later
    88! version.
    99!
     
    2626! -----------------
    2727! $Id$
     28! reading of namelist file and actions in case of namelist errors revised so that statement labels
     29! and goto statements are not required any more
     30!
     31! 4828 2021-01-05 11:21:41Z Giersch
    2832! Bugfix in obtaining the correct timestamp in case of restart runs
    2933!
     
    3943! 4671 2020-09-09 20:27:58Z pavelkrc
    4044! Implementation of downward facing USM and LSM surfaces
    41 ! 
     45!
    4246! 4535 2020-05-15 12:07:23Z raasch
    4347! bugfix for restart data format query
    44 ! 
     48!
    4549! 4527 2020-05-11 09:39:55Z monakurppa
    4650! Correct a bug in salsa_wrd_global and salsa_check_data_output,
    4751! and add reglim to be read/written in the restart data
    48 ! 
     52!
    4953! 4525 2020-05-10 17:05:07Z raasch
    5054! added reading/writing of global restart data,
    5155! added reading/writing restart data with MPI-IO,
    5256! variable write_binary_salsa removed
    53 ! 
     57!
    5458! 4512 2020-04-30 12:55:34Z monakurppa
    5559! Fixed a bug in component_index_constructor: index out of bounds if all chemical
    5660! components are used
    57 ! 
     61!
    5862! 4508 2020-04-24 13:32:20Z raasch
    5963! decycling replaced by explicit setting of lateral boundary conditions (Siggi)
    60 ! 
     64!
    6165! 4487 2020-04-03 09:38:20Z raasch
    6266! bugfix for subroutine calls that contain the decycle_salsa switches as arguments
    63 ! 
     67!
    6468! 4481 2020-03-31 18:55:54Z maronga
    6569! Bug fix to the previous commit: the logical switch monotonic_limiter_z missing
    6670! from advec_s_ws in salsa_tendency_ij
    67 ! 
     71!
    6872! 4478 2020-03-27 14:06:23Z monakurppa
    6973! Bug fixes:
    7074! - call salsa_driver in salsa_init also for the ghost points
    7175! - decycle flags missing from advec_s_ws call in salsa_tendency
    72 ! 
     76!
    7377! 4457 2020-03-11 14:20:43Z raasch
    7478! use statement for exchange horiz added
    75 ! 
     79!
    7680! 4442 2020-03-04 19:21:13Z suehring
    77 ! Change order of dimension in surface array %frac to allow for better 
     81! Change order of dimension in surface array %frac to allow for better
    7882! vectorization.
    79 ! 
     83!
    8084! 4441 2020-03-04 19:20:35Z suehring
    8185! Bug fixes and reformatting for the restart data and averaged data output
     
    8690!   chemical components: set to 4d arrays instead of separate arrays
    8791! - add allocation checks for averaged data output arrays
    88 ! 
     92!
    8993! 4416 2020-02-20 17:53:57Z monakurppa
    9094! Time index error in salsa_emission_setup
    91 ! 
     95!
    9296! 4380 2020-01-17 23:39:51Z monakurppa
    9397! - Error in saving the surface fluxes in an array that is applied in the
     
    9599! - Corrections in the header: aerosol bin diameters and lower bin limits not
    96100!   printed correctly
    97 ! 
     101!
    98102! 4364 2020-01-08 02:12:31Z monakurppa
    99103! Set time coordinate in the input data relative to origin_time rather than to
    100104! 00:00:00 UTC
    101 ! 
     105!
    102106! 4360 2020-01-07 11:25:50Z suehring
    103107! Introduction of wall_flags_total_0, which currently sets bits based on static
    104108! topography information used in wall_flags_static_0
    105 ! 
     109!
    106110! 4342 2019-12-16 13:49:14Z Giersch
    107111! cdc replaced by canopy_drag_coeff
    108 ! 
     112!
    109113! 4329 2019-12-10 15:46:36Z motisi
    110114! Renamed wall_flags_0 to wall_flags_static_0
    111 ! 
     115!
    112116! 4315 2019-12-02 09:20:07Z monakurppa
    113117! Add an additional check for the time dimension PIDS_SALSA in
    114118! salsa_emission_setup and correct some error message identifiers.
    115 ! 
     119!
    116120! 4298 2019-11-21 15:59:16Z suehring
    117121! Bugfix, close netcdf input files after reading
    118 ! 
     122!
    119123! 4295 2019-11-14 06:15:31Z monakurppa
    120 ! 
    121 ! 
     124!
     125!
    122126! 4280 2019-10-29 14:34:15Z monakurppa
    123127! Corrected a bug in boundary conditions and fac_dt in offline nesting
    124 ! 
     128!
    125129! 4273 2019-10-24 13:40:54Z monakurppa
    126130! - Rename nest_salsa to nesting_salsa
     
    129133!   chemistry module is applied
    130134! - Set the default value of nesting_salsa and nesting_offline_salsa to .TRUE.
    131 ! 
     135!
    132136! 4272 2019-10-23 15:18:57Z schwenkel
    133137! Further modularization of boundary conditions: moved boundary conditions to
     
    144148! - Reformat salsa emission data with LOD=2: size distribution given for each
    145149!   emission category
    146 ! 
     150!
    147151! 4268 2019-10-17 11:29:38Z schwenkel
    148152! Moving module specific boundary conditions from time_integration to module
    149 ! 
     153!
    150154! 4256 2019-10-07 10:08:52Z monakurppa
    151155! Document previous changes: use global variables nx, ny and nz in salsa_header
    152 ! 
     156!
    153157! 4227 2019-09-10 18:04:34Z gronemeier
    154158! implement new palm_date_time_mod
    155 ! 
     159!
    156160! 4226 2019-09-10 17:03:24Z suehring
    157161! Netcdf input routine for dimension length renamed
    158 ! 
     162!
    159163! 4182 2019-08-22 15:20:23Z scharf
    160164! Corrected "Former revisions" section
    161 ! 
     165!
    162166! 4167 2019-08-16 11:01:48Z suehring
    163 ! Changed behaviour of masked output over surface to follow terrain and ignore 
     167! Changed behaviour of masked output over surface to follow terrain and ignore
    164168! buildings (J.Resler, T.Gronemeier)
    165 ! 
     169!
    166170! 4131 2019-08-02 11:06:18Z monakurppa
    167171! - Add "salsa_" before each salsa output variable
     
    174178! - Add the z-dimension for gaseous emissions to correspond the implementation
    175179!   in the chemistry module
    176 ! 
     180!
    177181! 4118 2019-07-25 16:11:45Z suehring
    178182! - When Dirichlet condition is applied in decycling, the boundary conditions are
     
    189193!   This is done to overcome high concentration peaks due to stationary numerical
    190194!   oscillations caused by horizontal advection discretization.
    191 ! 
     195!
    192196! 4117 2019-07-25 08:54:02Z monakurppa
    193 ! Pass integer flag array as well as boundary flags to WS scalar advection 
     197! Pass integer flag array as well as boundary flags to WS scalar advection
    194198! routine
    195 ! 
     199!
    196200! 4109 2019-07-22 17:00:34Z suehring
    197 ! Slightly revise setting of boundary conditions at horizontal walls, use 
     201! Slightly revise setting of boundary conditions at horizontal walls, use
    198202! data-structure offset index instead of pre-calculate it for each facing
    199 ! 
     203!
    200204! 4079 2019-07-09 18:04:41Z suehring
    201 ! Application of monotonic flux limiter for the vertical scalar advection 
    202 ! up to the topography top (only for the cache-optimized version at the 
     205! Application of monotonic flux limiter for the vertical scalar advection
     206! up to the topography top (only for the cache-optimized version at the
    203207! moment).
    204 ! 
     208!
    205209! 4069 2019-07-01 14:05:51Z Giersch
    206 ! Masked output running index mid has been introduced as a local variable to 
     210! Masked output running index mid has been introduced as a local variable to
    207211! avoid runtime error (Loop variable has been modified) in time_integration
    208 ! 
     212!
    209213! 4058 2019-06-27 15:25:42Z knoop
    210214! Bugfix: to_be_resorted was uninitialized in case of s_H2O in 3d_data_averaging
    211 ! 
     215!
    212216! 4012 2019-05-31 15:19:05Z monakurppa
    213217! Merge salsa branch to trunk. List of changes:
     
    221225! - stuff from salsa_util_mod.f90 moved into salsa_mod.f90
    222226! - calls for closing the netcdf input files added
    223 ! 
     227!
    224228! 3956 2019-05-07 12:32:52Z monakurppa
    225229! - Conceptual bug in depo_surf correct for urban and land surface model
     
    229233!   salsa_exchange_horiz_bounds after calling salsa_driver only when needed
    230234!   (i.e. every dt_salsa).
    231 ! 
     235!
    232236! 3924 2019-04-23 09:33:06Z monakurppa
    233237! Correct a bug introduced by the previous update.
    234 ! 
     238!
    235239! 3899 2019-04-16 14:05:27Z monakurppa
    236240! - remove unnecessary error / location messages
     
    239243!
    240244! 3885 2019-04-11 11:29:34Z kanani
    241 ! Changes related to global restructuring of location messages and introduction 
     245! Changes related to global restructuring of location messages and introduction
    242246! of additional debug messages
    243 ! 
     247!
    244248! 3876 2019-04-08 18:41:49Z knoop
    245249! Introduced salsa_actions module interface
    246 ! 
     250!
    247251! 3871 2019-04-08 14:38:39Z knoop
    248252! Major changes in formatting, performance and data input structure (see branch
     
    255259!   surface_aerosol_flux, aerosol_flux_dpg/sigmag/mass_fracs_a/mass_fracs_b.
    256260! - All emissions are now implemented as surface fluxes! No 3D sources anymore.
    257 ! - Update the emission information by calling salsa_emission_update if 
     261! - Update the emission information by calling salsa_emission_update if
    258262!   skip_time_do_salsa >= time_since_reference_point and
    259263!   next_aero_emission_update <= time_since_reference_point
     
    280284! - Removed tailing white spaces and unused variables
    281285! - Change error message to start by PA instead of SA
    282 ! 
     286!
    283287! 3833 2019-03-28 15:04:04Z forkel
    284 ! added USE chem_gasphase_mod for nvar, nspec and spc_names 
    285 ! 
     288! added USE chem_gasphase_mod for nvar, nspec and spc_names
     289!
    286290! 3787 2019-03-07 08:43:54Z raasch
    287291! unused variables removed
    288 ! 
     292!
    289293! 3780 2019-03-05 11:19:45Z forkel
    290294! unused variable for file index removed from rrd-subroutines parameter list
    291 ! 
     295!
    292296! 3685 2019-01-21 01:02:11Z knoop
    293297! Some interface calls moved to module_interface + cleanup
    294 ! 
     298!
    295299! 3655 2019-01-07 16:51:22Z knoop
    296300! Implementation of the PALM module interface
     
    438442        (/0.0,   0.056, 0.0,   0.056, 0.056, 0.042, 0.056, -99., 0.042,0.014,0.056, -99., -99., -99., 0.056/)
    439443!
    440 !-- Constants for the dry deposition model by Zhang et al. (2001): 
    441 !-- empirical constants "alpha" and "gamma" and characteristic radius "A" for 
     444!-- Constants for the dry deposition model by Zhang et al. (2001):
     445!-- empirical constants "alpha" and "gamma" and characteristic radius "A" for
    442446!-- each land use category (15) and season (5)
    443447    REAL(wp), DIMENSION(1:15), PARAMETER :: alpha_z01 = &
     
    445449    REAL(wp), DIMENSION(1:15), PARAMETER :: gamma_z01 = &
    446450        (/0.56, 0.58, 0.56, 0.56, 0.56, 0.54, 0.54, 0.54, 0.54, 0.54, 0.54, 0.54, 0.50, 0.50, 0.56/)
    447     REAL(wp), DIMENSION(1:15,1:5), PARAMETER :: A_z01 =  RESHAPE( (/& 
     451    REAL(wp), DIMENSION(1:15,1:5), PARAMETER :: A_z01 =  RESHAPE( (/&
    448452         2.0, 5.0, 2.0,  5.0, 5.0, 2.0, 2.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC1
    449453         2.0, 5.0, 2.0,  5.0, 5.0, 2.0, 2.0, -99., -99., 10.0, 10.0, -99., -99., -99., 10.0,&  ! SC2
     
    11131117 CONTAINS
    11141118
    1115 !------------------------------------------------------------------------------!
     1119!-------------------  -----------------------------------------------------------------------------!
    11161120! Description:
    11171121! ------------
    11181122!> Parin for &salsa_par for new modules
    1119 !------------------------------------------------------------------------------!
     1123!---------------------                    ---------------------------------------------------------!
    11201124 SUBROUTINE salsa_parin
    11211125
     
    11251129    IMPLICIT NONE
    11261130
    1127     CHARACTER(LEN=80) ::  line   !< dummy string that contains the current line of parameter file
     1131    CHARACTER(LEN=100) ::  line   !< dummy string that contains the current line of parameter file
    11281132
    11291133    INTEGER(iwp) ::  i                 !< loop index
     1134    INTEGER(iwp) ::  io_status         !< status after reading the namelist file
    11301135    INTEGER(iwp) ::  max_pr_salsa_tmp  !< dummy variable
    11311136
    1132     NAMELIST /salsa_parameters/      aerosol_flux_dpg,                         &
    1133                                      aerosol_flux_mass_fracs_a,                &
    1134                                      aerosol_flux_mass_fracs_b,                &
    1135                                      aerosol_flux_sigmag,                      &
    1136                                      advect_particle_water,                    &
    1137                                      bc_aer_b,                                 &
    1138                                      bc_aer_l,                                 &
    1139                                      bc_aer_n,                                 &
    1140                                      bc_aer_r,                                 &
    1141                                      bc_aer_s,                                 &
    1142                                      bc_aer_t,                                 &
    1143                                      depo_pcm_par,                             &
    1144                                      depo_pcm_type,                            &
    1145                                      depo_surf_par,                            &
    1146                                      dpg,                                      &
    1147                                      dt_salsa,                                 &
    1148                                      emiss_factor_main,                        &
    1149                                      emiss_factor_side,                        &
    1150                                      feedback_to_palm,                         &
    1151                                      h2so4_init,                               &
    1152                                      hno3_init,                                &
    1153                                      listspec,                                 &
    1154                                      main_street_id,                           &
    1155                                      mass_fracs_a,                             &
    1156                                      mass_fracs_b,                             &
    1157                                      max_street_id,                            &
    1158                                      n_lognorm,                                &
    1159                                      nbin,                                     &
    1160                                      nesting_salsa,                            &
    1161                                      nesting_offline_salsa,                    &
    1162                                      nf2a,                                     &
    1163                                      nh3_init,                                 &
    1164                                      nj3,                                      &
    1165                                      nlcnd,                                    &
    1166                                      nlcndgas,                                 &
    1167                                      nlcndh2oae,                               &
    1168                                      nlcoag,                                   &
    1169                                      nldepo,                                   &
    1170                                      nldepo_pcm,                               &
    1171                                      nldepo_surf,                              &
    1172                                      nldistupdate,                             &
    1173                                      nsnucl,                                   &
    1174                                      ocnv_init,                                &
    1175                                      ocsv_init,                                &
    1176                                      reglim,                                   &
    1177                                      salsa,                                    &
    1178                                      salsa_emission_mode,                      &
    1179                                      season_z01,                               &
    1180                                      sigmag,                                   &
    1181                                      side_street_id,                           &
    1182                                      skip_time_do_salsa,                       &
    1183                                      surface_aerosol_flux,                     &
     1137    NAMELIST /salsa_parameters/      aerosol_flux_dpg,                                             &
     1138                                     aerosol_flux_mass_fracs_a,                                    &
     1139                                     aerosol_flux_mass_fracs_b,                                    &
     1140                                     aerosol_flux_sigmag,                                          &
     1141                                     advect_particle_water,                                        &
     1142                                     bc_aer_b,                                                     &
     1143                                     bc_aer_l,                                                     &
     1144                                     bc_aer_n,                                                     &
     1145                                     bc_aer_r,                                                     &
     1146                                     bc_aer_s,                                                     &
     1147                                     bc_aer_t,                                                     &
     1148                                     depo_pcm_par,                                                 &
     1149                                     depo_pcm_type,                                                &
     1150                                     depo_surf_par,                                                &
     1151                                     dpg,                                                          &
     1152                                     dt_salsa,                                                     &
     1153                                     emiss_factor_main,                                            &
     1154                                     emiss_factor_side,                                            &
     1155                                     feedback_to_palm,                                             &
     1156                                     h2so4_init,                                                   &
     1157                                     hno3_init,                                                    &
     1158                                     listspec,                                                     &
     1159                                     main_street_id,                                               &
     1160                                     mass_fracs_a,                                                 &
     1161                                     mass_fracs_b,                                                 &
     1162                                     max_street_id,                                                &
     1163                                     n_lognorm,                                                    &
     1164                                     nbin,                                                         &
     1165                                     nesting_salsa,                                                &
     1166                                     nesting_offline_salsa,                                        &
     1167                                     nf2a,                                                         &
     1168                                     nh3_init,                                                     &
     1169                                     nj3,                                                          &
     1170                                     nlcnd,                                                        &
     1171                                     nlcndgas,                                                     &
     1172                                     nlcndh2oae,                                                   &
     1173                                     nlcoag,                                                       &
     1174                                     nldepo,                                                       &
     1175                                     nldepo_pcm,                                                   &
     1176                                     nldepo_surf,                                                  &
     1177                                     nldistupdate,                                                 &
     1178                                     nsnucl,                                                       &
     1179                                     ocnv_init,                                                    &
     1180                                     ocsv_init,                                                    &
     1181                                     reglim,                                                       &
     1182                                     salsa,                                                        &
     1183                                     salsa_emission_mode,                                          &
     1184                                     season_z01,                                                   &
     1185                                     sigmag,                                                       &
     1186                                     side_street_id,                                               &
     1187                                     skip_time_do_salsa,                                           &
     1188                                     surface_aerosol_flux,                                         &
    11841189                                     van_der_waals_coagc
    11851190
    1186     line = ' '
    1187 !
    1188 !-- Try to find salsa package
    1189     REWIND ( 11 )
    1190     line = ' '
    1191     DO WHILE ( INDEX( line, '&salsa_parameters' ) == 0 )
    1192        READ ( 11, '(A)', END=10 )  line
    1193     ENDDO
    1194     BACKSPACE ( 11 )
    1195 !
    1196 !-- Read user-defined namelist
    1197     READ ( 11, salsa_parameters )
    1198 !
    1199 !-- Enable salsa (salsa switch in modules.f90)
    1200     salsa = .TRUE.
    1201 
    1202  10 CONTINUE
     1191
     1192!
     1193!-- Move to the beginning of the namelist file and try to find and read the namelist.
     1194    REWIND( 11 )
     1195    READ( 11, salsa_parameters, IOSTAT=io_status )
     1196
     1197!
     1198!-- Action depending on the READ status
     1199    IF ( io_status == 0 )  THEN
     1200!
     1201!--    salsa_parameters namelist was found and read correctly. Enable salsa (salsa switch in
     1202!--    modules.f90)
     1203       salsa = .TRUE.
     1204
     1205    ELSEIF ( io_status > 0 )  THEN
     1206!
     1207!--    salsa_parameters namelist was found but contained errors. Print an error message including
     1208!--    the line that caused the problem.
     1209       BACKSPACE( 11 )
     1210       READ( 11 , '(A)' ) line
     1211       CALL parin_fail_message( 'salsa_parameters', line )
     1212
     1213    ENDIF
     1214
    12031215!
    12041216!-- Update the number of output profiles
     
    12121224
    12131225 END SUBROUTINE salsa_parin
     1226
    12141227
    12151228!------------------------------------------------------------------------------!
     
    14451458
    14461459    IMPLICIT NONE
    1447  
     1460
    14481461    INTEGER(iwp), INTENT(IN) ::  io   !< Unit of the output file
    14491462!
     
    17481761!-- (number concentration (#/m3) )
    17491762!
    1750 !-- If chemistry is on, read gas phase concentrations from there. Otherwise, 
     1763!-- If chemistry is on, read gas phase concentrations from there. Otherwise,
    17511764!-- allocate salsa_gas array.
    17521765
     
    18221835       ENDDO
    18231836!
    1824 !--    Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and 
     1837!--    Vertical surfaces: northward (l=0), southward (l=1), eastward (l=2) and
    18251838!--    westward (l=3) facing
    18261839       DO  l = 0, 3
     
    19992012! Description:
    20002013! ------------
    2001 !> Initializes particle size distribution grid by calculating size bin limits 
    2002 !> and mid-size for *dry* particles in each bin. Called from salsa_initialize 
     2014!> Initializes particle size distribution grid by calculating size bin limits
     2015!> and mid-size for *dry* particles in each bin. Called from salsa_initialize
    20032016!> (only at the beginning of simulation).
    20042017!> Size distribution described using:
     
    20092022!> based on given subrange size limits and bin number.
    20102023!
    2011 !> Mona changed 06/2017: Use geometric mean diameter to describe the mean 
     2024!> Mona changed 06/2017: Use geometric mean diameter to describe the mean
    20122025!> particle diameter in a size bin, not the arithmeric mean which clearly
    2013 !> overestimates the total particle volume concentration. 
     2026!> overestimates the total particle volume concentration.
    20142027!
    20152028!> Coded by:
     
    20892102!> Initilize altitude-dependent aerosol size distributions and compositions.
    20902103!>
    2091 !> Mona added 06/2017: Correct the number and mass concentrations by normalizing 
     2104!> Mona added 06/2017: Correct the number and mass concentrations by normalizing
    20922105!< by the given total number and mass concentration.
    20932106!>
     
    22682281             CALL get_variable( id_dyn, 'Dmid', pr_dmid )
    22692282!
    2270 !--          Check whether the sectional representation conform to the one 
     2283!--          Check whether the sectional representation conform to the one
    22712284!--          applied in the model
    22722285             IF ( ANY( ABS( ( aero(1:nbins_aerosol)%dmid - pr_dmid ) /                             &
     
    23232336             message_string = 'Error in initialising mass fractions of chemical components. ' //   &
    23242337                              'Check that all chemical components are included in parameter file!'
    2325              CALL message( 'salsa_mod: aerosol_init', 'PA0606', 2, 2, 0, 6, 0 ) 
     2338             CALL message( 'salsa_mod: aerosol_init', 'PA0606', 2, 2, 0, 6, 0 )
    23262339          ENDIF
    23272340!
     
    25502563                   ENDIF
    25512564                   ib = ib+1
    2552                 ENDDO 
     2565                ENDDO
    25532566             ENDIF
    25542567          ENDDO !< k
     
    25932606! Description:
    25942607! ------------
    2595 !> Create a lognormal size distribution and discretise to a sectional 
     2608!> Create a lognormal size distribution and discretise to a sectional
    25962609!> representation.
    25972610!------------------------------------------------------------------------------!
     
    26872700!
    26882701!--          Predetermine flag to mask topography
    2689              flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     2702             flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
    26902703!
    26912704!--          Regime 2a:
     
    27172730                   IF ( prunmode == 1 )  THEN
    27182731                      aerosol_mass(ic)%init(k) = MAX( 0.0_wp, pmf2b(k) ) * ( 1.0_wp - pnf2a(k) ) * &
    2719                                                  pndist(k,ib) * pcore(ib) * prho 
     2732                                                 pndist(k,ib) * pcore(ib) * prho
    27202733                   ENDIF
    27212734                   ib = ib + 1
     
    36303643! Description:
    36313644! ------------
    3632 !> Performs necessary unit and dimension conversion between the host model and 
     3645!> Performs necessary unit and dimension conversion between the host model and
    36333646!> SALSA module, and calls the main SALSA routine.
    36343647!> Partially adobted form the original SALSA boxmodel version.
    36353648!> Now takes masses in as kg/kg from LES!! Converted to m3/m3 for SALSA
    3636 !> 05/2016 Juha: This routine is still pretty much in its original shape. 
     3649!> 05/2016 Juha: This routine is still pretty much in its original shape.
    36373650!>               It's dumb as a mule and twice as ugly, so implementation of
    36383651!>               an improved solution is necessary sooner or later.
     
    37523765!
    37533766!--    Set volume concentrations:
    3754 !--    Sulphate (SO4) or sulphuric acid H2SO4 
     3767!--    Sulphate (SO4) or sulphuric acid H2SO4
    37553768       IF ( index_so4 > 0 )  THEN
    37563769          vc = 1
     
    38203833       IF ( index_no > 0 )  THEN
    38213834          vc = 6
    3822           str = ( index_no-1 ) * nbins_aerosol + 1 
     3835          str = ( index_no-1 ) * nbins_aerosol + 1
    38233836          endi = index_no * nbins_aerosol
    38243837          ic = 1
     
    38593872       aero_old(1:nbins_aerosol)%volc(vc) = lo_aero(1:nbins_aerosol)%volc(vc)
    38603873!
    3861 !--    Number concentrations (numc) and particle sizes 
     3874!--    Number concentrations (numc) and particle sizes
    38623875!--    (dwet = wet diameter, core = dry volume)
    38633876       DO  ib = 1, nbins_aerosol
     
    41144127!
    41154128!-- Set surfaces and wall fluxes due to deposition
    4116     IF ( lsdepo  .AND.  lsdepo_surf  .AND.  prunmode == 3 )  THEN 
     4129    IF ( lsdepo  .AND.  lsdepo_surf  .AND.  prunmode == 3 )  THEN
    41174130       IF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
    41184131          CALL depo_surf( i, j, surf_def_h(0), vd, schmidt_num, kvis, in_u, .TRUE. )
     
    41894202
    41904203 END SUBROUTINE set_salsa_runtime
    4191  
     4204
    41924205!------------------------------------------------------------------------------!
    41934206! Description:
    41944207! ------------
    4195 !> Calculates the absolute temperature (using hydrostatic pressure), saturation 
    4196 !> vapour pressure and mixing ratio over water, relative humidity and air 
     4208!> Calculates the absolute temperature (using hydrostatic pressure), saturation
     4209!> vapour pressure and mixing ratio over water, relative humidity and air
    41974210!> density needed in the SALSA model.
    4198 !> NOTE, no saturation adjustment takes place -> the resulting water vapour 
     4211!> NOTE, no saturation adjustment takes place -> the resulting water vapour
    41994212!> mixing ratio can be supersaturated, allowing the microphysical calculations
    42004213!> in SALSA.
     
    42544267! Description:
    42554268! ------------
    4256 !> Calculates ambient sizes of particles by equilibrating soluble fraction of 
     4269!> Calculates ambient sizes of particles by equilibrating soluble fraction of
    42574270!> particles with water using the ZSR method (Stokes and Robinson, 1966).
    42584271!> Method:
     
    42604273!> - (ammonium) sulphate (100%)
    42614274!> - sea salt (100 %)
    4262 !> - organic carbon (epsoc * 100%) 
     4275!> - organic carbon (epsoc * 100%)
    42634276!> Exact thermodynamic considerations neglected.
    4264 !> - If particles contain no sea salt, calculation according to sulphate 
     4277!> - If particles contain no sea salt, calculation according to sulphate
    42654278!>   properties
    4266 !> - If contain sea salt but no sulphate, calculation according to sea salt 
     4279!> - If contain sea salt but no sulphate, calculation according to sea salt
    42674280!>   properties
    4268 !> - If contain both sulphate and sea salt -> the molar fraction of these 
     4281!> - If contain both sulphate and sea salt -> the molar fraction of these
    42694282!>   compounds determines which one of them is used as the basis of calculation.
    4270 !> If sulphate and sea salt coexist in a particle, it is assumed that the Cl is 
    4271 !> replaced by sulphate; thus only either sulphate + organics or sea salt + 
     4283!> If sulphate and sea salt coexist in a particle, it is assumed that the Cl is
     4284!> replaced by sulphate; thus only either sulphate + organics or sea salt +
    42724285!> organics is included in the calculation of soluble fraction.
    4273 !> Molality parameterizations taken from Table 1 of Tang: Thermodynamic and 
    4274 !> optical properties of mixed-salt aerosols of atmospheric importance, 
     4286!> Molality parameterizations taken from Table 1 of Tang: Thermodynamic and
     4287!> optical properties of mixed-salt aerosols of atmospheric importance,
    42754288!> J. Geophys. Res., 102 (D2), 1883-1893 (1997)
    42764289!
    42774290!> Coded by:
    4278 !> Hannele Korhonen (FMI) 2005 
     4291!> Hannele Korhonen (FMI) 2005
    42794292!> Harri Kokkola (FMI) 2006
    42804293!> Matti Niskanen(FMI) 2012
     
    42824295!> Modified for the new aerosol datatype, Juha Tonttila (FMI) 2014
    42834296!
    4284 !> fxm: should sea salt form a solid particle when prh is very low (even though 
     4297!> fxm: should sea salt form a solid particle when prh is very low (even though
    42854298!> it could be mixed with e.g. sulphate)?
    42864299!> fxm: crashes if no sulphate or sea salt
     
    43354348          zvpart(6:7) = paero(ib)%volc(6:7) / paero(ib)%numc
    43364349!
    4337 !--       Total volume and wet diameter of one dry particle 
     4350!--       Total volume and wet diameter of one dry particle
    43384351          zcore = SUM( zvpart(1:2) )
    43394352          zdwet = paero(ib)%dwet
     
    43454358             zaw = MAX( 1.0E-3_wp, zrh / zke ) ! To avoid underflow
    43464359!
    4347 !--          Binary molalities (mol/kg): 
     4360!--          Binary molalities (mol/kg):
    43484361!--          Sulphate
    43494362             zbinmol(1) = 1.1065495E+2_wp - 3.6759197E+2_wp * zaw + 5.0462934E+2_wp * zaw**2 -     &
     
    43674380                       zcore / api6 )**0.33333333_wp
    43684381!
    4369 !--          Kelvin effect (Eq. 10.85 in in Seinfeld and Pandis (2006)). Avoid 
     4382!--          Kelvin effect (Eq. 10.85 in in Seinfeld and Pandis (2006)). Avoid
    43704383!--          overflow.
    43714384             zke = EXP( MIN( 50.0_wp, 4.0_wp * surfw0 * amvh2so4 / ( abo * ptemp *  zdwet ) ) )
    43724385
    43734386             counti = counti + 1
    4374              IF ( counti > 1000 )  THEN 
     4387             IF ( counti > 1000 )  THEN
    43754388                message_string = 'Subrange 1: no convergence!'
    43764389                CALL message( 'salsa_mod: equilibration', 'PA0617', 1, 2, 0, 6, 0 )
     
    43784391          ENDDO
    43794392!
    4380 !--       Instead of lwc, use the volume concentration of water from now on 
     4393!--       Instead of lwc, use the volume concentration of water from now on
    43814394!--       (easy to convert...)
    43824395          paero(ib)%volc(8) = zlwc / arhoh2o
     
    44384451                             6.210577919E+1_wp * zaw**2 + 5.510176187E+2_wp * zaw**3 -             &
    44394452                             1.460055286E+3_wp * zaw**4 + 1.894467542E+3_wp * zaw**5 -             &
    4440                              1.220611402E+3_wp * zaw**6 + 3.098597737E+2_wp * zaw**7 
     4453                             1.220611402E+3_wp * zaw**6 + 3.098597737E+2_wp * zaw**7
    44414454!--             Sea salt (natrium chloride)
    44424455                zbinmol(5) = 5.875248E+1_wp - 1.8781997E+2_wp * zaw + 2.7211377E+2_wp * zaw**2 -   &
     
    44574470
    44584471                counti = counti + 1
    4459                 IF ( counti > 1000 )  THEN 
     4472                IF ( counti > 1000 )  THEN
    44604473                   message_string = 'Subrange 2: no convergence!'
    44614474                CALL message( 'salsa_mod: equilibration', 'PA0618', 1, 2, 0, 6, 0 )
     
    44824495!> Description:
    44834496!> ------------
    4484 !> Calculation of the settling velocity vc (m/s) per aerosol size bin and 
     4497!> Calculation of the settling velocity vc (m/s) per aerosol size bin and
    44854498!> deposition on plant canopy (lsdepo_pcm).
    44864499!
     
    47504763!> Calculate the dry deposition on horizontal and vertical surfaces. Implement
    47514764!> as a surface flux.
    4752 !> @todo aerodynamic resistance ignored for now (not important for 
     4765!> @todo aerodynamic resistance ignored for now (not important for
    47534766!        high-resolution simulations)
    47544767!------------------------------------------------------------------------------!
     
    50105023! ------------
    50115024!> Calculates particle loss and change in size distribution due to (Brownian)
    5012 !> coagulation. Only for particles with dwet < 30 micrometres. 
     5025!> coagulation. Only for particles with dwet < 30 micrometres.
    50135026!
    50145027!> Method:
    50155028!> Semi-implicit, non-iterative method: (Jacobson, 1994)
    50165029!> Volume concentrations of the smaller colliding particles added to the bin of
    5017 !> the larger colliding particles. Start from first bin and use the updated 
     5030!> the larger colliding particles. Start from first bin and use the updated
    50185031!> number and volume for calculation of following bins. NB! Our bin numbering
    50195032!> does not follow particle size in subrange 2.
     
    50285041!> Exact coagulation coefficients for each pressure level are scaled according
    50295042!> to current particle wet size (linear scaling).
    5030 !> Bins are organized in terms of the dry size of the condensation nucleus, 
     5043!> Bins are organized in terms of the dry size of the condensation nucleus,
    50315044!> while coagulation kernell is calculated with the actual hydrometeor
    50325045!> size.
     
    50785091!--    CoagSink ~ Dp in continuum subrange --> 'effective' number conc. of coarse particles
    50795092
    5080 !-- 2) Updating coagulation coefficients 
     5093!-- 2) Updating coagulation coefficients
    50815094!
    50825095!-- Aerosol mass (kg). Density of 1500 kg/m3 assumed
     
    52685281    mfp = ( 1.656E-10_wp * temp + 1.828E-8_wp ) * ( p_0 + 1325.0_wp ) / pres
    52695282!
    5270 !-- 2) Slip correction factor for small particles 
     5283!-- 2) Slip correction factor for small particles
    52715284    knud = 2.0_wp * EXP( LOG(mfp) - LOG(diam) )! Knudsen number for air (15.23)
    52725285!
     
    53255338! Description:
    53265339! ------------
    5327 !> Calculates the change in particle volume and gas phase 
     5340!> Calculates the change in particle volume and gas phase
    53285341!> concentrations due to nucleation, condensation and dissolutional growth.
    53295342!
    53305343!> Sulphuric acid and organic vapour: only condensation and no evaporation.
    53315344!
    5332 !> New gas and aerosol phase concentrations calculated according to Jacobson 
     5345!> New gas and aerosol phase concentrations calculated according to Jacobson
    53335346!> (1997): Numerical techniques to solve condensational and dissolutional growth
    53345347!> equations when growth is coupled to reversible reactions, Aerosol Sci. Tech.,
     
    53365349!
    53375350!> Following parameterization has been used:
    5338 !> Molecular diffusion coefficient of condensing vapour (m2/s) 
     5351!> Molecular diffusion coefficient of condensing vapour (m2/s)
    53395352!> (Reid et al. (1987): Properties of gases and liquids, McGraw-Hill, New York.)
    53405353!> D = {1.d-7*sqrt(1/M_air + 1/M_gas)*T^1.75} / &
     
    53435356!> d_air = 19.70  : diffusion volume of air
    53445357!> M_h2so4 = 98.08 : molar mass of h2so4 (g/mol)
    5345 !> d_h2so4 = 51.96  : diffusion volume of h2so4 
     5358!> d_h2so4 = 51.96  : diffusion volume of h2so4
    53465359!
    53475360!> Called from main aerosol model
     
    54475460       zknud(ss:ee) = 2.0_wp * zmfp / paero(ss:ee)%dwet
    54485461!
    5449 !--    Transitional correction factor: aerosol + gas (the semi-empirical Fuchs- Sutugin 
     5462!--    Transitional correction factor: aerosol + gas (the semi-empirical Fuchs- Sutugin
    54505463!--    interpolation function (Fuchs and Sutugin, 1971))
    54515464       zbeta = ( zknud + 1.0_wp ) / ( 0.377_wp * zknud + 1.0_wp + 4.0_wp / ( 3.0_wp * massacc ) *  &
     
    54595472                 * paero(start_subrange_1a:start_subrange_1a+1)%dwet)
    54605473!
    5461 !--    Collision rate (mass-transfer coefficient): gases on aerosols (1/s) (Eq. 16.64 in 
     5474!--    Collision rate (mass-transfer coefficient): gases on aerosols (1/s) (Eq. 16.64 in
    54625475!--    Jacobson (2005))
    54635476       ss = start_subrange_1a
     
    54755488!--    5) Changes in gas-phase concentrations and particle volume
    54765489!
    5477 !--    5.1) Organic vapours 
     5490!--    5.1) Organic vapours
    54785491!
    54795492!--    5.1.1) Non-volatile organic compound: condenses onto all bins
     
    55275540!
    55285541!--       Change in gas concentration (#/m3)
    5529           zdvap3 = pcocsv - zcvap_new3 
     5542          zdvap3 = pcocsv - zcvap_new3
    55305543!
    55315544!--       Updated gas concentration (#/m3)
     
    55905603!
    55915604!-- Condensation of water vapour
    5592     IF ( lscndh2oae )  THEN 
     5605    IF ( lscndh2oae )  THEN
    55935606       CALL gpparth2o( paero, ptemp, ppres, pcs, pcw, ptstep )
    55945607    ENDIF
     
    56005613! ------------
    56015614!> Calculates the particle number and volume increase, and gas-phase
    5602 !> concentration decrease due to nucleation subsequent growth to detectable size 
     5615!> concentration decrease due to nucleation subsequent growth to detectable size
    56035616!> of 3 nm.
    56045617!
     
    56595672    REAL(wp) ::  zdelta_vap   !< change of H2SO4 and organic vapour concentration (#/m3)
    56605673    REAL(wp) ::  zdfvap       !< air diffusion coefficient (m2/s)
    5661     REAL(wp) ::  zdmean       !< mean diameter of existing particles (m) 
     5674    REAL(wp) ::  zdmean       !< mean diameter of existing particles (m)
    56625675    REAL(wp) ::  zeta         !< constant: proportional to ratio of CS/GR (m)
    56635676                              !< (condensation sink / growth rate)
     
    56745687    REAL(wp) ::  zlambda      !< parameter for adjusting the growth rate due to self-coagulation
    56755688    REAL(wp) ::  zm_c         !< particle mass (kg) for c = critical (1nm)
    5676     REAL(wp) ::  zm_para      !< Parameter m for calculating the coagulation sink (Eq. 5&6 in 
     5689    REAL(wp) ::  zm_para      !< Parameter m for calculating the coagulation sink (Eq. 5&6 in
    56775690                              !< Lehtinen et al. 2007)
    56785691    REAL(wp) ::  zm_x         !< particle mass (kg) for x = 3nm
     
    56845697    REAL(wp) ::  znsa         !< number of H2SO4 molecules in critical cluster
    56855698
    5686     REAL(wp), INTENT(in) ::  pc_nh3   !< ammonia concentration (#/m3) 
     5699    REAL(wp), INTENT(in) ::  pc_nh3   !< ammonia concentration (#/m3)
    56875700    REAL(wp), INTENT(in) ::  pc_ocnv  !< conc. of non-volatile OC (#/m3)
    56885701    REAL(wp), INTENT(in) ::  pc_sa    !< sulphuric acid conc. (#/m3)
     
    58125825          znsa    = 1.0_wp
    58135826!
    5814 !--    Heteromolecular nucleation, J~[H2SO4]*[ORG] 
     5827!--    Heteromolecular nucleation, J~[H2SO4]*[ORG]
    58155828!--    (See Paasonen et al. (2010), Atmos. Chem. Phys., 10, 11223-11242.)
    58165829       CASE(7)
     
    58645877!
    58655878!-- 2.1) Check that there is enough H2SO4 and organic vapour to produce the nucleation
    5866     IF ( nsnucl <= 4 )  THEN 
     5879    IF ( nsnucl <= 4 )  THEN
    58675880!
    58685881!--    If the chosen nucleation scheme is 1-4, nucleation occurs only due to H2SO4. All of the total
     
    58815894          pxocnv = 0.0_wp
    58825895       ELSE
    5883           pxsa   = pc_sa * znsa / ( pc_sa * znsa + pc_ocnv * znoc ) 
     5896          pxsa   = pc_sa * znsa / ( pc_sa * znsa + pc_ocnv * znoc )
    58845897          pxocnv = pc_ocnv * znoc / ( pc_sa * znsa + pc_ocnv * znoc )
    58855898       ENDIF
     
    60096022                   ( 3.0_wp * z_r_c2 * zgamma_f_2 ) - z_r_c2
    60106023       zomega_2x = ( ( z_r_x2 + zgamma_f_2 )**3 - ( z_r_x2**2 + zgamma_f_2 )**1.5_wp ) /           &
    6011                    ( 3.0_wp * z_r_x2 * zgamma_f_2 ) - z_r_x2 
     6024                   ( 3.0_wp * z_r_x2 * zgamma_f_2 ) - z_r_x2
    60126025!
    60136026!--    The distance (m) at which the two fluxes are matched (condensation and coagulation sinks)
     
    60256038       zcoags_x = MAX( 1.0E-20_wp, SUM( z_k_x2 * paero(:)%numc ) )
    60266039!
    6027 !--    Parameter m for calculating the coagulation sink onto background particles (Eq. 5&6 in 
     6040!--    Parameter m for calculating the coagulation sink onto background particles (Eq. 5&6 in
    60286041!--    Lehtinen et al. 2007)
    60296042       zm_para = LOG( zcoags_x / zcoags_c ) / LOG( reglim(1) / zdcrit )
     
    60416054       ELSEIF ( nj3 == 3 )  THEN  ! Anttila et al. (2010): coagulation sink and self-coag.
    60426055!
    6043 !--       If air is polluted, the self-coagulation becomes important. Self-coagulation of small 
     6056!--       If air is polluted, the self-coagulation becomes important. Self-coagulation of small
    60446057!--       particles < 3 nm.
    60456058!
     
    61986211!
    61996212!-- Nucleation rate in #/(cm3 s)
    6200     pnuc_rate = EXP( pnuc_rate ) 
     6213    pnuc_rate = EXP( pnuc_rate )
    62016214!
    62026215!-- Check the validity of parameterization
    6203     IF ( pnuc_rate < 1.0E-7_wp )  THEN 
     6216    IF ( pnuc_rate < 1.0E-7_wp )  THEN
    62046217       pnuc_rate = 0.0_wp
    62056218       pd_crit   = 1.0E-9_wp
     
    62526265!
    62536266!-- 6) Organic compounds not involved when binary nucleation is assumed
    6254     pn_crit_ocnv = 0.0_wp   ! number of organic molecules 
     6267    pn_crit_ocnv = 0.0_wp   ! number of organic molecules
    62556268    pk_sa        = 1.0_wp   ! if = 1, H2SO4 involved in nucleation
    62566269    pk_ocnv      = 0.0_wp   ! if = 1, organic compounds involved
     
    62996312
    63006313 END SUBROUTINE binnucl
    6301  
     6314
    63026315!------------------------------------------------------------------------------!
    63036316! Description:
     
    63536366    zlogsa  = LOG( pc_sa )
    63546367!
    6355 !-- 2) Nucleation rate (Eq. 7 in Napari et al., 2002: Parameterization of 
     6368!-- 2) Nucleation rate (Eq. 7 in Napari et al., 2002: Parameterization of
    63566369!--    ternary nucleation of sulfuric acid - ammonia - water.
    63576370    zlnj = - 84.7551114741543_wp + 0.3117595133628944_wp * prh +                                   &
     
    64616474! Description:
    64626475! ------------
    6463 !> Function z_n_nuc_tayl is connected to the calculation of self-coagualtion of 
     6476!> Function z_n_nuc_tayl is connected to the calculation of self-coagualtion of
    64646477!> small particles. It calculates number of the particles in the size range
    6465 !> [zdcrit,dx] using Taylor-expansion (please note that the expansion is not 
     6478!> [zdcrit,dx] using Taylor-expansion (please note that the expansion is not
    64666479!> valid for certain rational numbers, e.g. -4/3 and -3/2)
    64676480!------------------------------------------------------------------------------!
     
    65066519! Description:
    65076520! ------------
    6508 !> Calculates the condensation of water vapour on aerosol particles. Follows the 
     6521!> Calculates the condensation of water vapour on aerosol particles. Follows the
    65096522!> analytical predictor method by Jacobson (2005).
    6510 !> For equations, see Jacobson (2005), Fundamentals of atmospheric modelling 
     6523!> For equations, see Jacobson (2005), Fundamentals of atmospheric modelling
    65116524!> (2nd edition).
    65126525!------------------------------------------------------------------------------!
     
    66906703! Description:
    66916704! ------------
    6692 !> Calculates the activity coefficient of liquid water 
     6705!> Calculates the activity coefficient of liquid water
    66936706!------------------------------------------------------------------------------!
    66946707 REAL(wp) FUNCTION acth2o( ppart, pcw )
     
    67236736! Description:
    67246737! ------------
    6725 !> Calculates the dissolutional growth of particles (i.e. gas transfers to a 
    6726 !> particle surface and dissolves in liquid water on the surface). Treated here 
    6727 !> as a non-equilibrium (time-dependent) process. Gases: HNO3 and NH3 
     6738!> Calculates the dissolutional growth of particles (i.e. gas transfers to a
     6739!> particle surface and dissolves in liquid water on the surface). Treated here
     6740!> as a non-equilibrium (time-dependent) process. Gases: HNO3 and NH3
    67286741!> (Chapter 17.14 in Jacobson, 2005).
    67296742!
    6730 !> Called from subroutine condensation. 
     6743!> Called from subroutine condensation.
    67316744!> Coded by:
    67326745!> Harri Kokkola (FMI)
    6733 !------------------------------------------------------------------------------! 
     6746!------------------------------------------------------------------------------!
    67346747 SUBROUTINE gpparthno3( ppres, ptemp, paero, pghno3, pgnh3, pcw, pcs, pbeta, ptstep )
    67356748
     
    72707283                                         !< 1: HNO3, 2: HCL, 3: NH4+/H+ (NH3), 4: HHSO4**2/H2SO4,
    72717284                                         !< 5: H2SO4**3/HHSO4**2, 6: NH4HSO2, 7: HHSO4
    7272     REAL(wp), DIMENSION(:) ::  ions      !< ion molarities (mol/m3): 1: H+, 2: NH4+, 3: Na+, 
     7285    REAL(wp), DIMENSION(:) ::  ions      !< ion molarities (mol/m3): 1: H+, 2: NH4+, 3: Na+,
    72737286                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
    7274     REAL(wp), DIMENSION(7) ::  ions_mol  !< ion molalities (mol/kg): 1: H+, 2: NH4+, 3: Na+, 
     7287    REAL(wp), DIMENSION(7) ::  ions_mol  !< ion molalities (mol/kg): 1: H+, 2: NH4+, 3: Na+,
    72757288                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
    7276     REAL(wp), DIMENSION(:) ::  mols_out  !< ion molality output (mol/kg): 1: H+, 2: NH4+, 3: Na+, 
     7289    REAL(wp), DIMENSION(:) ::  mols_out  !< ion molality output (mol/kg): 1: H+, 2: NH4+, 3: Na+,
    72777290                                         !< 4: SO4(2-), 5: HSO4-, 6: NO3-, 7: Cl-
    72787291!
     
    75607573                      sodium_nitrate_eq_frac * nano3_h2so4 + sodium_chloride_eq_frac * nacl_h2so4
    75617574
    7562        gamma_h2so4 = EXP( ln_h2so4_act )    ! molal activity coefficient 
     7575       gamma_h2so4 = EXP( ln_h2so4_act )    ! molal activity coefficient
    75637576!
    75647577!--    Export activity coefficients
     
    75897602       ENDIF
    75907603!
    7591 !--    Calculate the new hydrogen ion, bisulphate ion and sulphate ion 
     7604!--    Calculate the new hydrogen ion, bisulphate ion and sulphate ion
    75927605!--    concentration
    75937606       h_real    = ions(1)
     
    76157628!-- 4) ACTIVITY COEFFICIENTS -for vapour pressures of HNO3,HCL and NH3
    76167629!
    7617 !-- This section evaluates activity coefficients and vapour pressures using the water content 
     7630!-- This section evaluates activity coefficients and vapour pressures using the water content
    76187631!-- calculated above) for each inorganic condensing species: a - HNO3, b - NH3, c - HCL.
    7619 !-- The following procedure is used: Zaveri et al (2005) found that one could express the variation 
     7632!-- The following procedure is used: Zaveri et al (2005) found that one could express the variation
    76207633!-- of activity coefficients linearly in log-space if equivalent mole fractions were used.
    76217634!-- So, by a taylor series expansion LOG( activity coefficient ) =
     
    79277940!> Update the particle size distribution. Put particles into corrects bins.
    79287941!>
    7929 !> Moving-centre method assumed, i.e. particles are allowed to grow to their 
    7930 !> exact size as long as they are not crossing the fixed diameter bin limits. 
    7931 !> If the particles in a size bin cross the lower or upper diameter limit, they 
     7942!> Moving-centre method assumed, i.e. particles are allowed to grow to their
     7943!> exact size as long as they are not crossing the fixed diameter bin limits.
     7944!> If the particles in a size bin cross the lower or upper diameter limit, they
    79327945!> are all moved to the adjacent diameter bin and their volume is averaged with
    7933 !> the particles in the new bin, which then get a new diameter. 
    7934 !
    7935 !> Moving-centre method minimises numerical diffusion. 
     7946!> the particles in the new bin, which then get a new diameter.
     7947!
     7948!> Moving-centre method minimises numerical diffusion.
    79367949!------------------------------------------------------------------------------!
    79377950 SUBROUTINE distr_update( paero )
     
    79968009!
    79978010!--          If size bin has not grown, cycle.
    7998 !--          Changed by Mona: compare to the arithmetic mean volume, as done originally. Now 
    7999 !--          particle volume is derived from the geometric mean diameter, not arithmetic (see 
     8011!--          Changed by Mona: compare to the arithmetic mean volume, as done originally. Now
     8012!--          particle volume is derived from the geometric mean diameter, not arithmetic (see
    80008013!--          SUBROUTINE set_sizebins).
    80018014             IF ( zvpart <= api6 * ( ( aero(ib)%vhilim + aero(ib)%vlolim ) / ( 2.0_wp * api6 ) ) ) &
     
    95379550    REAL(wp), DIMENSION(:), INTENT(out) ::  mconc  !< total dry or wet mass concentration
    95389551
    9539 !-- Number of components 
     9552!-- Number of components
    95409553    IF ( itype == 'dry' )  THEN
    9541        iend = prtcl%ncomp - 1 
     9554       iend = prtcl%ncomp - 1
    95429555    ELSE IF ( itype == 'wet' )  THEN
    95439556       iend = prtcl%ncomp
     
    1002710040                   message_string = 'end_time of the simulation exceeds the time dimension in ' // &
    1002810041                                    'the salsa input file.'
    10029                    CALL message( 'salsa_emission_setup', 'PA0692', 1, 2, 0, 6, 0 ) 
     10042                   CALL message( 'salsa_emission_setup', 'PA0692', 1, 2, 0, 6, 0 )
    1003010043                ENDIF
    1003110044!
     
    1009310106                inn = def_modes%cat_input_to_model(in)
    1009410107!
    10095 !--             Calculate the number concentration (1/m3) of a log-normal size distribution 
     10108!--             Calculate the number concentration (1/m3) of a log-normal size distribution
    1009610109!--             following Jacobson (2005): Eq 13.25.
    1009710110                def_modes%ntot_table = 6.0_wp * def_modes%pm_frac_table(:,inn) / ( pi *            &
     
    1064310656                                          MAX( time_since_reference_point, 0.0_wp ) ), DIM = 1 ) - 1
    1064410657!
    10645 !--    Allocate the data input array always before reading in the data and deallocate after (NOTE 
     10658!--    Allocate the data input array always before reading in the data and deallocate after (NOTE
    1064610659!--    that "preprocessed" input data array is applied now here)
    1064710660       ALLOCATE( dum_var_5d(1,1,nys:nyn,nxl:nxr,1:chem_emission_att%n_emiss_species) )
     
    1176211775!
    1176311776!--                         Diameter in micrometres
    11764                             mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp 
     11777                            mean_d = 1.0E+6_wp * ra_dry(k,j,i,ib) * 2.0_wp
    1176511778!
    1176611779!--                         Deposition factor: alveolar
     
    1211212125                   DO  k = nzb_do, nzt_do
    1211312126                      local_pf(i,j,k) = MERGE( nbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
    12114                                                BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12127                                               BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1211512128                   ENDDO
    1211612129                ENDDO
     
    1214612159                   DO  k = nzb_do, nzt_do
    1214712160                      local_pf(i,j,k) = MERGE( mbins_av(k,j,i,ib), REAL( fill_value, KIND = wp ),  &
    12148                                                BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12161                                               BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1214912162                   ENDDO
    1215012163                ENDDO
     
    1222512238                      DO  k = nzb_do, nzt_do
    1222612239                         local_pf(i,j,k) = MERGE( ldsa_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12227                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12240                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1222812241                      ENDDO
    1222912242                   ENDDO
     
    1225612269                      DO  k = nzb_do, nzt_do
    1225712270                         local_pf(i,j,k) = MERGE( nufp_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12258                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12271                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1225912272                      ENDDO
    1226012273                   ENDDO
     
    1228512298                      DO  k = nzb_do, nzt_do
    1228612299                         local_pf(i,j,k) = MERGE( ntot_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12287                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12300                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1228812301                      ENDDO
    1228912302                   ENDDO
     
    1230512318                         ENDDO
    1230612319                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12307                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12320                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1230812321                      ENDDO
    1230912322                   ENDDO
     
    1231812331                      DO  k = nzb_do, nzt_do
    1231912332                         local_pf(i,j,k) = MERGE( pm01_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12320                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12333                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1232112334                      ENDDO
    1232212335                   ENDDO
     
    1233812351                         ENDDO
    1233912352                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12340                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12353                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1234112354                      ENDDO
    1234212355                   ENDDO
     
    1235112364                      DO  k = nzb_do, nzt_do
    1235212365                         local_pf(i,j,k) = MERGE( pm25_av(k,j,i), REAL( fill_value, KIND = wp ),   &
    12353                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12366                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1235412367                      ENDDO
    1235512368                   ENDDO
     
    1237112384                         ENDDO
    1237212385                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12373                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12386                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1237412387                      ENDDO
    1237512388                   ENDDO
     
    1240212415                            ENDDO
    1240312416                            local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),      &
    12404                                                      BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12417                                                     BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1240512418                         ENDDO
    1240612419                      ENDDO
     
    1243412447                         ENDDO
    1243512448                         local_pf(i,j,k) = MERGE( temp_bin, REAL( fill_value, KIND = wp ),         &
    12436                                                   BTEST( wall_flags_total_0(k,j,i), 0 ) ) 
     12449                                                  BTEST( wall_flags_total_0(k,j,i), 0 ) )
    1243712450                      ENDDO
    1243812451                   ENDDO
     
    1258512598                   ENDDO
    1258612599                ENDDO
    12587              ELSE 
     12600             ELSE
    1258812601                DO  i = 1, mask_size_l(mid,1)
    1258912602                   DO  j = 1, mask_size_l(mid,2)
     
    1266612679                      ENDDO
    1266712680                   ENDDO
    12668                 ELSE 
     12681                ELSE
    1266912682                   DO  i = 1, mask_size_l(mid,1)
    1267012683                      DO  j = 1, mask_size_l(mid,2)
     
    1275512768                      ENDDO
    1275612769                   ENDDO
    12757                 ENDDO 
     12770                ENDDO
    1275812771                IF ( .NOT. mask_surface(mid) )  THEN
    1275912772                   DO  i = 1, mask_size_l(mid,1)
     
    1276412777                      ENDDO
    1276512778                   ENDDO
    12766                 ELSE 
     12779                ELSE
    1276712780                   DO  i = 1, mask_size_l(mid,1)
    1276812781                      DO  j = 1, mask_size_l(mid,2)
     
    1280712820                      ENDDO
    1280812821                   ENDDO
    12809                 ENDDO 
     12822                ENDDO
    1281012823                IF ( .NOT. mask_surface(mid) )  THEN
    1281112824                   DO  i = 1, mask_size_l(mid,1)
     
    1281612829                      ENDDO
    1281712830                   ENDDO
    12818                 ELSE 
     12831                ELSE
    1281912832                   DO  i = 1, mask_size_l(mid,1)
    1282012833                      DO  j = 1, mask_size_l(mid,2)
     
    1286812881                      ENDDO
    1286912882                   ENDDO
    12870                 ELSE 
     12883                ELSE
    1287112884                   DO  i = 1, mask_size_l(mid,1)
    1287212885                      DO  j = 1, mask_size_l(mid,2)
     
    1291112924                      ENDDO
    1291212925                   ENDDO
    12913                 ENDDO 
     12926                ENDDO
    1291412927                IF ( .NOT. mask_surface(mid) )  THEN
    1291512928                   DO  i = 1, mask_size_l(mid,1)
     
    1292012933                      ENDDO
    1292112934                   ENDDO
    12922                 ELSE 
     12935                ELSE
    1292312936                   DO  i = 1, mask_size_l(mid,1)
    1292412937                      DO  j = 1, mask_size_l(mid,2)
     
    1309813111! Description:
    1309913112! ------------
    13100 !> Creates index tables for different (aerosol) components 
     13113!> Creates index tables for different (aerosol) components
    1310113114!------------------------------------------------------------------------------!
    1310213115 SUBROUTINE component_index_constructor( self, ncomp, nlist, listcomp )
     
    1358313596          message_string = 'end_time of the simulation exceeds the time dimension in the dynamic'//&
    1358413597                           ' input file.'
    13585           CALL message( 'salsa_nesting_offl_init', 'PA0690', 1, 2, 0, 6, 0 ) 
     13598          CALL message( 'salsa_nesting_offl_init', 'PA0690', 1, 2, 0, 6, 0 )
    1358613599       ENDIF
    1358713600
     
    1374713760          CALL message( 'salsa_mod: salsa_nesting_offl_input', 'PA0693', 2, 2, 0, 6, 0 )
    1374813761       ENDIF
    13749        
     13762
    1375013763       CALL close_input_file( salsa_nest_offl%id_dynamic )
    1375113764#endif
Note: See TracChangeset for help on using the changeset viewer.