Changeset 3737 for palm


Ignore:
Timestamp:
Feb 12, 2019 4:57:06 PM (5 years ago)
Author:
suehring
Message:

Enable initialization of chemistry variables via dynamic input file; enable mesoscale offline nesting of chemistry variables if data is in dynamic input file

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r3727 r3737  
    2525# -----------------
    2626# $Id$
     27# Enable mesoscale offline nesting for chemistry variables as well as
     28# initialization of chemistry via dynamic input file.
     29#
     30# 3727 2019-02-08 14:52:10Z gronemeier
    2731# surface_data_output_mod depends on netcdf_interface_mod
    2832#
     
    13571361        user_module.o
    13581362nesting_offl_mod.o: \
     1363        chemistry_model_mod.o \
    13591364        cpulog_mod.o \
    13601365        mod_kinds.o \
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3719 r3737  
    2727! -----------------
    2828! $Id$
     29! Enable mesoscale offline nesting for chemistry variables as well as
     30! initialization of chemistry via dynamic input file.
     31!
     32! 3719 2019-02-06 13:10:18Z kanani
    2933! Resolved cpu logpoint overlap with all progn.equations, moved cpu_log call
    3034! to prognostic_equations for better overview
     
    14081412!                                                           TRIM(chem_species(lsp)%name)       
    14091413            IF (av == 0) THEN
     1414            write(9,*) "before", TRIM(chem_species(lsp)%name), fill_value
     1415            flush(9)
    14101416               DO  i = nxl, nxr
    14111417                  DO  j = nys, nyn
    14121418                     DO  k = nzb_do, nzt_do
     1419!                      write(9,*) k, j, i
     1420!                      flush(9)
     1421!                      write(9) chem_species(lsp)%conc(k,j,i)
     1422!                      flush(9)
     1423!                      write(9) "fill", fill_value
     1424!                      flush(9)
    14131425                         local_pf(i,j,k) = MERGE(                             &
    14141426                                             chem_species(lsp)%conc(k,j,i),   &
     
    17451757    USE chem_emissions_mod,                                                    &
    17461758        ONLY:  chem_emissions_init
     1759       
     1760    USE netcdf_data_input_mod,                                                 &
     1761        ONLY:  init_3d
    17471762
    17481763    IMPLICIT NONE
    17491764
     1765    INTEGER(iwp) ::  i !< running index x dimension
     1766    INTEGER(iwp) ::  j !< running index y dimension
     1767    INTEGER(iwp) ::  n !< running index for chemical species
    17501768
    17511769    IF ( do_emis )  CALL chem_emissions_init
     1770!
     1771!-- Chemistry variables will be initialized if availabe from dynamic
     1772!-- input file. Note, it is possible to initialize only part of the chemistry
     1773!-- variables from dynamic input.
     1774    IF ( INDEX( initializing_actions, 'inifor' ) /= 0 )  THEN
     1775       DO  n = 1, nspec
     1776          IF ( init_3d%from_file_chem(n) )  THEN
     1777             DO  i = nxlg, nxrg
     1778                DO  j = nysg, nyng
     1779                   chem_species(n)%conc(:,j,i) = init_3d%chem_init(:,n)
     1780                ENDDO
     1781             ENDDO
     1782          ENDIF
     1783       ENDDO
     1784    ENDIF
    17521785
    17531786
     
    17641797 SUBROUTINE chem_init_internal
    17651798
    1766     USE control_parameters,                                                  &
     1799    USE control_parameters,                                                    &
    17671800        ONLY:  message_string, io_blocks, io_group, turbulent_inflow
    1768     USE arrays_3d,                                                           &
     1801    USE arrays_3d,                                                             &
    17691802        ONLY:  mean_inflow_profiles
    17701803    USE pegrid
    17711804
    17721805    USE netcdf_data_input_mod,                                                 &
    1773         ONLY:  chem_emis, chem_emis_att, netcdf_data_input_chemistry_data
     1806        ONLY:  chem_emis, chem_emis_att, input_pids_dynamic, init_3d,          &
     1807               netcdf_data_input_chemistry_data
    17741808
    17751809    IMPLICIT NONE
     
    18391873!-- Initial concentration of profiles is prescribed by parameters cs_profile
    18401874!-- and cs_heights in the namelist &chemistry_parameters
    1841     CALL chem_init_profiles     
     1875    CALL chem_init_profiles
     1876!   
     1877!-- In case there is dynamic input file, create a list of names for chemistry
     1878!-- initial input files. Also, initialize array that indicates whether the
     1879!-- respective variable is on file or not.
     1880    IF ( input_pids_dynamic )  THEN   
     1881       ALLOCATE( init_3d%var_names_chem(1:nspec) )
     1882       ALLOCATE( init_3d%from_file_chem(1:nspec) )
     1883       init_3d%from_file_chem(:) = .FALSE.
     1884       
     1885       DO  lsp = 1, nspec
     1886          init_3d%var_names_chem(lsp) = init_3d%init_char // TRIM( chem_species(lsp)%name )
     1887       ENDDO
     1888    ENDIF
     1889
    18421890
    18431891
    18441892!
    18451893!-- Initialize model variables
    1846 
    1847 
    18481894    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.            &
    18491895         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
  • palm/trunk/SOURCE/nesting_offl_mod.f90

    r3705 r3737  
    2525! -----------------
    2626! $Id$
     27! Introduce mesoscale nesting for chemical species
     28!
     29! 3705 2019-01-29 19:56:39Z suehring
    2730! Formatting adjustments
    2831!
     
    5457    USE arrays_3d,                                                             &
    5558        ONLY:  dzw, e, diss, pt, pt_init, q, q_init, s, u, u_init, ug, v,      &
    56                v_init, vg, w, zu, zw         
     59               v_init, vg, w, zu, zw
     60                 
     61    USE chemistry_model_mod,                                                   &
     62        ONLY:  chem_species
    5763
    5864    USE control_parameters,                                                    &
    59         ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, bc_dirichlet_s, &
    60                dt_3d, dz, constant_diffusion, humidity, message_string,        &
    61                nesting_offline, neutral, passive_scalar, rans_mode, rans_tke_e,&
    62                time_since_reference_point, volume_flow
     65        ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, &
     66               bc_dirichlet_s, dt_3d, dz, constant_diffusion, humidity,        &
     67               message_string, nesting_offline, neutral, passive_scalar,       &
     68               rans_mode, rans_tke_e, time_since_reference_point, volume_flow
    6369               
    6470    USE cpulog,                                                                &
     
    235241       INTEGER(iwp) ::  j !< running index y-direction
    236242       INTEGER(iwp) ::  k !< running index z-direction
     243       INTEGER(iwp) ::  n !< running index for chemical species
    237244
    238245       REAL(wp) ::  fac_dt   !< interpolation factor
     
    335342             ENDDO
    336343          ENDIF
     344         
     345          IF ( air_chemistry )  THEN
     346             DO  n = 1, UBOUND( chem_species, 1 )
     347                IF ( nest_offl%chem_from_file_l(n) )  THEN                   
     348                   DO  j = nys, nyn
     349                      DO  k = nzb+1, nzt
     350                         chem_species(n)%conc(k,j,-1) = interpolate_in_time(   &
     351                                                  nest_offl%chem_left(0,k,j,n),&
     352                                                  nest_offl%chem_left(1,k,j,n),&
     353                                                  fac_dt                   )
     354                      ENDDO
     355                   ENDDO
     356                ENDIF
     357             ENDDO
     358          ENDIF
    337359
    338360       ENDIF
     
    395417             ENDDO
    396418          ENDIF
     419         
     420          IF ( air_chemistry )  THEN
     421             DO  n = 1, UBOUND( chem_species, 1 )
     422                IF ( nest_offl%chem_from_file_r(n) )  THEN 
     423                   DO  j = nys, nyn
     424                      DO  k = nzb+1, nzt
     425                         chem_species(n)%conc(k,j,nxr+1) = interpolate_in_time(&
     426                                                 nest_offl%chem_right(0,k,j,n),&
     427                                                 nest_offl%chem_right(1,k,j,n),&
     428                                                 fac_dt                       )
     429                      ENDDO
     430                   ENDDO
     431                ENDIF
     432             ENDDO
     433          ENDIF
    397434
    398435       ENDIF
     
    458495             ENDDO
    459496          ENDIF
     497         
     498          IF ( air_chemistry )  THEN
     499             DO  n = 1, UBOUND( chem_species, 1 )
     500                IF ( nest_offl%chem_from_file_s(n) )  THEN 
     501                   DO  i = nxl, nxr
     502                      DO  k = nzb+1, nzt
     503                         chem_species(n)%conc(k,-1,i) = interpolate_in_time(   &
     504                                                 nest_offl%chem_south(0,k,i,n),&
     505                                                 nest_offl%chem_south(1,k,i,n),&
     506                                                 fac_dt                    )
     507                      ENDDO
     508                   ENDDO
     509                ENDIF
     510             ENDDO
     511          ENDIF
    460512
    461513       ENDIF
     
    520572             ENDDO
    521573          ENDIF
     574         
     575          IF ( air_chemistry )  THEN
     576             DO  n = 1, UBOUND( chem_species, 1 )
     577                IF ( nest_offl%chem_from_file_n(n) )  THEN 
     578                   DO  i = nxl, nxr
     579                      DO  k = nzb+1, nzt
     580                         chem_species(n)%conc(k,nyn+1,i) = interpolate_in_time(&
     581                                                 nest_offl%chem_north(0,k,i,n),&
     582                                                 nest_offl%chem_north(1,k,i,n),&
     583                                                 fac_dt                       )
     584                      ENDDO
     585                   ENDDO
     586                ENDIF
     587             ENDDO
     588          ENDIF
    522589
    523590       ENDIF
     
    579646          ENDDO
    580647       ENDIF
     648       
     649       IF ( air_chemistry )  THEN
     650          DO  n = 1, UBOUND( chem_species, 1 )
     651             IF ( nest_offl%chem_from_file_t(n) )  THEN 
     652                DO  i = nxl, nxr
     653                   DO  j = nys, nyn
     654                      chem_species(n)%conc(nzt+1,j,i) = interpolate_in_time(   &
     655                                              nest_offl%chem_north(0,j,i,n),   &
     656                                              nest_offl%chem_north(1,j,i,n),   &
     657                                              fac_dt                       )
     658                   ENDDO
     659                ENDDO
     660             ENDIF
     661          ENDDO
     662       ENDIF
    581663!
    582664!--    Moreover, set Neumann boundary condition for subgrid-scale TKE,
     
    607689       IF ( .NOT. neutral )  CALL exchange_horiz( pt, nbgp )
    608690       IF ( humidity      )  CALL exchange_horiz( q,  nbgp )
     691       IF ( air_chemistry )  THEN
     692          DO  n = 1, UBOUND( chem_species, 1 )
     693             CALL exchange_horiz( chem_species(n)%conc, nbgp )
     694          ENDDO
     695       ENDIF
     696       
    609697!
    610698!--    In case of Rayleigh damping, where the profiles u_init, v_init
     
    9851073
    9861074       IMPLICIT NONE
     1075       
     1076       INTEGER(iwp) ::  n !< running index for chemical species
    9871077
    9881078
     
    10001090          IF ( humidity )       ALLOCATE( nest_offl%q_left(0:1,nzb+1:nzt,nys:nyn)  )
    10011091          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_left(0:1,nzb+1:nzt,nys:nyn) )
     1092          IF ( air_chemistry )  ALLOCATE( nest_offl%chem_left(0:1,nzb+1:nzt,nys:nyn,&
     1093                                          1:UBOUND( chem_species, 1 )) )
    10021094       ENDIF
    10031095       IF ( bc_dirichlet_r )  THEN
     
    10071099          IF ( humidity )       ALLOCATE( nest_offl%q_right(0:1,nzb+1:nzt,nys:nyn)  )
    10081100          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_right(0:1,nzb+1:nzt,nys:nyn) )
     1101          IF ( air_chemistry )  ALLOCATE( nest_offl%chem_right(0:1,nzb+1:nzt,nys:nyn,&
     1102                                          1:UBOUND( chem_species, 1 )) )
    10091103       ENDIF
    10101104       IF ( bc_dirichlet_n )  THEN
     
    10141108          IF ( humidity )       ALLOCATE( nest_offl%q_north(0:1,nzb+1:nzt,nxl:nxr)  )
    10151109          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_north(0:1,nzb+1:nzt,nxl:nxr) )
     1110          IF ( air_chemistry )  ALLOCATE( nest_offl%chem_north(0:1,nzb+1:nzt,nxl:nxr,&
     1111                                          1:UBOUND( chem_species, 1 )) )
    10161112       ENDIF
    10171113       IF ( bc_dirichlet_s )  THEN
     
    10211117          IF ( humidity )       ALLOCATE( nest_offl%q_south(0:1,nzb+1:nzt,nxl:nxr)  )
    10221118          IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_south(0:1,nzb+1:nzt,nxl:nxr) )
     1119          IF ( air_chemistry )  ALLOCATE( nest_offl%chem_south(0:1,nzb+1:nzt,nxl:nxr,&
     1120                                          1:UBOUND( chem_species, 1 )) )
    10231121       ENDIF
    10241122       
     
    10281126       IF ( humidity )       ALLOCATE( nest_offl%q_top(0:1,nys:nyn,nxl:nxr)  )
    10291127       IF ( .NOT. neutral )  ALLOCATE( nest_offl%pt_top(0:1,nys:nyn,nxl:nxr) )
    1030 
     1128       IF ( air_chemistry )  ALLOCATE( nest_offl%chem_top(0:1,nys:nyn,nxl:nxr, &
     1129                                       1:UBOUND( chem_species, 1 )) )
     1130!
     1131!--    For chemical species, create the names of the variables. This is necessary
     1132!--    to identify the respective variable and write it onto the correct array
     1133!--    in the chem_species datatype.
     1134       IF ( air_chemistry )  THEN
     1135          ALLOCATE( nest_offl%chem_from_file_l(1:UBOUND( chem_species, 1 )) )
     1136          ALLOCATE( nest_offl%chem_from_file_n(1:UBOUND( chem_species, 1 )) )
     1137          ALLOCATE( nest_offl%chem_from_file_r(1:UBOUND( chem_species, 1 )) )
     1138          ALLOCATE( nest_offl%chem_from_file_s(1:UBOUND( chem_species, 1 )) )
     1139          ALLOCATE( nest_offl%chem_from_file_t(1:UBOUND( chem_species, 1 )) )
     1140         
     1141          ALLOCATE( nest_offl%var_names_chem_l(1:UBOUND( chem_species, 1 )) )
     1142          ALLOCATE( nest_offl%var_names_chem_n(1:UBOUND( chem_species, 1 )) )
     1143          ALLOCATE( nest_offl%var_names_chem_r(1:UBOUND( chem_species, 1 )) )
     1144          ALLOCATE( nest_offl%var_names_chem_s(1:UBOUND( chem_species, 1 )) )
     1145          ALLOCATE( nest_offl%var_names_chem_t(1:UBOUND( chem_species, 1 )) )
     1146!
     1147!--       Initialize flags that indicate whether the variable is on file or
     1148!--       not. Please note, this is only necessary for chemistry variables.
     1149          nest_offl%chem_from_file_l(:) = .FALSE.
     1150          nest_offl%chem_from_file_n(:) = .FALSE.
     1151          nest_offl%chem_from_file_r(:) = .FALSE.
     1152          nest_offl%chem_from_file_s(:) = .FALSE.
     1153          nest_offl%chem_from_file_t(:) = .FALSE.
     1154         
     1155          DO  n = 1, UBOUND( chem_species, 1 )
     1156             nest_offl%var_names_chem_l(n) = nest_offl%char_l //               &
     1157                                                  TRIM(chem_species(n)%name)
     1158             nest_offl%var_names_chem_n(n) = nest_offl%char_n //               &
     1159                                                  TRIM(chem_species(n)%name)
     1160             nest_offl%var_names_chem_r(n) = nest_offl%char_r //               &
     1161                                                  TRIM(chem_species(n)%name)
     1162             nest_offl%var_names_chem_s(n) = nest_offl%char_s //               &
     1163                                                  TRIM(chem_species(n)%name)
     1164             nest_offl%var_names_chem_t(n) = nest_offl%char_t //               &
     1165                                                  TRIM(chem_species(n)%name)
     1166          ENDDO
     1167       ENDIF
    10311168!
    10321169!--    Read COSMO data at lateral and top boundaries
     
    10411178                                   nest_offl%pt_left(0,nzb+1:nzt,nys:nyn)
    10421179          IF ( humidity      )  q(nzb+1:nzt,nys:nyn,-1)  =                     &
    1043                                    nest_offl%q_left(0,nzb+1:nzt,nys:nyn)
     1180                                   nest_offl%q_left(0,nzb+1:nzt,nys:nyn)
     1181          IF ( air_chemistry )  THEN
     1182             DO  n = 1, UBOUND( chem_species, 1 )
     1183                IF( nest_offl%chem_from_file_l(n) )  THEN
     1184                   chem_species(n)%conc(nzb+1:nzt,nys:nyn,-1) =                &
     1185                                   nest_offl%chem_left(0,nzb+1:nzt,nys:nyn,n)
     1186                ENDIF
     1187             ENDDO
     1188          ENDIF
    10441189       ENDIF
    10451190       IF ( bc_dirichlet_r )  THEN
     
    10511196          IF ( humidity      )  q(nzb+1:nzt,nys:nyn,nxr+1)  =                  &
    10521197                                   nest_offl%q_right(0,nzb+1:nzt,nys:nyn)
     1198          IF ( air_chemistry )  THEN
     1199             DO  n = 1, UBOUND( chem_species, 1 )
     1200                IF( nest_offl%chem_from_file_r(n) )  THEN
     1201                   chem_species(n)%conc(nzb+1:nzt,nys:nyn,nxr+1) =             &
     1202                                   nest_offl%chem_right(0,nzb+1:nzt,nys:nyn,n)
     1203                ENDIF
     1204             ENDDO
     1205          ENDIF
    10531206       ENDIF
    10541207       IF ( bc_dirichlet_s )  THEN
     
    10601213          IF ( humidity      )  q(nzb+1:nzt,-1,nxl:nxr)  =                     &
    10611214                                   nest_offl%q_south(0,nzb+1:nzt,nxl:nxr)
     1215          IF ( air_chemistry )  THEN
     1216             DO  n = 1, UBOUND( chem_species, 1 )
     1217                IF( nest_offl%chem_from_file_s(n) )  THEN
     1218                   chem_species(n)%conc(nzb+1:nzt,-1,nxl:nxr) =                &
     1219                                   nest_offl%chem_south(0,nzb+1:nzt,nxl:nxr,n)
     1220                ENDIF
     1221             ENDDO
     1222          ENDIF
    10621223       ENDIF
    10631224       IF ( bc_dirichlet_n )  THEN
     
    10691230          IF ( humidity      )  q(nzb+1:nzt,nyn+1,nxl:nxr)  =                  &
    10701231                                   nest_offl%q_north(0,nzb+1:nzt,nxl:nxr)
     1232          IF ( air_chemistry )  THEN
     1233             DO  n = 1, UBOUND( chem_species, 1 )
     1234                IF( nest_offl%chem_from_file_n(n) )  THEN
     1235                   chem_species(n)%conc(nzb+1:nzt,nyn+1,nxl:nxr) =             &
     1236                                   nest_offl%chem_north(0,nzb+1:nzt,nxl:nxr,n)
     1237                ENDIF
     1238             ENDDO
     1239          ENDIF
    10711240       ENDIF
    10721241!
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r3705 r3737  
    2525! -----------------
    2626! $Id$
     27! Enable mesoscale offline nesting for chemistry variables as well as
     28! initialization of chemistry via dynamic input file.
     29!
     30! 3705 2019-01-29 19:56:39Z suehring
    2731! Interface for attribute input of 8-bit and 32-bit integer
    2832!
     
    310314    TYPE nest_offl_type
    311315
    312        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
     316       CHARACTER(LEN=16) ::  char_l = 'ls_forcing_left_'  !< leading substring for variables at left boundary
     317       CHARACTER(LEN=17) ::  char_n = 'ls_forcing_north_' !< leading substring for variables at north boundary 
     318       CHARACTER(LEN=17) ::  char_r = 'ls_forcing_right_' !< leading substring for variables at right boundary 
     319       CHARACTER(LEN=17) ::  char_s = 'ls_forcing_south_' !< leading substring for variables at south boundary
     320       CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'   !< leading substring for variables at top boundary
     321   
     322       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names         !< list of variable in dynamic input file
     323       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_l  !< names of mesoscale nested chemistry variables at left boundary
     324       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_n  !< names of mesoscale nested chemistry variables at north boundary
     325       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_r  !< names of mesoscale nested chemistry variables at right boundary
     326       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_s  !< names of mesoscale nested chemistry variables at south boundary
     327       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_t  !< names of mesoscale nested chemistry variables at top boundary
    313328
    314329       INTEGER(iwp) ::  nt     !< number of time levels in dynamic input file
     
    319334
    320335       LOGICAL      ::  init         = .FALSE. !< flag indicating that offline nesting is already initialized
     336       
     337       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_l !< flags inidicating whether left boundary data for chemistry is in dynamic input file 
     338       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_n !< flags inidicating whether north boundary data for chemistry is in dynamic input file
     339       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_r !< flags inidicating whether right boundary data for chemistry is in dynamic input file
     340       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_s !< flags inidicating whether south boundary data for chemistry is in dynamic input file
     341       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_t !< flags inidicating whether top boundary data for chemistry is in dynamic input file
    321342
    322343       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surface_pressure !< time dependent surface pressure
     
    357378       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_top    !< mixing ratio at top boundary
    358379       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
     380       
     381       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_left   !< chemical species at left boundary
     382       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_north  !< chemical species at left boundary
     383       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_right  !< chemical species at left boundary
     384       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_south  !< chemical species at left boundary
     385       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_top    !< chemical species at left boundary
    359386
    360387    END TYPE nest_offl_type
     
    362389    TYPE init_type
    363390
     391       CHARACTER(LEN=16) ::  init_char = 'init_atmosphere_'          !< leading substring for init variables
    364392       CHARACTER(LEN=23) ::  origin_time = '2000-01-01 00:00:00 +00' !< reference time of input data
     393       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem !< list of chemistry variable names that can potentially be on file
    365394
    366395       INTEGER(iwp) ::  lod_msoil !< level of detail - soil moisture
     
    378407       INTEGER(iwp) ::  nzu       !< number of vertical levels on scalar grid in dynamic input file
    379408       INTEGER(iwp) ::  nzw       !< number of vertical levels on w grid in dynamic input file
     409       
     410       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  lod_chem !< level of detail - chemistry variables
    380411
    381412       LOGICAL ::  from_file_msoil  = .FALSE. !< flag indicating whether soil moisture is already initialized from file
     
    388419       LOGICAL ::  from_file_vg     = .FALSE. !< flag indicating whether ug is already initialized from file
    389420       LOGICAL ::  from_file_w      = .FALSE. !< flag indicating whether w is already initialized from file
     421       
     422       LOGICAL, DIMENSION(:), ALLOCATABLE ::  from_file_chem !< flag indicating whether chemistry variable is read from file
    390423
    391424       REAL(wp) ::  fill_msoil              !< fill value for soil moisture
     
    403436       REAL(wp) ::  rotation_angle = 0.0_wp !< rotation angle of input data
    404437
     438       REAL(wp), DIMENSION(:), ALLOCATABLE ::  fill_chem    !< fill value - chemistry variables
    405439       REAL(wp), DIMENSION(:), ALLOCATABLE ::  msoil_1d     !< initial vertical profile of soil moisture
    406440       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init      !< initial vertical profile of pt
     
    415449       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos     !< vertical levels at scalar grid in dynamic input file, used for interpolation
    416450       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw_atmos     !< vertical levels at w grid in dynamic input file, used for interpolation
     451       
     452       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  chem_init  !< initial vertical profiles of chemistry variables
    417453
    418454
     
    727763    CHARACTER(LEN=100) ::  input_file_uvem    = 'PIDS_UVEM'    !< Name of file which comprises static uv_exposure model input data
    728764    CHARACTER(LEN=100) ::  input_file_vm      = 'PIDS_VM'      !< Name of file which comprises virtual measurement data
    729 
    730     CHARACTER (LEN=25), ALLOCATABLE, DIMENSION(:)    ::  string_values  !< output of string variables read from netcdf input files
     765   
     766    CHARACTER(LEN=25), ALLOCATABLE, DIMENSION(:)    ::  string_values  !< output of string variables read from netcdf input files
    731767
    732768    INTEGER(iwp)                                     ::  id_emis        !< NetCDF id of input file for chemistry emissions: TBD: It has to be removed
     
    27132749
    27142750       USE control_parameters,                                                 &
    2715            ONLY:  bc_lr_cyc, bc_ns_cyc, humidity, message_string, neutral
     2751           ONLY:  air_chemistry, bc_lr_cyc, bc_ns_cyc, humidity,               &
     2752                  message_string, neutral
    27162753
    27172754       USE indices,                                                            &
     
    27252762       
    27262763       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
     2764       INTEGER(iwp) ::  n          !< running index for chemistry variables
    27272765       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
    27282766
     
    30783116             CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
    30793117          ENDIF
     3118       ENDIF       
     3119!
     3120!--    Read chemistry variables.
     3121!--    Please note, for the moment, only LOD=1 is allowed
     3122       IF ( air_chemistry )  THEN
     3123!
     3124!--       Allocate chemistry input profiles, as well as arrays for fill values
     3125!--       and LOD's.
     3126          ALLOCATE( init_3d%chem_init(nzb:nzt+1,                               &
     3127                                      1:UBOUND(init_3d%var_names_chem, 1 )) )
     3128          ALLOCATE( init_3d%fill_chem(1:UBOUND(init_3d%var_names_chem, 1)) )   
     3129          ALLOCATE( init_3d%lod_chem(1:UBOUND(init_3d%var_names_chem, 1))  ) 
     3130         
     3131          DO  n = 1, UBOUND(init_3d%var_names_chem, 1)
     3132             IF ( check_existence( var_names,                                  &
     3133                                   TRIM( init_3d%var_names_chem(n) ) ) )  THEN
     3134!
     3135!--             Read attributes for the fill value and level-of-detail
     3136                CALL get_attribute( id_dynamic, char_fill,                     &
     3137                                    init_3d%fill_chem(n),                      &
     3138                                    .FALSE.,                                   &
     3139                                    TRIM( init_3d%var_names_chem(n) ) )
     3140                CALL get_attribute( id_dynamic, char_lod,                      &
     3141                                    init_3d%lod_chem(n),                       &
     3142                                    .FALSE.,                                   &
     3143                                    TRIM( init_3d%var_names_chem(n) ) )
     3144!
     3145!--             Give message that only LOD=1 is allowed.
     3146                IF ( init_3d%lod_chem(n) /= 1 )  THEN               
     3147                   message_string = 'For chemistry variables only LOD=1 is ' //&
     3148                                    'allowed.'
     3149                   CALL message( 'netcdf_data_input_mod', 'PA0586',            &
     3150                                 1, 2, 0, 6, 0 )
     3151                ENDIF
     3152!
     3153!--             level-of-detail 1 - read initialization profile
     3154                CALL get_variable( id_dynamic,                                 &
     3155                                   TRIM( init_3d%var_names_chem(n) ),          &
     3156                                   init_3d%chem_init(nzb+1:nzt,n) )
     3157!
     3158!--             Set bottom and top boundary condition (Neumann)
     3159                init_3d%chem_init(nzb,n)   = init_3d%chem_init(nzb+1,n)
     3160                init_3d%chem_init(nzt+1,n) = init_3d%chem_init(nzt,n)
     3161               
     3162                init_3d%from_file_chem(n) = .TRUE.
     3163             ENDIF
     3164          ENDDO
    30803165       ENDIF
    30813166!
     
    33263411
    33273412       USE control_parameters,                                                 &
    3328            ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,              &
    3329                   bc_dirichlet_s, humidity, neutral, nesting_offline,          &
    3330                   time_since_reference_point
     3413           ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n,               &
     3414                  bc_dirichlet_r, bc_dirichlet_s, humidity, neutral,           &
     3415                  nesting_offline, time_since_reference_point
    33313416
    33323417       USE indices,                                                            &
     
    33363421       
    33373422       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
     3423       INTEGER(iwp) ::  n          !< running index for chemistry variables
    33383424       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
    33393425       INTEGER(iwp) ::  t          !< running index time dimension
     
    34543540                           nys+1, nzb+1, nest_offl%tind+1,                     &
    34553541                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     3542          ENDIF
     3543         
     3544          IF ( air_chemistry )  THEN
     3545             DO  n = 1, UBOUND(nest_offl%var_names_chem_l, 1)
     3546                IF ( check_existence( nest_offl%var_names,                     &
     3547                                      nest_offl%var_names_chem_l(n) ) )        &
     3548                THEN
     3549                   CALL get_variable( id_dynamic,                              &
     3550                              TRIM( nest_offl%var_names_chem_l(n) ),           &
     3551                              nest_offl%chem_left(0:1,nzb+1:nzt,nys:nyn,n),    &
     3552                              nys+1, nzb+1, nest_offl%tind+1,                  &
     3553                              nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     3554                   nest_offl%chem_from_file_l(n) = .TRUE.
     3555                ENDIF
     3556             ENDDO
    34563557          ENDIF
    34573558
     
    34853586                           nys+1, nzb+1, nest_offl%tind+1,                     &
    34863587                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     3588          ENDIF
     3589         
     3590          IF ( air_chemistry )  THEN
     3591             DO  n = 1, UBOUND(nest_offl%var_names_chem_r, 1)
     3592                IF ( check_existence( nest_offl%var_names,                     &
     3593                                      nest_offl%var_names_chem_r(n) ) )        &
     3594                THEN
     3595                   CALL get_variable( id_dynamic,                              &
     3596                              TRIM( nest_offl%var_names_chem_r(n) ),           &
     3597                              nest_offl%chem_right(0:1,nzb+1:nzt,nys:nyn,n),   &
     3598                              nys+1, nzb+1, nest_offl%tind+1,                  &
     3599                              nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
     3600                   nest_offl%chem_from_file_r(n) = .TRUE.
     3601                ENDIF
     3602             ENDDO
    34873603          ENDIF
    34883604       ENDIF
     
    35173633                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
    35183634          ENDIF
     3635         
     3636          IF ( air_chemistry )  THEN
     3637             DO  n = 1, UBOUND(nest_offl%var_names_chem_n, 1)
     3638                IF ( check_existence( nest_offl%var_names,                     &
     3639                                      nest_offl%var_names_chem_n(n) ) )        &
     3640                THEN
     3641                   CALL get_variable( id_dynamic,                              &
     3642                              TRIM( nest_offl%var_names_chem_n(n) ),           &
     3643                              nest_offl%chem_north(0:1,nzb+1:nzt,nxl:nxr,n),   &
     3644                              nxl+1, nzb+1, nest_offl%tind+1,                  &
     3645                              nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
     3646                   nest_offl%chem_from_file_n(n) = .TRUE.
     3647                ENDIF
     3648             ENDDO
     3649          ENDIF
    35193650       ENDIF
    35203651
     
    35473678                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
    35483679          ENDIF
     3680         
     3681          IF ( air_chemistry )  THEN
     3682             DO  n = 1, UBOUND(nest_offl%var_names_chem_s, 1)
     3683                IF ( check_existence( nest_offl%var_names,                     &
     3684                                      nest_offl%var_names_chem_s(n) ) )        &
     3685                THEN
     3686                   CALL get_variable( id_dynamic,                              &
     3687                              TRIM( nest_offl%var_names_chem_s(n) ),           &
     3688                              nest_offl%chem_south(0:1,nzb+1:nzt,nxl:nxr,n),   &
     3689                              nxl+1, nzb+1, nest_offl%tind+1,                  &
     3690                              nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
     3691                   nest_offl%chem_from_file_s(n) = .TRUE.
     3692                ENDIF
     3693             ENDDO
     3694          ENDIF
    35493695       ENDIF
    35503696
     
    35773723                                nxl+1, nys+1, nest_offl%tind+1,                &
    35783724                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
     3725       ENDIF
     3726       
     3727       IF ( air_chemistry )  THEN
     3728          DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
     3729             IF ( check_existence( nest_offl%var_names,                     &
     3730                                   nest_offl%var_names_chem_t(n) ) )  THEN     
     3731                CALL get_variable( id_dynamic,                                 &
     3732                              TRIM( nest_offl%var_names_chem_t(n) ),           &
     3733                              nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,n),       &
     3734                              nxl+1, nys+1, nest_offl%tind+1,                  &
     3735                              nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
     3736                nest_offl%chem_from_file_t(n) = .TRUE.
     3737             ENDIF
     3738          ENDDO
    35793739       ENDIF
    35803740
Note: See TracChangeset for help on using the changeset viewer.