Ignore:
Timestamp:
Apr 5, 2019 9:01:56 AM (6 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/pmc_interface_mod.f90

    r3833 r3864  
    2525! -----------------
    2626! $Id$
     27! Implemented nesting for salsa variables.
     28!
     29! 3833 2019-03-28 15:04:04Z forkel
    2730! replaced USE chem_modules by USE chem_gasphase_mod
    2831!
     
    398401               coupling_char, dt_3d, dz, humidity, message_string,             &
    399402               neutral, passive_scalar, rans_mode, rans_tke_e,                 &
    400                roughness_length, topography, volume_flow
     403               roughness_length, salsa, topography, volume_flow
    401404
    402405    USE chem_gasphase_mod,                                                          &
     
    457460
    458461#endif
     462   
     463    USE salsa_mod,                                                             &
     464        ONLY:  aerosol_mass, aerosol_number, gconc_2, mconc_2, nbins_aerosol,  &
     465               ncomponents_mass, nconc_2, nest_salsa, ngases_salsa, salsa_gas, &
     466               salsa_gases_from_chem
    459467
    460468    USE surface_mod,                                                           &
     
    518526    INTEGER(idp), SAVE, DIMENSION(:,:), ALLOCATABLE, TARGET, PUBLIC ::  part_adrc   !<
    519527
    520     REAL(wp), SAVE, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  chem_spec_c !< Parent-grid array on child domain - chemical species
     528    REAL(wp), SAVE, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  chem_spec_c !< coarse grid array on child domain - chemical species
     529
     530    REAL(wp), SAVE, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  aerosol_mass_c   !< aerosol mass
     531    REAL(wp), SAVE, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  aerosol_number_c !< aerosol number
     532    REAL(wp), SAVE, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  salsa_gas_c      !<  salsa gases
    521533!
    522534!-- Grid-spacing ratios.
     
    817829
    818830    CHARACTER(LEN=32) ::  myname
    819    
    820     INTEGER(iwp) ::  child_id           !<
    821     INTEGER(iwp) ::  ierr               !<
    822     INTEGER(iwp) ::  k                  !<
    823     INTEGER(iwp) ::  m                  !<
    824     INTEGER(iwp) ::  mid                !<
    825     INTEGER(iwp) ::  mm                 !<
    826     INTEGER(iwp) ::  n = 1              !< Running index for chemical species
    827     INTEGER(iwp) ::  nest_overlap       !<
    828     INTEGER(iwp) ::  nomatch            !<
    829     INTEGER(iwp) ::  nx_cl              !<
    830     INTEGER(iwp) ::  ny_cl              !<
    831     INTEGER(iwp) ::  nz_cl              !<
    832     INTEGER(iwp), DIMENSION(3) ::  val  !< Array for receiving the child-grid dimensions
     831    INTEGER(iwp) ::  child_id         !<
     832    INTEGER(iwp) ::  ib = 1           !< running index for aerosol size bins
     833    INTEGER(iwp) ::  ic = 1           !< running index for aerosol mass bins
     834    INTEGER(iwp) ::  ig = 1           !< running index for salsa gases
     835    INTEGER(iwp) ::  ierr             !<
     836    INTEGER(iwp) ::  k                !<
     837    INTEGER(iwp) ::  m                !<
     838    INTEGER(iwp) ::  mid              !<
     839    INTEGER(iwp) ::  mm               !<
     840    INTEGER(iwp) ::  n = 1            !< running index for chemical species
     841    INTEGER(iwp) ::  nest_overlap     !<
     842    INTEGER(iwp) ::  nomatch          !<
     843    INTEGER(iwp) ::  nx_cl            !<
     844    INTEGER(iwp) ::  ny_cl            !<
     845    INTEGER(iwp) ::  nz_cl            !<
     846
     847    INTEGER(iwp), DIMENSION(5) ::  val    !<
     848
    833849    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ch_xl   !<
    834850    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ch_xr   !<   
     
    10321048             CALL pmci_set_array_pointer( myname, child_id = child_id,         &
    10331049                                          nz_cl = nz_cl, n = n )
    1034              n = n + 1
     1050             n = n + 1 
     1051          ELSEIF ( INDEX( TRIM( myname ), 'an_' ) /= 0 )  THEN
     1052             CALL pmci_set_array_pointer( myname, child_id = child_id,         &
     1053                                          nz_cl = nz_cl, n = ib )
     1054             ib = ib + 1
     1055          ELSEIF ( INDEX( TRIM( myname ), 'am_' ) /= 0 )  THEN
     1056             CALL pmci_set_array_pointer( myname, child_id = child_id,         &
     1057                                          nz_cl = nz_cl, n = ic )
     1058             ic = ic + 1
     1059          ELSEIF ( INDEX( TRIM( myname ), 'sg_' ) /= 0  .AND.                  &
     1060             .NOT. salsa_gases_from_chem )                                     &
     1061          THEN
     1062             CALL pmci_set_array_pointer( myname, child_id = child_id,         &
     1063                                          nz_cl = nz_cl, n = ig )
     1064             ig = ig + 1
    10351065          ELSE
    10361066             CALL pmci_set_array_pointer( myname, child_id = child_id,         &
     
    11931223    IMPLICIT NONE
    11941224
    1195     CHARACTER(LEN=da_namelen) ::  myname     !<
    1196     INTEGER(iwp) ::  ierr       !< MPI error code
     1225
     1226    CHARACTER(LEN=da_namelen) ::  myname     !<
     1227    CHARACTER(LEN=5) ::  salsa_char          !<
     1228    INTEGER(iwp) ::  ib         !< running index for aerosol size bins
     1229    INTEGER(iwp) ::  ic         !< running index for aerosol mass bins
     1230    INTEGER(iwp) ::  ierr       !<
    11971231    INTEGER(iwp) ::  icl        !< Left index limit for children's parent-grid arrays
    11981232    INTEGER(iwp) ::  icla       !< Left index limit for allocation of index-mapping and other auxiliary arrays
     
    12011235    INTEGER(iwp) ::  icra       !< Right index limit for allocation of index-mapping and other auxiliary arrays
    12021236    INTEGER(iwp) ::  icrw       !< Right index limit for children's parent-grid work arrays
     1237    INTEGER(iwp) ::  ig         !< running index for salsa gases
    12031238    INTEGER(iwp) ::  jcn        !< North index limit for children's parent-grid arrays
    12041239    INTEGER(iwp) ::  jcna       !< North index limit for allocation of index-mapping and other auxiliary arrays
     
    12811316                                          'chem_' //                           &
    12821317                                          TRIM( chem_species(n)%name ),        &
    1283                                          'fine',                               &
     1318                                          'fine',                              &
    12841319                                          'chem_' //                           &
    12851320                                          TRIM( chem_species(n)%name ),        &
    12861321                                          ierr )
    12871322          ENDDO
     1323       ENDIF
     1324
     1325       IF ( salsa  .AND.  nest_salsa )  THEN
     1326          DO  ib = 1, nbins_aerosol
     1327             WRITE(salsa_char,'(i0)') ib
     1328             CALL pmc_set_dataarray_name( 'coarse',                            &
     1329                                          'an_' //                             &
     1330                                          TRIM( salsa_char ),                  &
     1331                                          'fine',                              &
     1332                                          'an_' //                             &
     1333                                          TRIM( salsa_char ),                  &
     1334                                          ierr )
     1335          ENDDO
     1336          DO  ic = 1, nbins_aerosol * ncomponents_mass
     1337             WRITE(salsa_char,'(i0)') ic
     1338             CALL pmc_set_dataarray_name( 'coarse',                            &
     1339                                          'am_' //                             &
     1340                                          TRIM( salsa_char ),                  &
     1341                                          'fine',                              &
     1342                                          'am_' //                             &
     1343                                          TRIM( salsa_char ),                  &
     1344                                          ierr )
     1345          ENDDO
     1346          IF ( .NOT. salsa_gases_from_chem )  THEN
     1347             DO  ig = 1, ngases_salsa
     1348                WRITE(salsa_char,'(i0)') ig
     1349                CALL pmc_set_dataarray_name( 'coarse',                         &
     1350                                             'sg_' //                          &
     1351                                             TRIM( salsa_char ),               &
     1352                                             'fine',                           &
     1353                                             'sg_' //                          &
     1354                                             TRIM( salsa_char ),               &
     1355                                             ierr )
     1356             ENDDO
     1357          ENDIF
    12881358       ENDIF
    12891359
     
    13641434       CALL  pmc_c_clear_next_array_list
    13651435
    1366        n = 1
     1436       ib = 1
     1437       ic = 1
     1438       ig = 1
     1439       n  = 1
     1440
    13671441       DO  WHILE ( pmc_c_getnextarray( myname ) )
    13681442!--       Note that cg%nz is not the original nz of parent, but the highest
     
    13751449          IF ( INDEX( TRIM( myname ), 'chem_' ) /= 0 )  THEN             
    13761450             CALL pmci_create_child_arrays ( myname, icl, icr, jcs, jcn, cg%nz, n )
    1377              n = n + 1
     1451             n = n + 1   
     1452          ELSEIF ( INDEX( TRIM( myname ), 'an_' ) /= 0 )  THEN
     1453             CALL pmci_create_child_arrays ( myname, icl, icr, jcs, jcn, cg%nz,&
     1454                                             ib )
     1455             ib = ib + 1
     1456          ELSEIF ( INDEX( TRIM( myname ), 'am_' ) /= 0 )  THEN
     1457             CALL pmci_create_child_arrays ( myname, icl, icr, jcs, jcn, cg%nz,&
     1458                                             ic )
     1459             ic = ic + 1
     1460          ELSEIF ( INDEX( TRIM( myname ), 'sg_' ) /= 0  .AND.                  &
     1461             .NOT. salsa_gases_from_chem )                                     &
     1462          THEN
     1463             CALL pmci_create_child_arrays ( myname, icl, icr, jcs, jcn, cg%nz,&
     1464                                             ig )
     1465             ig = ig + 1
    13781466          ELSE
    13791467             CALL pmci_create_child_arrays ( myname, icl, icr, jcs, jcn, cg%nz )
     
    21142202    IF ( air_chemistry  .AND.  nest_chemistry )                                &
    21152203       pmc_max_array = pmc_max_array + nspec
     2204!
     2205!-- Salsa, depens on the number aerosol size bins and chemical components +
     2206!-- the number of default gases
     2207    IF ( salsa  .AND.  nest_salsa )                                            &
     2208       pmc_max_array = pmc_max_array + nbins_aerosol + nbins_aerosol *         &
     2209                       ncomponents_mass
     2210       IF ( .NOT. salsa_gases_from_chem )  pmc_max_array = pmc_max_array +     &
     2211                                                           ngases_salsa
     2212
     2213
    21162214#endif
    21172215   
     
    21262224    INTEGER(iwp), INTENT(IN)          ::  child_id    !<
    21272225    INTEGER(iwp), INTENT(IN)          ::  nz_cl       !<
    2128     INTEGER(iwp), INTENT(IN),OPTIONAL ::  n           !< index of chemical species
     2226    INTEGER(iwp), INTENT(IN),OPTIONAL ::  n           !< index of chemical
     2227                                                      !< species / salsa variables
    21292228
    21302229    CHARACTER(LEN=*), INTENT(IN) ::  name             !<
     
    21592258    IF ( TRIM(name) == "nr_part"    )  i_2d => nr_part
    21602259    IF ( TRIM(name) == "part_adr"   )  i_2d => part_adr
    2161     IF ( INDEX( TRIM(name), "chem_" ) /= 0 )  p_3d => chem_species(n)%conc
     2260    IF ( INDEX( TRIM(name), "chem_" ) /= 0      )  p_3d => chem_species(n)%conc
     2261    IF ( INDEX( TRIM(name), "an_" ) /= 0  )  p_3d => aerosol_number(n)%conc
     2262    IF ( INDEX( TRIM(name), "am_" ) /= 0 )  p_3d => aerosol_mass(n)%conc
     2263    IF ( INDEX( TRIM(name), "sg_" ) /= 0  .AND.  .NOT. salsa_gases_from_chem ) &
     2264       p_3d => salsa_gas(n)%conc
    21622265!
    21632266!-- Next line is just an example for a 2D array (not active for coupling!)
     
    21762279    IF ( TRIM(name) == "s"    )  p_3d_sec => s_2
    21772280    IF ( TRIM(name) == "diss" )  p_3d_sec => diss_2
    2178     IF ( INDEX( TRIM(name), "chem_" ) /= 0 )  p_3d_sec => spec_conc_2(:,:,:,n)
     2281    IF ( INDEX( TRIM(name), "chem_" ) /= 0      )  p_3d_sec => spec_conc_2(:,:,:,n)
     2282    IF ( INDEX( TRIM(name), "an_" ) /= 0  )  p_3d_sec => nconc_2(:,:,:,n)
     2283    IF ( INDEX( TRIM(name), "am_" ) /= 0 )  p_3d_sec => mconc_2(:,:,:,n)
     2284    IF ( INDEX( TRIM(name), "sg_" ) /= 0  .AND.  .NOT. salsa_gases_from_chem ) &
     2285       p_3d_sec => gconc_2(:,:,:,n)
    21792286
    21802287    IF ( ASSOCIATED( p_3d ) )  THEN
     
    22952402    INTEGER(iwp), INTENT(IN) ::  nzc     !<  nzc is cg%nz, but note that cg%nz is not the original nz of parent, but the highest parent-grid level needed for nesting.
    22962403
    2297     INTEGER(iwp), INTENT(IN), OPTIONAL ::  n  !< number of chemical species
     2404    INTEGER(iwp), INTENT(IN), OPTIONAL ::  n  !< number of chemical species /
     2405                                              !< salsa variables
    22982406
    22992407#if defined( __parallel )
     
    23562464          ALLOCATE( chem_spec_c(0:nzc+1,js:je,is:ie,1:nspec) )
    23572465       p_3d => chem_spec_c(:,:,:,n)
     2466    ELSEIF ( TRIM( name(1:3) ) == "an_" )  THEN
     2467       IF ( .NOT. ALLOCATED( aerosol_number_c ) )                              &
     2468          ALLOCATE( aerosol_number_c(0:nzc+1,js:je,is:ie,1:nbins_aerosol) )
     2469       p_3d => aerosol_number_c(:,:,:,n)
     2470    ELSEIF ( TRIM( name(1:3) ) == "am_" )  THEN
     2471       IF ( .NOT. ALLOCATED( aerosol_mass_c ) )                                &
     2472          ALLOCATE( aerosol_mass_c(0:nzc+1,js:je,is:ie,1:(nbins_aerosol*ncomponents_mass) ) )
     2473       p_3d => aerosol_mass_c(:,:,:,n)
     2474    ELSEIF ( TRIM( name(1:3) ) == "sg_"  .AND.  .NOT. salsa_gases_from_chem )  &
     2475    THEN
     2476       IF ( .NOT. ALLOCATED( salsa_gas_c ) )                                   &
     2477          ALLOCATE( salsa_gas_c(0:nzc+1,js:je,is:ie,1:ngases_salsa) )
     2478       p_3d => salsa_gas_c(:,:,:,n)
    23582479    !ELSEIF (trim(name) == "z0") then
    23592480       !IF (.not.allocated(z0c))  allocate(z0c(js:je, is:ie))
     
    24192540
    24202541    INTEGER(iwp) ::  i          !<
     2542    INTEGER(iwp) ::  ib         !< running index for aerosol size bins
     2543    INTEGER(iwp) ::  ic         !< running index for aerosol mass bins
    24212544    INTEGER(iwp) ::  icl        !<
    24222545    INTEGER(iwp) ::  icla       !<
     
    24252548    INTEGER(iwp) ::  icra       !<
    24262549    INTEGER(iwp) ::  icrw       !<
     2550    INTEGER(iwp) ::  ig         !< running index for salsa gases
    24272551    INTEGER(iwp) ::  j          !<
    24282552    INTEGER(iwp) ::  jcn        !<
     
    24342558    INTEGER(iwp) ::  k          !<
    24352559    INTEGER(iwp) ::  n          !< running index for chemical species
     2560
    24362561    REAL(wp) ::  waittime       !<
    24372562
     
    25022627                                         kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, 's' )
    25032628          ENDDO
     2629       ENDIF
     2630
     2631       IF ( salsa  .AND.  nest_salsa )  THEN
     2632          DO  ib = 1, nbins_aerosol
     2633             CALL pmci_interp_1sto_all ( aerosol_number(ib)%conc, aerosol_number_c(:,:,:,ib),        &
     2634                                         kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, 's' )
     2635          ENDDO
     2636          DO  ic = 1, nbins_aerosol * ncomponents_mass
     2637             CALL pmci_interp_1sto_all ( aerosol_mass(ic)%conc, aerosol_mass_c(:,:,:,ic),            &
     2638                                         kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, 's' )
     2639          ENDDO
     2640          IF ( .NOT. salsa_gases_from_chem )  THEN
     2641             DO  ig = 1, ngases_salsa
     2642                CALL pmci_interp_1sto_all ( salsa_gas(ig)%conc, salsa_gas_c(:,:,:,ig),             &
     2643                                            kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, 's' )
     2644             ENDDO
     2645          ENDIF
    25042646       ENDIF
    25052647
     
    30803222       INTEGER(iwp) ::  ibgp       !< index running over the nbgp boundary ghost points in i-direction
    30813223       INTEGER(iwp) ::  jbgp       !< index running over the nbgp boundary ghost points in j-direction
     3224       INTEGER(iwp) ::  ib         !< running index for aerosol size bins
     3225       INTEGER(iwp) ::  ic         !< running index for aerosol mass bins
     3226       INTEGER(iwp) ::  ig         !< running index for salsa gases
    30823227       INTEGER(iwp) ::  n          !< running index for number of chemical species
    30833228     
     
    31413286             ENDIF
    31423287
     3288             IF ( salsa  .AND.  nest_salsa )  THEN
     3289                DO  ib = 1, nbins_aerosol
     3290                   CALL pmci_interp_1sto_lr( aerosol_number(ib)%conc, aerosol_number_c(:,:,:,ib),    &
     3291                                             kcto, jflo, jfuo, kflo, kfuo, 'l', 's')
     3292                ENDDO
     3293                DO  ic = 1, nbins_aerosol * ncomponents_mass
     3294                   CALL pmci_interp_1sto_lr( aerosol_mass(ic)%conc, aerosol_mass_c(:,:,:,ic),        &
     3295                                             kcto, jflo, jfuo, kflo, kfuo, 'l', 's')
     3296                ENDDO
     3297                IF ( .NOT. salsa_gases_from_chem )  THEN
     3298                   DO  ig = 1, ngases_salsa
     3299                      CALL pmci_interp_1sto_lr( salsa_gas(ig)%conc, salsa_gas_c(:,:,:,ig),         &
     3300                                                kcto, jflo, jfuo, kflo, kfuo, 'l', 's')
     3301                   ENDDO
     3302                ENDIF
     3303             ENDIF
     3304
    31433305          ENDIF
    31443306!
     
    31953357                ENDDO
    31963358             ENDIF
     3359
     3360             IF ( salsa  .AND.  nest_salsa )  THEN
     3361                DO  ib = 1, nbins_aerosol
     3362                   CALL pmci_interp_1sto_lr( aerosol_number(ib)%conc, aerosol_number_c(:,:,:,ib),    &
     3363                                             kcto, jflo, jfuo, kflo, kfuo, 'r', 's' )
     3364                ENDDO
     3365                DO  ic = 1, nbins_aerosol * ncomponents_mass
     3366                   CALL pmci_interp_1sto_lr( aerosol_mass(ic)%conc, aerosol_mass_c(:,:,:,ic),        &
     3367                                             kcto, jflo, jfuo, kflo, kfuo, 'r', 's' )
     3368                ENDDO
     3369                IF ( .NOT. salsa_gases_from_chem )  THEN
     3370                   DO  ig = 1, ngases_salsa
     3371                      CALL pmci_interp_1sto_lr( salsa_gas(ig)%conc, salsa_gas_c(:,:,:,ig),         &
     3372                                                kcto, jflo, jfuo, kflo, kfuo, 'r', 's' )
     3373                   ENDDO
     3374                ENDIF
     3375             ENDIF
     3376
    31973377          ENDIF
    31983378!
     
    32483428                ENDDO
    32493429             ENDIF
     3430             
     3431             IF ( salsa  .AND.  nest_salsa )  THEN
     3432                DO  ib = 1, nbins_aerosol
     3433                   CALL pmci_interp_1sto_sn( aerosol_number(ib)%conc, aerosol_number_c(:,:,:,ib),    &
     3434                                             kcto, iflo, ifuo, kflo, kfuo, 's', 's' )
     3435                ENDDO
     3436                DO  ic = 1, nbins_aerosol * ncomponents_mass
     3437                   CALL pmci_interp_1sto_sn( aerosol_mass(ic)%conc, aerosol_mass_c(:,:,:,ic),        &
     3438                                             kcto, iflo, ifuo, kflo, kfuo, 's', 's' )
     3439                ENDDO
     3440                IF ( .NOT. salsa_gases_from_chem )  THEN
     3441                   DO  ig = 1, ngases_salsa
     3442                      CALL pmci_interp_1sto_sn( salsa_gas(ig)%conc, salsa_gas_c(:,:,:,ig),         &
     3443                                                kcto, iflo, ifuo, kflo, kfuo, 's', 's' )
     3444                   ENDDO
     3445                ENDIF
     3446             ENDIF
     3447                       
    32503448          ENDIF
    32513449!
     
    33013499                ENDDO
    33023500             ENDIF
     3501             
     3502             IF ( salsa  .AND.  nest_salsa )  THEN
     3503                DO  ib = 1, nbins_aerosol
     3504                   CALL pmci_interp_1sto_sn( aerosol_number(ib)%conc, aerosol_number_c(:,:,:,ib),    &
     3505                                             kcto, iflo, ifuo, kflo, kfuo, 'n', 's' )
     3506                ENDDO
     3507                DO  ic = 1, nbins_aerosol * ncomponents_mass
     3508                   CALL pmci_interp_1sto_sn( aerosol_mass(ic)%conc, aerosol_mass_c(:,:,:,ic),        &
     3509                                             kcto, iflo, ifuo, kflo, kfuo, 'n', 's' )
     3510                ENDDO
     3511                IF ( .NOT. salsa_gases_from_chem )  THEN
     3512                   DO  ig = 1, ngases_salsa
     3513                      CALL pmci_interp_1sto_sn( salsa_gas(ig)%conc, salsa_gas_c(:,:,:,ig),         &
     3514                                                kcto, iflo, ifuo, kflo, kfuo, 'n', 's' )
     3515                   ENDDO
     3516                ENDIF
     3517             ENDIF
     3518                         
    33033519          ENDIF
    33043520
     
    33483564                                      kcto, iflo, ifuo, jflo, jfuo, 's' )
    33493565          ENDDO
     3566       ENDIF
     3567       
     3568       IF ( salsa  .AND.  nest_salsa )  THEN
     3569          DO  ib = 1, nbins_aerosol
     3570             CALL pmci_interp_1sto_t( aerosol_number(ib)%conc, aerosol_number_c(:,:,:,ib),           &
     3571                                      kcto, iflo, ifuo, jflo, jfuo, 's' )
     3572          ENDDO
     3573          DO  ic = 1, nbins_aerosol * ncomponents_mass
     3574             CALL pmci_interp_1sto_t( aerosol_mass(ic)%conc, aerosol_mass_c(:,:,:,ic),               &
     3575                                      kcto, iflo, ifuo, jflo, jfuo, 's' )
     3576          ENDDO
     3577          IF ( .NOT. salsa_gases_from_chem )  THEN
     3578             DO  ig = 1, ngases_salsa
     3579                CALL pmci_interp_1sto_t( salsa_gas(ig)%conc, salsa_gas_c(:,:,:,ig),                &
     3580                                         kcto, iflo, ifuo, jflo, jfuo, 's' )
     3581             ENDDO
     3582          ENDIF
    33503583       ENDIF
    33513584
     
    33603593!--   Note that TKE is not anterpolated.
    33613594      IMPLICIT NONE
     3595      INTEGER(iwp) ::  ib         !< running index for aerosol size bins
     3596      INTEGER(iwp) ::  ic         !< running index for aerosol mass bins
    33623597      INTEGER(iwp) ::  n          !< running index for number of chemical species
    3363 
    3364      
     3598      INTEGER(iwp) ::  ig         !< running index for salsa gases
     3599
     3600
    33653601      CALL pmci_anterp_tophat( u,  uc,  kcto, iflu, ifuu, jflo, jfuo, kflo, kfuo, ijkfc_u, 'u' )
    33663602      CALL pmci_anterp_tophat( v,  vc,  kcto, iflo, ifuo, jflv, jfuv, kflo, kfuo, ijkfc_v, 'v' )
     
    34193655                                     kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, ijkfc_s, 's' )
    34203656         ENDDO
     3657      ENDIF
     3658     
     3659      IF ( salsa  .AND.  nest_salsa )  THEN
     3660         DO  ib = 1, nbins_aerosol
     3661            CALL pmci_anterp_tophat( aerosol_number(ib)%conc, aerosol_number_c(:,:,:,ib),            &
     3662                                     kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, ijkfc_s, 's' )
     3663         ENDDO
     3664         DO  ic = 1, nbins_aerosol * ncomponents_mass
     3665            CALL pmci_anterp_tophat( aerosol_mass(ic)%conc, aerosol_mass_c(:,:,:,ic),                &
     3666                                     kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, ijkfc_s, 's' )
     3667         ENDDO
     3668         IF ( .NOT. salsa_gases_from_chem )  THEN
     3669            DO  ig = 1, ngases_salsa
     3670               CALL pmci_anterp_tophat( salsa_gas(ig)%conc, salsa_gas_c(:,:,:,ig),                 &
     3671                                        kcto, iflo, ifuo, jflo, jfuo, kflo, kfuo, ijkfc_s, 's' )
     3672            ENDDO
     3673         ENDIF
    34213674      ENDIF
    34223675
     
    42754528        ONLY:  ibc_pt_b, ibc_q_b, ibc_s_b, ibc_uv_b
    42764529
     4530    USE salsa_mod,                                                             &
     4531        ONLY:  ibc_salsa_b
     4532
    42774533    USE surface_mod,                                                           &
    42784534        ONLY:  bc_h
     
    42804536    IMPLICIT NONE
    42814537
    4282     INTEGER(iwp) ::  i  !< Index along x-direction
    4283     INTEGER(iwp) ::  j  !< Index along y-direction
    4284     INTEGER(iwp) ::  k  !< Index along z-direction
    4285     INTEGER(iwp) ::  m  !< Running index for surface type
    4286     INTEGER(iwp) ::  n  !< running index for number of chemical species
    4287    
     4538    INTEGER(iwp) ::  i   !< Index along x-direction
     4539    INTEGER(iwp) ::  ib  !< running index for aerosol size bins
     4540    INTEGER(iwp) ::  ic  !< running index for aerosol mass bins
     4541    INTEGER(iwp) ::  ig  !< running index for salsa gases
     4542    INTEGER(iwp) ::  j   !< Index along y-direction
     4543    INTEGER(iwp) ::  k   !< Index along z-direction
     4544    INTEGER(iwp) ::  m   !< Running index for surface type
     4545    INTEGER(iwp) ::  n   !< running index for number of chemical species
     4546
    42884547!
    42894548!-- Set Dirichlet boundary conditions for horizontal velocity components
     
    44334692          ENDDO
    44344693       ENDIF
    4435     ENDIF
     4694    ENDIF
     4695!
     4696!-- Set Neumann boundary conditions for aerosols and salsa gases
     4697    IF ( salsa  .AND.  nest_salsa )  THEN
     4698       IF ( ibc_salsa_b == 1 )  THEN
     4699          DO  m = 1, bc_h(0)%ns
     4700             i = bc_h(0)%i(m)
     4701             j = bc_h(0)%j(m)
     4702             k = bc_h(0)%k(m)
     4703             DO  ib = 1, nbins_aerosol
     4704                aerosol_number(ib)%conc(k-1,j,i) = aerosol_number(ib)%conc(k,j,i)
     4705             ENDDO
     4706             DO  ic = 1, nbins_aerosol * ncomponents_mass
     4707                aerosol_mass(ic)%conc(k-1,j,i) = aerosol_mass(ic)%conc(k,j,i)
     4708             ENDDO
     4709             IF ( .NOT. salsa_gases_from_chem )  THEN
     4710                DO  ig = 1, ngases_salsa
     4711                   salsa_gas(ig)%conc(k-1,j,i) = salsa_gas(ig)%conc(k,j,i)
     4712                ENDDO
     4713             ENDIF
     4714          ENDDO
     4715          DO  m = 1, bc_h(1)%ns
     4716             i = bc_h(1)%i(m)
     4717             j = bc_h(1)%j(m)
     4718             k = bc_h(1)%k(m)
     4719             DO  ib = 1, nbins_aerosol
     4720                aerosol_number(ib)%conc(k+1,j,i) = aerosol_number(ib)%conc(k,j,i)
     4721             ENDDO
     4722             DO  ic = 1, nbins_aerosol * ncomponents_mass
     4723                aerosol_mass(ic)%conc(k+1,j,i) = aerosol_mass(ic)%conc(k,j,i)
     4724             ENDDO
     4725             IF ( .NOT. salsa_gases_from_chem )  THEN
     4726                DO  ig = 1, ngases_salsa
     4727                   salsa_gas(ig)%conc(k+1,j,i) = salsa_gas(ig)%conc(k,j,i)
     4728                ENDDO
     4729             ENDIF
     4730          ENDDO
     4731       ENDIF
     4732    ENDIF   
    44364733
    44374734 END SUBROUTINE pmci_boundary_conds
Note: See TracChangeset for help on using the changeset viewer.