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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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!
Note: See TracChangeset for help on using the changeset viewer.