Changeset 4273


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

Add logical switched nesting_chem and nesting_offline_chem

Location:
palm/trunk
Files:
7 edited

Legend:

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

    r4182 r4273  
    2727! -----------------
    2828! $Id$
     29! Add logical switches nesting_chem and nesting_offline_chem (both .TRUE.
     30! by default)
     31!
     32! 4182 2019-08-22 15:20:23Z scharf
    2933! Corrected "Former revisions" section
    3034!
     
    134138    LOGICAL ::  emissions_anthropogenic   = .FALSE.  !< namelist parameter: flag for turning on anthropogenic emissions
    135139    LOGICAL ::  emission_output_required  = .TRUE.   !< internal flag for requiring emission outputs
     140    LOGICAL ::  nesting_chem              = .TRUE.   !< apply self-nesting for the chemistry model
     141    LOGICAL ::  nesting_offline_chem      = .TRUE.   !< apply offline nesting for the chemistry model
    136142
    137143    REAL(wp) ::  cs_surface_initial_change(99)     = 0.0_wp        !< namelist parameter: ...???
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r4272 r4273  
    2727! -----------------
    2828! $Id$
     29! Add logical switches nesting_chem and nesting_offline_chem (both .TRUE.
     30! by default)
     31!
     32! 4272 2019-10-23 15:18:57Z schwenkel
    2933! Further modularization of boundary conditions: moved boundary conditions to
    3034! respective modules
     
    859863 SUBROUTINE chem_boundary_conds_decycle( cs_3d, cs_pr_init )
    860864
    861 
    862    INTEGER(iwp) ::  boundary  !<
    863    INTEGER(iwp) ::  ee        !<
    864    INTEGER(iwp) ::  copied    !<
    865    INTEGER(iwp) ::  i         !<
    866    INTEGER(iwp) ::  j         !<
    867    INTEGER(iwp) ::  k         !<
    868    INTEGER(iwp) ::  ss        !<
    869 
    870    REAL(wp), DIMENSION(nzb:nzt+1) ::  cs_pr_init
    871    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  cs_3d
    872    REAL(wp) ::  flag          !< flag to mask topography grid points
    873 
    874 
    875    flag = 0.0_wp
    876    !
    877    !-- Left and right boundaries
    878    IF ( decycle_chem_lr  .AND.  bc_lr_cyc )  THEN
    879 
    880       DO  boundary = 1, 2
    881 
    882          IF ( decycle_method(boundary) == 'dirichlet' )  THEN
    883             !
    884             !--          Initial profile is copied to ghost and first three layers
    885             ss = 1
    886             ee = 0
    887             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
    888                ss = nxlg
    889                ee = nxl-1
    890             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
    891                ss = nxr+1
    892                ee = nxrg
    893             ENDIF
    894 
    895             DO  i = ss, ee
    896                DO  j = nysg, nyng
    897                   DO  k = nzb+1, nzt
    898                      flag = MERGE( 1.0_wp, 0.0_wp,                            &
    899                           BTEST( wall_flags_0(k,j,i), 0 ) )
    900                      cs_3d(k,j,i) = cs_pr_init(k) * flag
    901                   ENDDO
    902                ENDDO
    903             ENDDO
    904 
    905          ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
    906             !
    907             !--          The value at the boundary is copied to the ghost layers to simulate
    908             !--          an outlet with zero gradient
    909             ss = 1
    910             ee = 0
    911             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
    912                ss = nxlg
    913                ee = nxl-1
    914                copied = nxl
    915             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
    916                ss = nxr+1
    917                ee = nxrg
    918                copied = nxr
    919             ENDIF
    920 
    921             DO  i = ss, ee
    922                DO  j = nysg, nyng
    923                   DO  k = nzb+1, nzt
    924                      flag = MERGE( 1.0_wp, 0.0_wp,                            &
    925                           BTEST( wall_flags_0(k,j,i), 0 ) )
    926                      cs_3d(k,j,i) = cs_3d(k,j,copied) * flag
    927                   ENDDO
    928                ENDDO
    929             ENDDO
    930 
    931          ELSE
    932             WRITE(message_string,*)                                           &
    933                  'unknown decycling method: decycle_method (', &
    934                  boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
    935             CALL message( 'chem_boundary_conds_decycle', 'CM0431',           &
    936                  1, 2, 0, 6, 0 )
    937          ENDIF
    938       ENDDO
    939    ENDIF
    940    !
    941    !-- South and north boundaries
    942    IF ( decycle_chem_ns  .AND.  bc_ns_cyc )  THEN
    943 
    944       DO  boundary = 3, 4
    945 
    946          IF ( decycle_method(boundary) == 'dirichlet' )  THEN
    947             !
    948             !--          Initial profile is copied to ghost and first three layers
    949             ss = 1
    950             ee = 0
    951             IF ( boundary == 3  .AND.  nys == 0 )  THEN
    952                ss = nysg
    953                ee = nys-1
    954             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
    955                ss = nyn+1
    956                ee = nyng
    957             ENDIF
    958 
    959             DO  i = nxlg, nxrg
    960                DO  j = ss, ee
    961                   DO  k = nzb+1, nzt
    962                      flag = MERGE( 1.0_wp, 0.0_wp,                            &
    963                           BTEST( wall_flags_0(k,j,i), 0 ) )
    964                      cs_3d(k,j,i) = cs_pr_init(k) * flag
    965                   ENDDO
    966                ENDDO
    967             ENDDO
    968 
    969 
    970          ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
    971             !
    972             !--          The value at the boundary is copied to the ghost layers to simulate
    973             !--          an outlet with zero gradient
    974             ss = 1
    975             ee = 0
    976             IF ( boundary == 3  .AND.  nys == 0 )  THEN
    977                ss = nysg
    978                ee = nys-1
    979                copied = nys
    980             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
    981                ss = nyn+1
    982                ee = nyng
    983                copied = nyn
    984             ENDIF
    985 
    986             DO  i = nxlg, nxrg
    987                DO  j = ss, ee
    988                   DO  k = nzb+1, nzt
    989                      flag = MERGE( 1.0_wp, 0.0_wp,                            &
    990                           BTEST( wall_flags_0(k,j,i), 0 ) )
    991                      cs_3d(k,j,i) = cs_3d(k,copied,i) * flag
    992                   ENDDO
    993                ENDDO
    994             ENDDO
    995 
    996          ELSE
    997             WRITE(message_string,*)                                           &
    998                  'unknown decycling method: decycle_method (', &
    999                  boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
    1000             CALL message( 'chem_boundary_conds_decycle', 'CM0432',           &
    1001                  1, 2, 0, 6, 0 )
    1002          ENDIF
    1003       ENDDO
    1004    ENDIF
     865    USE control_parameters,                                                                         &
     866        ONLY:  nesting_offline
     867
     868    INTEGER(iwp) ::  boundary  !<
     869    INTEGER(iwp) ::  ee        !<
     870    INTEGER(iwp) ::  copied    !<
     871    INTEGER(iwp) ::  i         !<
     872    INTEGER(iwp) ::  j         !<
     873    INTEGER(iwp) ::  k         !<
     874    INTEGER(iwp) ::  ss        !<
     875
     876    REAL(wp), DIMENSION(nzb:nzt+1) ::  cs_pr_init
     877    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  cs_3d
     878    REAL(wp) ::  flag          !< flag to mask topography grid points
     879
     880
     881    flag = 0.0_wp
     882!
     883!-- Skip input if forcing from a larger-scale model is applied
     884    IF ( nesting_offline  .AND.  nesting_offline_chem )  RETURN
     885!
     886!-- Left and right boundaries
     887    IF ( decycle_chem_lr  .AND.  bc_lr_cyc )  THEN
     888
     889       DO  boundary = 1, 2
     890
     891          IF ( decycle_method(boundary) == 'dirichlet' )  THEN
     892!
     893!--          Initial profile is copied to ghost and first three layers
     894             ss = 1
     895             ee = 0
     896             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
     897                ss = nxlg
     898                ee = nxl-1
     899             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
     900                ss = nxr+1
     901                ee = nxrg
     902             ENDIF
     903
     904             DO  i = ss, ee
     905                DO  j = nysg, nyng
     906                   DO  k = nzb+1, nzt
     907                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
     908                      cs_3d(k,j,i) = cs_pr_init(k) * flag
     909                   ENDDO
     910                ENDDO
     911             ENDDO
     912
     913          ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
     914!
     915!--          The value at the boundary is copied to the ghost layers to simulate
     916!--          an outlet with zero gradient
     917             ss = 1
     918             ee = 0
     919             IF ( boundary == 1  .AND.  nxl == 0 )  THEN
     920                ss = nxlg
     921                ee = nxl-1
     922                copied = nxl
     923             ELSEIF ( boundary == 2  .AND.  nxr == nx )  THEN
     924                ss = nxr+1
     925                ee = nxrg
     926                copied = nxr
     927             ENDIF
     928
     929             DO  i = ss, ee
     930                DO  j = nysg, nyng
     931                   DO  k = nzb+1, nzt
     932                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
     933                      cs_3d(k,j,i) = cs_3d(k,j,copied) * flag
     934                   ENDDO
     935                ENDDO
     936             ENDDO
     937
     938          ELSE
     939             WRITE(message_string,*)                                           &
     940                  'unknown decycling method: decycle_method (', &
     941                  boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
     942             CALL message( 'chem_boundary_conds_decycle', 'CM0431',           &
     943                  1, 2, 0, 6, 0 )
     944          ENDIF
     945       ENDDO
     946    ENDIF
     947!
     948!-- South and north boundaries
     949    IF ( decycle_chem_ns  .AND.  bc_ns_cyc )  THEN
     950
     951       DO  boundary = 3, 4
     952
     953          IF ( decycle_method(boundary) == 'dirichlet' )  THEN
     954!
     955!--          Initial profile is copied to ghost and first three layers
     956             ss = 1
     957             ee = 0
     958             IF ( boundary == 3  .AND.  nys == 0 )  THEN
     959                ss = nysg
     960                ee = nys-1
     961             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
     962                ss = nyn+1
     963                ee = nyng
     964             ENDIF
     965
     966             DO  i = nxlg, nxrg
     967                DO  j = ss, ee
     968                   DO  k = nzb+1, nzt
     969                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
     970                      cs_3d(k,j,i) = cs_pr_init(k) * flag
     971                   ENDDO
     972                ENDDO
     973             ENDDO
     974
     975
     976          ELSEIF ( decycle_method(boundary) == 'neumann' )  THEN
     977!
     978!--          The value at the boundary is copied to the ghost layers to simulate
     979!--          an outlet with zero gradient
     980             ss = 1
     981             ee = 0
     982             IF ( boundary == 3  .AND.  nys == 0 )  THEN
     983                ss = nysg
     984                ee = nys-1
     985                copied = nys
     986             ELSEIF ( boundary == 4  .AND.  nyn == ny )  THEN
     987                ss = nyn+1
     988                ee = nyng
     989                copied = nyn
     990             ENDIF
     991
     992             DO  i = nxlg, nxrg
     993                DO  j = ss, ee
     994                   DO  k = nzb+1, nzt
     995                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
     996                      cs_3d(k,j,i) = cs_3d(k,copied,i) * flag
     997                   ENDDO
     998                ENDDO
     999             ENDDO
     1000
     1001          ELSE
     1002             WRITE(message_string,*)                                           &
     1003                  'unknown decycling method: decycle_method (', &
     1004                  boundary, ') ="' // TRIM( decycle_method(boundary) ) // '"'
     1005             CALL message( 'chem_boundary_conds_decycle', 'CM0432',           &
     1006                  1, 2, 0, 6, 0 )
     1007          ENDIF
     1008       ENDDO
     1009    ENDIF
    10051010
    10061011
     
    11751180       message_string = 'Incorrect chemistry mechanism selected, check spelling in namelist and/or chem_gasphase_mod'
    11761181       CALL message( 'chem_check_parameters', 'CM0462', 1, 2, 0, 6, 0 )
     1182    ENDIF
     1183!
     1184!-- If nesting_chem = .F., set top boundary condition to its default value
     1185    IF ( .NOT. nesting_chem  .AND.  ibc_cs_t == 3  )  THEN
     1186       ibc_cs_t = 2
     1187       bc_cs_t = 'initial_gradient'
    11771188    ENDIF
    11781189!
     
    16811692       WRITE ( io, 11 )  docsinit_chr
    16821693    ENDIF
     1694
     1695    IF ( nesting_chem )  WRITE( io, 12 )  nesting_chem
     1696    IF ( nesting_offline_chem )  WRITE( io, 13 )  nesting_offline_chem
    16831697!
    16841698!-- number of variable and fix chemical species and number of reactions
     
    1703171710  FORMAT (/'    ',A) 
    1704171811  FORMAT (/'    ',A)
     171912  FORMAT (/'   Nesting for chemistry variables: ', L1 )
     172013  FORMAT (/'   Offline nesting for chemistry variables: ', L1 )
    17051721!
    17061722!
     
    22672283         mode_emis,                        &
    22682284         my_steps,                         &
     2285         nesting_chem,                     &
     2286         nesting_offline_chem,             &
    22692287         rcntrl,                           &
    22702288         side_street_id,                   &
  • palm/trunk/SOURCE/nesting_offl_mod.f90

    r4270 r4273  
    2525! -----------------
    2626! $Id$
     27! Add a logical switch nesting_offline_chem
     28!
     29! 4270 2019-10-23 10:46:20Z monakurppa
    2730! Implement offline nesting for salsa variables.
    2831!
     
    139142           ONLY:  g,                                                           &
    140143                  pi
    141                  
     144
    142145    USE chem_modules,                                                          &
    143         ONLY:  chem_species
     146        ONLY:  chem_species, nesting_offline_chem
    144147
    145148    USE control_parameters,                                                    &
     
    170173               time_since_reference_point,                                     &
    171174               volume_flow
    172                
     175
    173176    USE cpulog,                                                                &
    174177        ONLY:  cpu_log,                                                        &
     
    520523                             .TRUE. )
    521524       ENDIF
    522        
    523        IF ( air_chemistry )  THEN
     525
     526       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    524527          DO  n = 1, UBOUND(nest_offl%var_names_chem_l, 1)
    525528             IF ( check_existence( nest_offl%var_names,                        &
    526                                    nest_offl%var_names_chem_l(n) ) )  THEN 
     529                                   nest_offl%var_names_chem_l(n) ) )  THEN
    527530                CALL get_variable( pids_id,                                    &
    528531                           TRIM( nest_offl%var_names_chem_l(n) ),              &
     
    594597                             .TRUE. )
    595598       ENDIF
    596        
    597        IF ( air_chemistry )  THEN
     599
     600       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    598601          DO  n = 1, UBOUND(nest_offl%var_names_chem_r, 1)
    599602             IF ( check_existence( nest_offl%var_names,                        &
    600                                    nest_offl%var_names_chem_r(n) ) )  THEN     
     603                                   nest_offl%var_names_chem_r(n) ) )  THEN
    601604                CALL get_variable( pids_id,                                    &
    602605                           TRIM( nest_offl%var_names_chem_r(n) ),              &
     
    623626                          MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    624627                          MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    625                           .TRUE. )                                             
    626                                                                                
     628                          .TRUE. )
     629
    627630       CALL get_variable( pids_id, 'ls_forcing_north_v',                       & ! array to be read
    628631                          nest_offl%v_north,                                   & ! start index x direction
     
    633636                          MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    634637                          MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    635                           .TRUE. )                                             
    636                                                                                
     638                          .TRUE. )
     639
    637640       CALL get_variable( pids_id, 'ls_forcing_north_w',                       & ! array to be read
    638641                          nest_offl%w_north,                                   & ! start index x direction
     
    643646                          MERGE( nest_offl%nzw, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
    644647                          MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
    645                           .TRUE. )                                             
    646                                                                                
    647        IF ( .NOT. neutral )  THEN                                             
     648                          .TRUE. )
     649
     650       IF ( .NOT. neutral )  THEN
    648651          CALL get_variable( pids_id, 'ls_forcing_north_pt',                   & ! array to be read
    649652                             nest_offl%pt_north,                               & ! start index x direction
     
    654657                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
    655658                             MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
    656                              .TRUE. )                                             
    657        ENDIF                                                                   
    658        IF ( humidity )  THEN                                                   
     659                             .TRUE. )
     660       ENDIF
     661       IF ( humidity )  THEN
    659662          CALL get_variable( pids_id, 'ls_forcing_north_qv',                   & ! array to be read
    660663                             nest_offl%q_north,                                & ! start index x direction
     
    665668                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
    666669                             MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
    667                              .TRUE. )                                             
    668        ENDIF                                                                   
    669                                                                                
    670        IF ( air_chemistry )  THEN                                             
    671           DO  n = 1, UBOUND(nest_offl%var_names_chem_n, 1)                     
     670                             .TRUE. )
     671       ENDIF
     672
     673       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     674          DO  n = 1, UBOUND(nest_offl%var_names_chem_n, 1)
    672675             IF ( check_existence( nest_offl%var_names,                        &
    673                                    nest_offl%var_names_chem_n(n) ) )  THEN     
     676                                   nest_offl%var_names_chem_n(n) ) )  THEN
    674677                CALL get_variable( pids_id,                                    &
    675678                           TRIM( nest_offl%var_names_chem_n(n) ),              &
     
    696699                          MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    697700                          MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    698                           .TRUE. )                                             
    699                                                                                
     701                          .TRUE. )
     702
    700703       CALL get_variable( pids_id, 'ls_forcing_south_v',                       & ! array to be read
    701704                          nest_offl%v_south,                                   & ! start index x direction
     
    706709                          MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    707710                          MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    708                           .TRUE. )                                             
    709                                                                                
     711                          .TRUE. )
     712
    710713       CALL get_variable( pids_id, 'ls_forcing_south_w',                       & ! array to be read
    711714                          nest_offl%w_south,                                   & ! start index x direction
     
    716719                          MERGE( nest_offl%nzw, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
    717720                          MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
    718                           .TRUE. )                                             
    719                                                                                
    720        IF ( .NOT. neutral )  THEN                                             
     721                          .TRUE. )
     722
     723       IF ( .NOT. neutral )  THEN
    721724          CALL get_variable( pids_id, 'ls_forcing_south_pt',                   & ! array to be read
    722725                             nest_offl%pt_south,                               & ! start index x direction
     
    727730                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
    728731                             MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
    729                              .TRUE. )                                             
    730        ENDIF                                                                   
    731        IF ( humidity )  THEN                                                   
     732                             .TRUE. )
     733       ENDIF
     734       IF ( humidity )  THEN
    732735          CALL get_variable( pids_id, 'ls_forcing_south_qv',                   & ! array to be read
    733736                             nest_offl%q_south,                                & ! start index x direction
     
    738741                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
    739742                             MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
    740                              .TRUE. )                                             
    741        ENDIF                                                                   
    742                                                                                
    743        IF ( air_chemistry )  THEN                                             
    744           DO  n = 1, UBOUND(nest_offl%var_names_chem_s, 1)                     
     743                             .TRUE. )
     744       ENDIF
     745
     746       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
     747          DO  n = 1, UBOUND(nest_offl%var_names_chem_s, 1)
    745748             IF ( check_existence( nest_offl%var_names,                        &
    746                                    nest_offl%var_names_chem_s(n) ) )  THEN     
     749                                   nest_offl%var_names_chem_s(n) ) )  THEN
    747750                CALL get_variable( pids_id,                                    &
    748751                           TRIM( nest_offl%var_names_chem_s(n) ),              &
     
    770773                             nxl+1, nysv, nest_offl%tind+1,                    &
    771774                             nxr-nxl+1, nyn-nysv+1, 2, .TRUE. )
    772                              
     775
    773776       CALL get_variable( pids_id, 'ls_forcing_top_w',                         &
    774777                             nest_offl%w_top(0:1,nys:nyn,nxl:nxr),             &
    775778                             nxl+1, nys+1, nest_offl%tind+1,                   &
    776779                             nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    777                              
     780
    778781       IF ( .NOT. neutral )  THEN
    779782          CALL get_variable( pids_id, 'ls_forcing_top_pt',                     &
     
    788791                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
    789792       ENDIF
    790        
    791        IF ( air_chemistry )  THEN
     793
     794       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    792795          DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
    793796             IF ( check_existence( nest_offl%var_names,                        &
    794                                    nest_offl%var_names_chem_t(n) ) )  THEN     
     797                                   nest_offl%var_names_chem_t(n) ) )  THEN
    795798                CALL get_variable( pids_id,                                    &
    796799                              TRIM( nest_offl%var_names_chem_t(n) ),           &
     
    961964       u_ref    = 0.0_wp
    962965       v_ref    = 0.0_wp
    963        
     966
    964967       pt_ref_l = 0.0_wp
    965968       q_ref_l  = 0.0_wp
     
    968971!
    969972!--    If required, allocate temporary arrays to compute chemistry mean profiles
    970        IF ( air_chemistry )  THEN
     973       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    971974          ALLOCATE( ref_chem(nzb:nzt+1,1:UBOUND( chem_species, 1 ) )   )
    972975          ALLOCATE( ref_chem_l(nzb:nzt+1,1:UBOUND( chem_species, 1 ) ) )
     
    10431046             ENDDO
    10441047          ENDIF
    1045          
    1046           IF ( air_chemistry )  THEN
     1048
     1049          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    10471050             DO  n = 1, UBOUND( chem_species, 1 )
    1048                 IF ( nest_offl%chem_from_file_l(n) )  THEN                   
     1051                IF ( nest_offl%chem_from_file_l(n) )  THEN
    10491052                   DO  j = nys, nyn
    10501053                      DO  k = nzb+1, nzt
     
    11211124             ENDDO
    11221125          ENDIF
    1123          
    1124           IF ( air_chemistry )  THEN
     1126
     1127          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    11251128             DO  n = 1, UBOUND( chem_species, 1 )
    1126                 IF ( nest_offl%chem_from_file_r(n) )  THEN 
     1129                IF ( nest_offl%chem_from_file_r(n) )  THEN
    11271130                   DO  j = nys, nyn
    11281131                      DO  k = nzb+1, nzt
     
    12021205             ENDDO
    12031206          ENDIF
    1204          
    1205           IF ( air_chemistry )  THEN
     1207
     1208          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    12061209             DO  n = 1, UBOUND( chem_species, 1 )
    1207                 IF ( nest_offl%chem_from_file_s(n) )  THEN 
     1210                IF ( nest_offl%chem_from_file_s(n) )  THEN
    12081211                   DO  i = nxl, nxr
    12091212                      DO  k = nzb+1, nzt
     
    12821285             ENDDO
    12831286          ENDIF
    1284          
    1285           IF ( air_chemistry )  THEN
     1287
     1288          IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    12861289             DO  n = 1, UBOUND( chem_species, 1 )
    1287                 IF ( nest_offl%chem_from_file_n(n) )  THEN 
     1290                IF ( nest_offl%chem_from_file_n(n) )  THEN
    12881291                   DO  i = nxl, nxr
    12891292                      DO  k = nzb+1, nzt
     
    13681371          ENDDO
    13691372       ENDIF
    1370        
    1371        IF ( air_chemistry )  THEN
     1373
     1374       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    13721375          DO  n = 1, UBOUND( chem_species, 1 )
    1373              IF ( nest_offl%chem_from_file_t(n) )  THEN 
     1376             IF ( nest_offl%chem_from_file_t(n) )  THEN
    13741377                DO  i = nxl, nxr
    13751378                   DO  j = nys, nyn
     
    14131416       IF ( .NOT. neutral )  CALL exchange_horiz( pt, nbgp )
    14141417       IF ( humidity      )  CALL exchange_horiz( q,  nbgp )
    1415        IF ( air_chemistry )  THEN
     1418       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    14161419          DO  n = 1, UBOUND( chem_species, 1 )
    14171420!
     
    14471450                              comm2d, ierr )
    14481451       ENDIF
    1449        IF ( air_chemistry )  THEN
     1452       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    14501453          CALL MPI_ALLREDUCE( ref_chem_l, ref_chem,                            &
    14511454                              ( nzt+1-nzb+1 ) * SIZE( ref_chem(nzb,:) ),       &
     
    14571460       IF ( humidity )       q_ref    = q_ref_l
    14581461       IF ( .NOT. neutral )  pt_ref   = pt_ref_l
    1459        IF ( air_chemistry )  ref_chem = ref_chem_l
     1462       IF ( air_chemistry  .AND.  nesting_offline_chem )  ref_chem = ref_chem_l
    14601463#endif
    14611464!
     
    14761479                                                          ( ny + 1 + nx + 1 ), &
    14771480                                              KIND = wp )
    1478        IF ( air_chemistry )                                                    &
     1481       IF ( air_chemistry  .AND.  nesting_offline_chem )                       &
    14791482          ref_chem(nzb:nzt,:) = ref_chem(nzb:nzt,:) / REAL( 2.0_wp *           &
    14801483                                                          ( ny + 1 + nx + 1 ), &
     
    14901493          pt_ref(nzt+1) = pt_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx + 1 ),       &
    14911494                                                KIND = wp )
    1492        IF ( air_chemistry )                                                    &
     1495       IF ( air_chemistry  .AND.  nesting_offline_chem )                       &
    14931496          ref_chem(nzt+1,:) = ref_chem(nzt+1,:) /                              &
    14941497                              REAL( ( ny + 1 ) * ( nx + 1 ),KIND = wp )
     
    15081511       ENDIF
    15091512
    1510        IF ( air_chemistry )  THEN
     1513       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    15111514          DO  n = 1, UBOUND( chem_species, 1 )
    15121515             IF ( nest_offl%chem_from_file_t(n) )  THEN
     
    15191522
    15201523       IF ( ALLOCATED( ref_chem   ) )  DEALLOCATE( ref_chem   )
    1521        IF ( ALLOCATED( ref_chem_l ) )  DEALLOCATE( ref_chem_l )     
     1524       IF ( ALLOCATED( ref_chem_l ) )  DEALLOCATE( ref_chem_l )
    15221525!
    15231526!--    Further, adjust Rayleigh damping height in case of time-changing conditions.
     
    15251528       CALL nesting_offl_calc_zi
    15261529       CALL adjust_sponge_layer
    1527        
     1530
    15281531       CALL  cpu_log( log_point(58), 'offline nesting', 'stop' )
    15291532
     
    18931896          IF ( humidity )       ALLOCATE( nest_offl%q_left(0:1,nzb+1:nzt,nys:nyn)  )
    18941897          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_left(0:1,nzb+1:nzt,nys:nyn) )
    1895           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_left(0:1,nzb+1:nzt,nys:nyn,&
    1896                                           1:UBOUND( chem_species, 1 )) )
     1898          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1899             ALLOCATE( nest_offl%chem_left(0:1,nzb+1:nzt,nys:nyn,1:UBOUND( chem_species, 1 )) )
    18971900       ELSE
    18981901          ALLOCATE( nest_offl%u_left(1:1,1:1,1:1)  )
     
    19011904          IF ( humidity )       ALLOCATE( nest_offl%q_left(1:1,1:1,1:1)  )
    19021905          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_left(1:1,1:1,1:1)  )
    1903           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_left(1:1,1:1,1:1,     &
    1904                                           1:UBOUND( chem_species, 1 )) )
     1906          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1907             ALLOCATE( nest_offl%chem_left(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19051908       ENDIF
    19061909       IF ( bc_dirichlet_r )  THEN
     
    19101913          IF ( humidity )       ALLOCATE( nest_offl%q_right(0:1,nzb+1:nzt,nys:nyn)  )
    19111914          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_right(0:1,nzb+1:nzt,nys:nyn) )
    1912           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_right(0:1,nzb+1:nzt,nys:nyn,&
    1913                                           1:UBOUND( chem_species, 1 )) )
     1915          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1916             ALLOCATE( nest_offl%chem_right(0:1,nzb+1:nzt,nys:nyn,1:UBOUND( chem_species, 1 )) )
    19141917       ELSE
    19151918          ALLOCATE( nest_offl%u_right(1:1,1:1,1:1)  )
     
    19181921          IF ( humidity )       ALLOCATE( nest_offl%q_right(1:1,1:1,1:1)  )
    19191922          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_right(1:1,1:1,1:1)  )
    1920           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_right(1:1,1:1,1:1,    &
    1921                                           1:UBOUND( chem_species, 1 )) )
     1923          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1924             ALLOCATE( nest_offl%chem_right(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19221925       ENDIF
    19231926!
     
    19321935          IF ( humidity )       ALLOCATE( nest_offl%q_north(0:1,nzb+1:nzt,nxl:nxr)  )
    19331936          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_north(0:1,nzb+1:nzt,nxl:nxr) )
    1934           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_north(0:1,nzb+1:nzt,nxl:nxr,&
    1935                                           1:UBOUND( chem_species, 1 )) )
     1937          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1938             ALLOCATE( nest_offl%chem_north(0:1,nzb+1:nzt,nxl:nxr,1:UBOUND( chem_species, 1 )) )
    19361939       ELSE
    19371940          ALLOCATE( nest_offl%u_north(1:1,1:1,1:1)  )
     
    19401943          IF ( humidity )       ALLOCATE( nest_offl%q_north(1:1,1:1,1:1)  )
    19411944          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_north(1:1,1:1,1:1)  )
    1942           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_north(1:1,1:1,1:1,    &
    1943                                           1:UBOUND( chem_species, 1 )) )
     1945          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1946             ALLOCATE( nest_offl%chem_north(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19441947       ENDIF
    19451948       IF ( bc_dirichlet_s )  THEN
     
    19491952          IF ( humidity )       ALLOCATE( nest_offl%q_south(0:1,nzb+1:nzt,nxl:nxr)  )
    19501953          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_south(0:1,nzb+1:nzt,nxl:nxr) )
    1951           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_south(0:1,nzb+1:nzt,nxl:nxr,&
    1952                                           1:UBOUND( chem_species, 1 )) )
     1954          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1955             ALLOCATE( nest_offl%chem_south(0:1,nzb+1:nzt,nxl:nxr,1:UBOUND( chem_species, 1 )) )
    19531956       ELSE
    19541957          ALLOCATE( nest_offl%u_south(1:1,1:1,1:1)  )
     
    19571960          IF ( humidity )       ALLOCATE( nest_offl%q_south(1:1,1:1,1:1)  )
    19581961          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_south(1:1,1:1,1:1)  )
    1959           IF ( air_chemistry )  ALLOCATE( nest_offl%chem_south(1:1,1:1,1:1,    &
    1960                                           1:UBOUND( chem_species, 1 )) )
     1962          IF ( air_chemistry  .AND.  nesting_offline_chem )                                        &
     1963             ALLOCATE( nest_offl%chem_south(1:1,1:1,1:1,1:UBOUND( chem_species, 1 )) )
    19611964       ENDIF
    19621965!
     
    19691972       IF ( humidity )       ALLOCATE( nest_offl%q_top(0:1,nys:nyn,nxl:nxr)  )
    19701973       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_top(0:1,nys:nyn,nxl:nxr) )
    1971        IF ( air_chemistry )  ALLOCATE( nest_offl%chem_top(0:1,nys:nyn,nxl:nxr, &
    1972                                        1:UBOUND( chem_species, 1 )) )
     1974       IF ( air_chemistry  .AND.  nesting_offline_chem )                                          &
     1975          ALLOCATE( nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,1:UBOUND( chem_species, 1 )) )
    19731976!
    19741977!--    For chemical species, create the names of the variables. This is necessary
    19751978!--    to identify the respective variable and write it onto the correct array
    19761979!--    in the chem_species datatype.
    1977        IF ( air_chemistry )  THEN
     1980       IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    19781981          ALLOCATE( nest_offl%chem_from_file_l(1:UBOUND( chem_species, 1 )) )
    19791982          ALLOCATE( nest_offl%chem_from_file_n(1:UBOUND( chem_species, 1 )) )
     
    19811984          ALLOCATE( nest_offl%chem_from_file_s(1:UBOUND( chem_species, 1 )) )
    19821985          ALLOCATE( nest_offl%chem_from_file_t(1:UBOUND( chem_species, 1 )) )
    1983          
     1986
    19841987          ALLOCATE( nest_offl%var_names_chem_l(1:UBOUND( chem_species, 1 )) )
    19851988          ALLOCATE( nest_offl%var_names_chem_n(1:UBOUND( chem_species, 1 )) )
     
    19951998          nest_offl%chem_from_file_s(:) = .FALSE.
    19961999          nest_offl%chem_from_file_t(:) = .FALSE.
    1997          
     2000
    19982001          DO  n = 1, UBOUND( chem_species, 1 )
    19992002             nest_offl%var_names_chem_l(n) = nest_offl%char_l //               &
     
    20542057             IF ( humidity      )  q(nzb+1:nzt,nys:nyn,-1)  =                  &
    20552058                                      nest_offl%q_left(0,nzb+1:nzt,nys:nyn)
    2056              IF ( air_chemistry )  THEN
     2059             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    20572060                DO  n = 1, UBOUND( chem_species, 1 )
    20582061                   IF( nest_offl%chem_from_file_l(n) )  THEN
     
    20712074             IF ( humidity      )  q(nzb+1:nzt,nys:nyn,nxr+1)  =               &
    20722075                                      nest_offl%q_right(0,nzb+1:nzt,nys:nyn)
    2073              IF ( air_chemistry )  THEN
     2076             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    20742077                DO  n = 1, UBOUND( chem_species, 1 )
    20752078                   IF( nest_offl%chem_from_file_r(n) )  THEN
     
    20882091             IF ( humidity      )  q(nzb+1:nzt,-1,nxl:nxr)  =                  &
    20892092                                      nest_offl%q_south(0,nzb+1:nzt,nxl:nxr)
    2090              IF ( air_chemistry )  THEN
     2093             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    20912094                DO  n = 1, UBOUND( chem_species, 1 )
    20922095                   IF( nest_offl%chem_from_file_s(n) )  THEN
     
    21052108             IF ( humidity      )  q(nzb+1:nzt,nyn+1,nxl:nxr)  =               &
    21062109                                      nest_offl%q_north(0,nzb+1:nzt,nxl:nxr)
    2107              IF ( air_chemistry )  THEN
     2110             IF ( air_chemistry  .AND.  nesting_offline_chem )  THEN
    21082111                DO  n = 1, UBOUND( chem_species, 1 )
    21092112                   IF( nest_offl%chem_from_file_n(n) )  THEN
     
    21142117             ENDIF
    21152118          ENDIF
    2116 !         
     2119!
    21172120!--       Initialize geostrophic wind components. Actually this is already done in
    21182121!--       init_3d_model when initializing_action = 'inifor', however, in speical
     
    21212124          ug(nzb+1:nzt) = nest_offl%ug(0,nzb+1:nzt)
    21222125          vg(nzb+1:nzt) = nest_offl%vg(0,nzb+1:nzt)
    2123 !         
     2126!
    21242127!--       Set bottom and top boundary condition for geostrophic wind components
    21252128          ug(nzt+1) = ug(nzt)
     
    21272130          ug(nzb)   = ug(nzb+1)
    21282131          vg(nzb)   = vg(nzb+1)
    2129        ENDIF     
     2132       ENDIF
    21302133!
    21312134!--    After boundary data is initialized, mask topography at the
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r4260 r4273  
    2525! -----------------
    2626! $Id$
     27! Add a logical switch nesting_chem and rename nest_salsa to nesting_salsa
     28!
     29! 4260 2019-10-09 14:04:03Z hellstea
    2730! Rest of the possibly round-off-error sensitive grid-line matching tests
    2831! changed to round-off-error tolerant forms throughout the module.
     
    189192
    190193    USE chem_modules,                                                          &
    191         ONLY:  chem_species
     194        ONLY:  chem_species, nesting_chem
    192195
    193196    USE chemistry_model_mod,                                                   &
     
    248251    USE salsa_mod,                                                             &
    249252        ONLY:  aerosol_mass, aerosol_number, gconc_2, mconc_2, nbins_aerosol,  &
    250                ncomponents_mass, nconc_2, nest_salsa, ngases_salsa, salsa_gas, &
    251                salsa_gases_from_chem
     253               ncomponents_mass, nconc_2, nesting_salsa, ngases_salsa,        &
     254               salsa_gas, salsa_gases_from_chem
    252255
    253256    USE surface_mod,                                                           &
     
    11661169       ENDIF
    11671170       
    1168        IF ( air_chemistry )  THEN
     1171       IF ( air_chemistry  .AND.  nesting_chem )  THEN
    11691172          DO n = 1, nspec
    11701173             CALL pmc_set_dataarray_name( 'parent', 'chem_' // TRIM( chem_species(n)%name ),        &
     
    11731176       ENDIF
    11741177
    1175        IF ( salsa  .AND.  nest_salsa )  THEN
     1178       IF ( salsa  .AND.  nesting_salsa )  THEN
    11761179          DO  lb = 1, nbins_aerosol
    11771180             WRITE(salsa_char,'(i0)') lb
     
    23102313!
    23112314!-- Chemistry, depends on number of species
    2312     IF ( air_chemistry )  pmc_max_array = pmc_max_array + nspec
     2315    IF ( air_chemistry  .AND.  nesting_chem )  pmc_max_array = pmc_max_array + nspec
    23132316!
    23142317!-- SALSA, depens on the number aerosol size bins and chemical components +
    23152318!-- the number of default gases
    2316     IF ( salsa  .AND.  nest_salsa )  pmc_max_array = pmc_max_array + nbins_aerosol +                &
    2317          nbins_aerosol * ncomponents_mass
     2319    IF ( salsa  .AND.  nesting_salsa )  pmc_max_array = pmc_max_array + nbins_aerosol +            &
     2320                                                        nbins_aerosol * ncomponents_mass
    23182321    IF ( .NOT. salsa_gases_from_chem )  pmc_max_array = pmc_max_array + ngases_salsa
    23192322
     
    27172720       ENDIF
    27182721
    2719        IF ( air_chemistry )  THEN
     2722       IF ( air_chemistry  .AND.  nesting_chem )  THEN
    27202723          DO  n = 1, nspec
    27212724             CALL pmci_interp_1sto_all ( chem_species(n)%conc, chem_spec_c(:,:,:,n),                &
     
    27242727       ENDIF
    27252728
    2726        IF ( salsa  .AND.  nest_salsa )  THEN
     2729       IF ( salsa  .AND.  nesting_salsa )  THEN
    27272730          DO  lb = 1, nbins_aerosol
    27282731             CALL pmci_interp_1sto_all ( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),       &
     
    33943397             ENDIF
    33953398
    3396              IF ( air_chemistry )  THEN
     3399             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    33973400                DO  n = 1, nspec
    33983401                   CALL pmci_interp_1sto_lr( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    34013404             ENDIF
    34023405
    3403              IF ( salsa  .AND.  nest_salsa )  THEN
     3406             IF ( salsa  .AND.  nesting_salsa )  THEN
    34043407                DO  lb = 1, nbins_aerosol
    34053408                   CALL pmci_interp_1sto_lr( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    34653468             ENDIF
    34663469
    3467              IF ( air_chemistry )  THEN
     3470             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    34683471                DO  n = 1, nspec
    34693472                   CALL pmci_interp_1sto_lr( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    34723475             ENDIF
    34733476
    3474              IF ( salsa  .AND.  nest_salsa )  THEN
     3477             IF ( salsa  .AND.  nesting_salsa )  THEN
    34753478                DO  lb = 1, nbins_aerosol
    34763479                   CALL pmci_interp_1sto_lr( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    35363539             ENDIF
    35373540
    3538              IF ( air_chemistry )  THEN
     3541             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    35393542                DO  n = 1, nspec
    35403543                   CALL pmci_interp_1sto_sn( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    35433546             ENDIF
    35443547             
    3545              IF ( salsa  .AND.  nest_salsa )  THEN
     3548             IF ( salsa  .AND.  nesting_salsa )  THEN
    35463549                DO  lb = 1, nbins_aerosol
    35473550                   CALL pmci_interp_1sto_sn( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    36073610             ENDIF
    36083611
    3609              IF ( air_chemistry )  THEN
     3612             IF ( air_chemistry  .AND.  nesting_chem )  THEN
    36103613                DO  n = 1, nspec
    36113614                   CALL pmci_interp_1sto_sn( chem_species(n)%conc, chem_spec_c(:,:,:,n),            &
     
    36143617             ENDIF
    36153618             
    3616              IF ( salsa  .AND.  nest_salsa )  THEN
     3619             IF ( salsa  .AND.  nesting_salsa )  THEN
    36173620                DO  lb = 1, nbins_aerosol
    36183621                   CALL pmci_interp_1sto_sn( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),   &
     
    36733676       ENDIF
    36743677
    3675        IF ( air_chemistry )  THEN
     3678       IF ( air_chemistry  .AND.  nesting_chem )  THEN
    36763679          DO  n = 1, nspec
    36773680             CALL pmci_interp_1sto_t( chem_species(n)%conc, chem_spec_c(:,:,:,n),                   &
     
    36803683       ENDIF
    36813684       
    3682        IF ( salsa  .AND.  nest_salsa )  THEN
     3685       IF ( salsa  .AND.  nesting_salsa )  THEN
    36833686          DO  lb = 1, nbins_aerosol
    36843687             CALL pmci_interp_1sto_t( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),          &
     
    37643767      ENDIF
    37653768
    3766       IF ( air_chemistry )  THEN
     3769      IF ( air_chemistry  .AND.  nesting_chem )  THEN
    37673770         DO  n = 1, nspec
    37683771            CALL pmci_anterp_tophat( chem_species(n)%conc, chem_spec_c(:,:,:,n),                    &
     
    37703773         ENDDO
    37713774      ENDIF
    3772      
    3773       IF ( salsa  .AND.  nest_salsa )  THEN
     3775
     3776      IF ( salsa  .AND.  nesting_salsa )  THEN
    37743777         DO  lb = 1, nbins_aerosol
    37753778            CALL pmci_anterp_tophat( aerosol_number(lb)%conc, aerosol_number_c(:,:,:,lb),           &
     
    48164819!
    48174820!-- Set Neumann boundary conditions for chemical species
    4818     IF ( air_chemistry )  THEN
     4821    IF ( air_chemistry  .AND.  nesting_chem )  THEN
    48194822       IF ( ibc_cs_b == 1 )  THEN
    48204823          DO  n = 1, nspec
     
    48364839!
    48374840!-- Set Neumann boundary conditions for aerosols and salsa gases
    4838     IF ( salsa  .AND.  nest_salsa )  THEN
     4841    IF ( salsa  .AND.  nesting_salsa )  THEN
    48394842       IF ( ibc_salsa_b == 1 )  THEN
    48404843          DO  m = 1, bc_h(0)%ns
  • 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'
  • palm/trunk/TESTS/cases/urban_environment_salsa/INPUT/urban_environment_salsa_p3d

    r4270 r4273  
    272272    advect_particle_water   = .T.,   ! particle water: advect or calculate at each dt_salsa
    273273    feedback_to_palm        = .F.,   ! feedback to flow due to condensation of water
    274     nest_salsa              = .F.,   ! apply self-nesting for salsa variables
     274    nesting_salsa           = .F.,   ! apply self-nesting for salsa variables
    275275    read_restart_data_salsa = .F.,   ! skip reading restart data even if it's done for the flow
    276276    write_binary_salsa      = .F.,   ! skip writing restart data even if it's done for the flow
Note: See TracChangeset for help on using the changeset viewer.