Ignore:
Timestamp:
Oct 24, 2019 1:40:54 PM (4 years ago)
Author:
monakurppa
Message:

Add logical switched nesting_chem and nesting_offline_chem

File:
1 edited

Legend:

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

    r4272 r4273  
    2626! -----------------
    2727! $Id$
     28! - Rename nest_salsa to nesting_salsa
     29! - Correct some errors in boundary condition flags
     30! - Add a check for not trying to output gas concentrations in salsa if the
     31!   chemistry module is applied
     32! - Set the default value of nesting_salsa and nesting_offline_salsa to .TRUE.
     33!
     34! 4272 2019-10-23 15:18:57Z schwenkel
    2835! Further modularization of boundary conditions: moved boundary conditions to
    2936! respective modules
     
    454461    LOGICAL ::  include_emission        = .FALSE.  !< Include or not emissions
    455462    LOGICAL ::  feedback_to_palm        = .FALSE.  !< Allow feedback due to condensation of H2O
    456     LOGICAL ::  nest_salsa              = .FALSE.  !< Apply nesting for salsa
    457     LOGICAL ::  nesting_offline_salsa   = .FALSE.  !< Apply offline nesting for salsa
     463    LOGICAL ::  nesting_salsa           = .TRUE.   !< Apply nesting for salsa
     464    LOGICAL ::  nesting_offline_salsa   = .TRUE.   !< Apply offline nesting for salsa
    458465    LOGICAL ::  no_insoluble            = .FALSE.  !< Exclude insoluble chemical components
    459466    LOGICAL ::  read_restart_data_salsa = .FALSE.  !< Read restart data for salsa
     
    652659       CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'   !< leading substring at top boundary
    653660
    654        CHARACTER(LEN=5), DIMENSION(1:ngases_salsa) ::  gas_name = (/'h2so4','hno3 ','nh3  ','ocnv ','ocsv '/)
     661       CHARACTER(LEN=5), DIMENSION(1:ngases_salsa) ::  gas_name = (/'H2SO4','HNO3 ','NH3  ','OCNV ','OCSV '/)
    655662
    656663       CHARACTER(LEN=25),  DIMENSION(:), ALLOCATABLE ::  cc_name    !< chemical component name
     
    973980           init_aerosol_type,     &
    974981           init_gases_type,       &
    975            nest_salsa,            &
     982           nesting_salsa,         &
    976983           nesting_offline_salsa, &
    977984           salsa_gases_from_chem, &
     
    10371044                                     n_lognorm,                                &
    10381045                                     nbin,                                     &
    1039                                      nest_salsa,                               &
     1046                                     nesting_salsa,                            &
    10401047                                     nesting_offline_salsa,                    &
    10411048                                     nf2a,                                     &
     
    11021109
    11031110    USE control_parameters,                                                                        &
    1104         ONLY:  humidity, initializing_actions
     1111        ONLY:  child_domain, humidity, initializing_actions, nesting_offline
    11051112
    11061113    IMPLICIT NONE
     
    11111118       WRITE( message_string, * ) 'salsa = ', salsa, ' is not allowed with humidity = ', humidity
    11121119       CALL message( 'salsa_check_parameters', 'PA0594', 1, 2, 0, 6, 0 )
     1120    ENDIF
     1121!
     1122!-- For nested runs, explicitly set nesting boundary conditions.
     1123    IF ( nesting_salsa  .AND. child_domain )  bc_salsa_t = 'nested'
     1124!
     1125!-- Set boundary conditions also in case the model is offline-nested in larger-scale models.
     1126    IF ( nesting_offline )  THEN
     1127       IF ( nesting_offline_salsa )  THEN
     1128          bc_salsa_t = 'nesting_offline'
     1129       ELSE
     1130          bc_salsa_t = 'neumann'
     1131       ENDIF
    11131132    ENDIF
    11141133!
     
    11281147    ELSEIF ( bc_salsa_t == 'neumann' )  THEN
    11291148       ibc_salsa_t = 1
    1130     ELSEIF ( bc_salsa_t == 'nested' )  THEN
     1149    ELSEIF ( bc_salsa_t == 'initial_gradient' )  THEN
    11311150       ibc_salsa_t = 2
     1151    ELSEIF ( bc_salsa_t == 'nested'  .OR.  bc_salsa_t == 'nesting_offline' )  THEN
     1152       ibc_salsa_t = 3
    11321153    ELSE
    11331154       message_string = 'unknown boundary condition: bc_salsa_t = "' // TRIM( bc_salsa_t ) // '"'
    11341155       CALL message( 'salsa_check_parameters', 'PA0596', 1, 2, 0, 6, 0 )
    1135     ENDIF
    1136 !
    1137 !-- If nest_salsa = .F., set top boundary to dirichlet
    1138     IF ( .NOT. nest_salsa  .AND.  ibc_salsa_t == 2  )  THEN
    1139        ibc_salsa_t = 0
    1140        bc_salsa_t = 'dirichlet'
    11411156    ENDIF
    11421157!
     
    12461261       WRITE( io, 19 )
    12471262    ENDIF
    1248     IF ( nest_salsa )  WRITE( io, 20 )  nest_salsa
    1249     WRITE( io, 21 ) salsa_emission_mode
     1263    IF ( nesting_salsa )  WRITE( io, 20 )  nesting_salsa
     1264    IF ( nesting_offline_salsa )  WRITE( io, 21 )  nesting_offline_salsa
     1265    WRITE( io, 22 ) salsa_emission_mode
    12501266    IF ( salsa_emission_mode == 'uniform' )  THEN
    1251        WRITE( io, 22 ) surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag,                &
     1267       WRITE( io, 23 ) surface_aerosol_flux, aerosol_flux_dpg, aerosol_flux_sigmag,                &
    12521268                       aerosol_flux_mass_fracs_a
    12531269    ENDIF
    12541270    IF ( SUM( aerosol_flux_mass_fracs_b ) > 0.0_wp  .OR. salsa_emission_mode == 'read_from_file' ) &
    12551271    THEN
    1256        WRITE( io, 23 )
     1272       WRITE( io, 24 )
    12571273    ENDIF
    12581274
     
    1297131319   FORMAT (/'      Size distribution read from a file.')
    1298131420   FORMAT (/'   Nesting for salsa variables: ', L1 )
    1299 21   FORMAT (/'   Emissions: salsa_emission_mode = ', A )
    1300 22   FORMAT (/'      surface_aerosol_flux = ', ES12.4E3, ' #/m**2/s', /                            &
     131521   FORMAT (/'   Offline nesting for salsa variables: ', L1 )
     131622   FORMAT (/'   Emissions: salsa_emission_mode = ', A )
     131723   FORMAT (/'      surface_aerosol_flux = ', ES12.4E3, ' #/m**2/s', /                            &
    13011318              '      aerosol_flux_dpg     =  ', 7(F7.3), ' (m)', /                                 &
    13021319              '      aerosol_flux_sigmag  =  ', 7(F7.2), /                                         &
    13031320              '      aerosol_mass_fracs_a =  ', 7(ES12.4E3) )
    1304 23   FORMAT (/'      (currently all emissions are soluble!)')
     132124   FORMAT (/'      (currently all emissions are soluble!)')
    13051322
    13061323 END SUBROUTINE salsa_header
     
    22092226!
    22102227!--       Read vertical profiles of gases:
    2211           CALL get_variable( id_dyn, 'init_atmosphere_h2so4', salsa_gas(1)%init(nzb+1:nzt) )
    2212           CALL get_variable( id_dyn, 'init_atmosphere_hno3',  salsa_gas(2)%init(nzb+1:nzt) )
    2213           CALL get_variable( id_dyn, 'init_atmosphere_nh3',   salsa_gas(3)%init(nzb+1:nzt) )
    2214           CALL get_variable( id_dyn, 'init_atmosphere_ocnv',  salsa_gas(4)%init(nzb+1:nzt) )
    2215           CALL get_variable( id_dyn, 'init_atmosphere_ocsv',  salsa_gas(5)%init(nzb+1:nzt) )
     2228          CALL get_variable( id_dyn, 'init_atmosphere_H2SO4', salsa_gas(1)%init(nzb+1:nzt) )
     2229          CALL get_variable( id_dyn, 'init_atmosphere_HNO3',  salsa_gas(2)%init(nzb+1:nzt) )
     2230          CALL get_variable( id_dyn, 'init_atmosphere_NH3',   salsa_gas(3)%init(nzb+1:nzt) )
     2231          CALL get_variable( id_dyn, 'init_atmosphere_OCNV',  salsa_gas(4)%init(nzb+1:nzt) )
     2232          CALL get_variable( id_dyn, 'init_atmosphere_OCSV',  salsa_gas(5)%init(nzb+1:nzt) )
    22162233!
    22172234!--       Set Neumann top and surface boundary condition for initial + initialise concentrations
     
    81468163
    81478164    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
    8148 
    81498165!
    81508166!--    Surface conditions:
     
    82478263          ENDIF
    82488264
    8249        ELSEIF ( ibc_salsa_t == 2 )  THEN   ! nested
     8265       ELSEIF ( ibc_salsa_t == 2 )  THEN   ! Initial gradient
    82508266
    82518267          DO  ib = 1, nbins_aerosol
     
    83588374    flag = 0.0_wp
    83598375!
    8360 !-- Skip input if forcing from larger-scale models is applied.
     8376!-- Skip input if forcing from a larger-scale models is applied.
    83618377    IF ( nesting_offline  .AND.  nesting_offline_salsa )  RETURN
    83628378!
     
    97789794
    97799795          CASE ( 'g_H2SO4', 'g_HNO3', 'g_NH3', 'g_OCNV',  'g_OCSV' )
    9780              IF (  salsa_gases_from_chem )  THEN
     9796             IF (  air_chemistry )  THEN
    97819797                message_string = 'gases are imported from the chemistry module and thus output '// &
    97829798                                 'of "' // TRIM( var ) // '" is not allowed'
Note: See TracChangeset for help on using the changeset viewer.