Ignore:
Timestamp:
Jun 14, 2019 2:04:35 PM (5 years ago)
Author:
raasch
Message:

bugfix: decycling of chemistry species after nesting data transfer, exchange of ghost points and boundary conditions separated for chemical species and SALSA module, nest_chemistry option removed, netcdf variable NF90_NOFILL is used as argument instead of 1 in calls to NF90_DEF_VAR_FILL

File:
1 edited

Legend:

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

    r4022 r4029  
    2525! -----------------
    2626! $Id$
     27! exchange of ghost points and boundary conditions separated for chemical species and SALSA module,
     28! bugfix: decycling of chemistry species after nesting data transfer
     29!
     30! 4022 2019-06-12 11:52:39Z suehring
    2731! Call synthetic turbulence generator at last RK3 substep right after boundary
    2832! conditions are updated in offline nesting in order to assure that
     
    10681072             DO  lsp = 1, nvar
    10691073                CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
    1070 !
    1071 !--             kanani: Push chem_boundary_conds after CALL boundary_conds
     1074             ENDDO
     1075          ENDIF
     1076
     1077          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
     1078             DO  ib = 1, nbins_aerosol
     1079                CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp )
     1080                DO  ic = 1, ncomponents_mass
     1081                   icc = ( ic - 1 ) * nbins_aerosol + ib
     1082                   CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp )
     1083                ENDDO
     1084             ENDDO
     1085             IF ( .NOT. salsa_gases_from_chem )  THEN
     1086                DO  ig = 1, ngases_salsa
     1087                   CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp )
     1088                ENDDO
     1089             ENDIF
     1090          ENDIF
     1091          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
     1092
     1093!
     1094!--       Boundary conditions for the prognostic quantities (except of the
     1095!--       velocities at the outflow in case of a non-cyclic lateral wall)
     1096          CALL boundary_conds
     1097
     1098!
     1099!--       Boundary conditions for prognostic quantitites of other modules:
     1100!--       Here, only decycling is carried out
     1101          IF ( air_chemistry )  THEN
     1102
     1103             DO  lsp = 1, nvar
    10721104                lsp_usr = 1
    10731105                DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    1074                    IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
     1106                   IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
    10751107                      CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
    10761108                                                chem_species(lsp)%conc_pr_init )
     
    10791111                ENDDO
    10801112             ENDDO
     1113
    10811114          ENDIF
    10821115
    10831116          IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
    1084 !
    1085 !--          Exchange ghost points and decycle boundary concentrations if needed
     1117
    10861118             DO  ib = 1, nbins_aerosol
    1087                 CALL exchange_horiz( aerosol_number(ib)%conc_p, nbgp )
    10881119                CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
    10891120                DO  ic = 1, ncomponents_mass
    10901121                   icc = ( ic - 1 ) * nbins_aerosol + ib
    1091                    CALL exchange_horiz( aerosol_mass(icc)%conc_p, nbgp )
    10921122                   CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
    10931123                ENDDO
     
    10951125             IF ( .NOT. salsa_gases_from_chem )  THEN
    10961126                DO  ig = 1, ngases_salsa
    1097                    CALL exchange_horiz( salsa_gas(ig)%conc_p, nbgp )
    10981127                   CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
    10991128                ENDDO
    11001129             ENDIF
    1101           ENDIF
    1102           CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
    1103 
    1104 !
    1105 !--       Boundary conditions for the prognostic quantities (except of the
    1106 !--       velocities at the outflow in case of a non-cyclic lateral wall)
    1107           CALL boundary_conds
     1130
     1131          ENDIF
     1132
    11081133!
    11091134!--       Swap the time levels in preparation for the next time step.
     
    11301155
    11311156             IF ( TRIM( nesting_mode ) == 'two-way' .OR.  nesting_mode == 'vertical' )  THEN
     1157
     1158                CALL cpu_log( log_point_s(92), 'exchange-horiz-nest', 'start' )
    11321159!
    11331160!--             Exchange_horiz is needed for all parent-domains after the
     
    11701197                   DO  ib = 1, nbins_aerosol
    11711198                      CALL exchange_horiz( aerosol_number(ib)%conc, nbgp )
    1172                       CALL salsa_boundary_conds( aerosol_number(ib)%conc, aerosol_number(ib)%init )
    11731199                      DO  ic = 1, ncomponents_mass
    11741200                         icc = ( ic - 1 ) * nbins_aerosol + ib
    11751201                         CALL exchange_horiz( aerosol_mass(icc)%conc, nbgp )
    1176                          CALL salsa_boundary_conds( aerosol_mass(icc)%conc, aerosol_mass(icc)%init )
    11771202                      ENDDO
    11781203                   ENDDO
     
    11801205                      DO  ig = 1, ngases_salsa
    11811206                         CALL exchange_horiz( salsa_gas(ig)%conc, nbgp )
    1182                          CALL salsa_boundary_conds( salsa_gas(ig)%conc, salsa_gas(ig)%init )
    11831207                      ENDDO
    11841208                   ENDIF
    11851209                ENDIF
    1186                 CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'stop' )
    1187 
    1188              ENDIF
     1210                CALL cpu_log( log_point_s(92), 'exchange-horiz-nest', 'stop' )
     1211
     1212             ENDIF
     1213
    11891214!
    11901215!--          Set boundary conditions again after interpolation and anterpolation.
    11911216             CALL pmci_boundary_conds
     1217
     1218!
     1219!--          Set chemistry boundary conditions (decycling)
     1220             IF ( air_chemistry )  THEN
     1221                DO  lsp = 1, nvar
     1222                   lsp_usr = 1
     1223                   DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     1224                      IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
     1225                         CALL chem_boundary_conds( chem_species(lsp)%conc,                         &
     1226                                                   chem_species(lsp)%conc_pr_init )
     1227                      ENDIF
     1228                      lsp_usr = lsp_usr + 1
     1229                   ENDDO
     1230                ENDDO
     1231             ENDIF
     1232
     1233!
     1234!--          Set SALSA boundary conditions (decycling)
     1235             IF ( salsa  .AND. time_since_reference_point >= skip_time_do_salsa )  THEN
     1236                DO  ib = 1, nbins_aerosol
     1237                   CALL salsa_boundary_conds( aerosol_number(ib)%conc, aerosol_number(ib)%init )
     1238                   DO  ic = 1, ncomponents_mass
     1239                      icc = ( ic - 1 ) * nbins_aerosol + ib
     1240                      CALL salsa_boundary_conds( aerosol_mass(icc)%conc, aerosol_mass(icc)%init )
     1241                   ENDDO
     1242                ENDDO
     1243                IF ( .NOT. salsa_gases_from_chem )  THEN
     1244                   DO  ig = 1, ngases_salsa
     1245                      CALL salsa_boundary_conds( salsa_gas(ig)%conc, salsa_gas(ig)%init )
     1246                   ENDDO
     1247                ENDIF
     1248             ENDIF
    11921249
    11931250             CALL cpu_log( log_point(60), 'nesting', 'stop' )
Note: See TracChangeset for help on using the changeset viewer.