Ignore:
Timestamp:
Apr 12, 2019 5:52:01 PM (5 years ago)
Author:
suehring
Message:

Bugfix in initialization of turbulence generator in case of restart runs and offline nesting

File:
1 edited

Legend:

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

    r3885 r3891  
    2525! -----------------
    2626! $Id$
     27! Bugfix, do not overwrite lateral and top boundary data in case of restart
     28! runs.
     29!
     30! 3885 2019-04-11 11:29:34Z kanani
    2731! Changes related to global restructuring of location messages and introduction
    2832! of additional debug messages
     
    7377        ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,  &
    7478               bc_dirichlet_s, dt_3d, dz, constant_diffusion,                  &
    75                debug_output, debug_string,                                     &
    76                humidity,                                                       &
     79               debug_output, debug_string, humidity, initializing_actions,     &
    7780               message_string, nesting_offline, neutral, passive_scalar,       &
    7881               rans_mode, rans_tke_e, time_since_reference_point, volume_flow
     
    12091212       CALL netcdf_data_input_offline_nesting
    12101213!
    1211 !--    Initialize boundary data.
    1212        IF ( bc_dirichlet_l )  THEN
    1213           u(nzb+1:nzt,nys:nyn,0)    = nest_offl%u_left(0,nzb+1:nzt,nys:nyn)
    1214           v(nzb+1:nzt,nysv:nyn,-1)  = nest_offl%v_left(0,nzb+1:nzt,nysv:nyn)
    1215           w(nzb+1:nzt-1,nys:nyn,-1) = nest_offl%w_left(0,nzb+1:nzt-1,nys:nyn)
    1216           IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,-1) =                     &
    1217                                    nest_offl%pt_left(0,nzb+1:nzt,nys:nyn)
    1218           IF ( humidity      )  q(nzb+1:nzt,nys:nyn,-1)  =                     &
    1219                                    nest_offl%q_left(0,nzb+1:nzt,nys:nyn)
    1220           IF ( air_chemistry )  THEN
    1221              DO  n = 1, UBOUND( chem_species, 1 )
    1222                 IF( nest_offl%chem_from_file_l(n) )  THEN
    1223                    chem_species(n)%conc(nzb+1:nzt,nys:nyn,-1) =                &
    1224                                    nest_offl%chem_left(0,nzb+1:nzt,nys:nyn,n)
    1225                 ENDIF
    1226              ENDDO
    1227           ENDIF
    1228        ENDIF
    1229        IF ( bc_dirichlet_r )  THEN
    1230           u(nzb+1:nzt,nys:nyn,nxr+1)   = nest_offl%u_right(0,nzb+1:nzt,nys:nyn)
    1231           v(nzb+1:nzt,nysv:nyn,nxr+1)  = nest_offl%v_right(0,nzb+1:nzt,nysv:nyn)
    1232           w(nzb+1:nzt-1,nys:nyn,nxr+1) = nest_offl%w_right(0,nzb+1:nzt-1,nys:nyn)
    1233           IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,nxr+1) =                  &
    1234                                    nest_offl%pt_right(0,nzb+1:nzt,nys:nyn)
    1235           IF ( humidity      )  q(nzb+1:nzt,nys:nyn,nxr+1)  =                  &
    1236                                    nest_offl%q_right(0,nzb+1:nzt,nys:nyn)
    1237           IF ( air_chemistry )  THEN
    1238              DO  n = 1, UBOUND( chem_species, 1 )
    1239                 IF( nest_offl%chem_from_file_r(n) )  THEN
    1240                    chem_species(n)%conc(nzb+1:nzt,nys:nyn,nxr+1) =             &
    1241                                    nest_offl%chem_right(0,nzb+1:nzt,nys:nyn,n)
    1242                 ENDIF
    1243              ENDDO
    1244           ENDIF
    1245        ENDIF
    1246        IF ( bc_dirichlet_s )  THEN
    1247           u(nzb+1:nzt,-1,nxlu:nxr)  = nest_offl%u_south(0,nzb+1:nzt,nxlu:nxr)
    1248           v(nzb+1:nzt,0,nxl:nxr)    = nest_offl%v_south(0,nzb+1:nzt,nxl:nxr)
    1249           w(nzb+1:nzt-1,-1,nxl:nxr) = nest_offl%w_south(0,nzb+1:nzt-1,nxl:nxr)
    1250           IF ( .NOT. neutral )  pt(nzb+1:nzt,-1,nxl:nxr) =                     &
    1251                                    nest_offl%pt_south(0,nzb+1:nzt,nxl:nxr)
    1252           IF ( humidity      )  q(nzb+1:nzt,-1,nxl:nxr)  =                     &
    1253                                    nest_offl%q_south(0,nzb+1:nzt,nxl:nxr)
    1254           IF ( air_chemistry )  THEN
    1255              DO  n = 1, UBOUND( chem_species, 1 )
    1256                 IF( nest_offl%chem_from_file_s(n) )  THEN
    1257                    chem_species(n)%conc(nzb+1:nzt,-1,nxl:nxr) =                &
    1258                                    nest_offl%chem_south(0,nzb+1:nzt,nxl:nxr,n)
    1259                 ENDIF
    1260              ENDDO
    1261           ENDIF
    1262        ENDIF
    1263        IF ( bc_dirichlet_n )  THEN
    1264           u(nzb+1:nzt,nyn+1,nxlu:nxr)  = nest_offl%u_north(0,nzb+1:nzt,nxlu:nxr)
    1265           v(nzb+1:nzt,nyn+1,nxl:nxr)   = nest_offl%v_north(0,nzb+1:nzt,nxl:nxr)
    1266           w(nzb+1:nzt-1,nyn+1,nxl:nxr) = nest_offl%w_north(0,nzb+1:nzt-1,nxl:nxr)
    1267           IF ( .NOT. neutral )  pt(nzb+1:nzt,nyn+1,nxl:nxr) =                  &
    1268                                    nest_offl%pt_north(0,nzb+1:nzt,nxl:nxr)
    1269           IF ( humidity      )  q(nzb+1:nzt,nyn+1,nxl:nxr)  =                  &
    1270                                    nest_offl%q_north(0,nzb+1:nzt,nxl:nxr)
    1271           IF ( air_chemistry )  THEN
    1272              DO  n = 1, UBOUND( chem_species, 1 )
    1273                 IF( nest_offl%chem_from_file_n(n) )  THEN
    1274                    chem_species(n)%conc(nzb+1:nzt,nyn+1,nxl:nxr) =             &
    1275                                    nest_offl%chem_north(0,nzb+1:nzt,nxl:nxr,n)
    1276                 ENDIF
    1277              ENDDO
    1278           ENDIF
    1279        ENDIF
    1280 !
    1281 !--    Initialize geostrophic wind components. Actually this is already done in
    1282 !--    init_3d_model when initializing_action = 'inifor', however, in speical
    1283 !--    case of user-defined initialization this will be done here again, in
    1284 !--    order to have a consistent initialization.
    1285        ug(nzb+1:nzt) = nest_offl%ug(0,nzb+1:nzt)
    1286        vg(nzb+1:nzt) = nest_offl%vg(0,nzb+1:nzt)
    1287 !
    1288 !--    Set bottom and top boundary condition for geostrophic wind components
    1289        ug(nzt+1) = ug(nzt)
    1290        vg(nzt+1) = vg(nzt)
    1291        ug(nzb)   = ug(nzb+1)
    1292        vg(nzb)   = vg(nzb+1)
    1293 !
    1294 !--    Initial calculation of the boundary layer depth from the prescribed
    1295 !--    boundary data. This is requiered for initialize the synthetic turbulence
    1296 !--    generator correctly.
    1297        CALL calc_zi
    1298        
     1214!--    Initialize boundary data. Please note, do not initialize boundaries in
     1215!--    case of restart runs. This case the boundaries are already initialized
     1216!--    and the boundary data from file would be on the wrong time level. 
     1217       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     1218          IF ( bc_dirichlet_l )  THEN
     1219             u(nzb+1:nzt,nys:nyn,0)    = nest_offl%u_left(0,nzb+1:nzt,nys:nyn)
     1220             v(nzb+1:nzt,nysv:nyn,-1)  = nest_offl%v_left(0,nzb+1:nzt,nysv:nyn)
     1221             w(nzb+1:nzt-1,nys:nyn,-1) = nest_offl%w_left(0,nzb+1:nzt-1,nys:nyn)
     1222             IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,-1) =                  &
     1223                                      nest_offl%pt_left(0,nzb+1:nzt,nys:nyn)
     1224             IF ( humidity      )  q(nzb+1:nzt,nys:nyn,-1)  =                  &
     1225                                      nest_offl%q_left(0,nzb+1:nzt,nys:nyn)
     1226             IF ( air_chemistry )  THEN
     1227                DO  n = 1, UBOUND( chem_species, 1 )
     1228                   IF( nest_offl%chem_from_file_l(n) )  THEN
     1229                      chem_species(n)%conc(nzb+1:nzt,nys:nyn,-1) =             &
     1230                                      nest_offl%chem_left(0,nzb+1:nzt,nys:nyn,n)
     1231                   ENDIF
     1232                ENDDO
     1233             ENDIF
     1234          ENDIF
     1235          IF ( bc_dirichlet_r )  THEN
     1236             u(nzb+1:nzt,nys:nyn,nxr+1)   = nest_offl%u_right(0,nzb+1:nzt,nys:nyn)
     1237             v(nzb+1:nzt,nysv:nyn,nxr+1)  = nest_offl%v_right(0,nzb+1:nzt,nysv:nyn)
     1238             w(nzb+1:nzt-1,nys:nyn,nxr+1) = nest_offl%w_right(0,nzb+1:nzt-1,nys:nyn)
     1239             IF ( .NOT. neutral )  pt(nzb+1:nzt,nys:nyn,nxr+1) =               &
     1240                                      nest_offl%pt_right(0,nzb+1:nzt,nys:nyn)
     1241             IF ( humidity      )  q(nzb+1:nzt,nys:nyn,nxr+1)  =               &
     1242                                      nest_offl%q_right(0,nzb+1:nzt,nys:nyn)
     1243             IF ( air_chemistry )  THEN
     1244                DO  n = 1, UBOUND( chem_species, 1 )
     1245                   IF( nest_offl%chem_from_file_r(n) )  THEN
     1246                      chem_species(n)%conc(nzb+1:nzt,nys:nyn,nxr+1) =          &
     1247                                      nest_offl%chem_right(0,nzb+1:nzt,nys:nyn,n)
     1248                   ENDIF
     1249                ENDDO
     1250             ENDIF
     1251          ENDIF
     1252          IF ( bc_dirichlet_s )  THEN
     1253             u(nzb+1:nzt,-1,nxlu:nxr)  = nest_offl%u_south(0,nzb+1:nzt,nxlu:nxr)
     1254             v(nzb+1:nzt,0,nxl:nxr)    = nest_offl%v_south(0,nzb+1:nzt,nxl:nxr)
     1255             w(nzb+1:nzt-1,-1,nxl:nxr) = nest_offl%w_south(0,nzb+1:nzt-1,nxl:nxr)
     1256             IF ( .NOT. neutral )  pt(nzb+1:nzt,-1,nxl:nxr) =                  &
     1257                                      nest_offl%pt_south(0,nzb+1:nzt,nxl:nxr)
     1258             IF ( humidity      )  q(nzb+1:nzt,-1,nxl:nxr)  =                  &
     1259                                      nest_offl%q_south(0,nzb+1:nzt,nxl:nxr)
     1260             IF ( air_chemistry )  THEN
     1261                DO  n = 1, UBOUND( chem_species, 1 )
     1262                   IF( nest_offl%chem_from_file_s(n) )  THEN
     1263                      chem_species(n)%conc(nzb+1:nzt,-1,nxl:nxr) =             &
     1264                                      nest_offl%chem_south(0,nzb+1:nzt,nxl:nxr,n)
     1265                   ENDIF
     1266                ENDDO
     1267             ENDIF
     1268          ENDIF
     1269          IF ( bc_dirichlet_n )  THEN
     1270             u(nzb+1:nzt,nyn+1,nxlu:nxr)  = nest_offl%u_north(0,nzb+1:nzt,nxlu:nxr)
     1271             v(nzb+1:nzt,nyn+1,nxl:nxr)   = nest_offl%v_north(0,nzb+1:nzt,nxl:nxr)
     1272             w(nzb+1:nzt-1,nyn+1,nxl:nxr) = nest_offl%w_north(0,nzb+1:nzt-1,nxl:nxr)
     1273             IF ( .NOT. neutral )  pt(nzb+1:nzt,nyn+1,nxl:nxr) =               &
     1274                                      nest_offl%pt_north(0,nzb+1:nzt,nxl:nxr)
     1275             IF ( humidity      )  q(nzb+1:nzt,nyn+1,nxl:nxr)  =               &
     1276                                      nest_offl%q_north(0,nzb+1:nzt,nxl:nxr)
     1277             IF ( air_chemistry )  THEN
     1278                DO  n = 1, UBOUND( chem_species, 1 )
     1279                   IF( nest_offl%chem_from_file_n(n) )  THEN
     1280                      chem_species(n)%conc(nzb+1:nzt,nyn+1,nxl:nxr) =          &
     1281                                      nest_offl%chem_north(0,nzb+1:nzt,nxl:nxr,n)
     1282                   ENDIF
     1283                ENDDO
     1284             ENDIF
     1285          ENDIF
     1286!         
     1287!--       Initialize geostrophic wind components. Actually this is already done in
     1288!--       init_3d_model when initializing_action = 'inifor', however, in speical
     1289!--       case of user-defined initialization this will be done here again, in
     1290!--       order to have a consistent initialization.
     1291          ug(nzb+1:nzt) = nest_offl%ug(0,nzb+1:nzt)
     1292          vg(nzb+1:nzt) = nest_offl%vg(0,nzb+1:nzt)
     1293!         
     1294!--       Set bottom and top boundary condition for geostrophic wind components
     1295          ug(nzt+1) = ug(nzt)
     1296          vg(nzt+1) = vg(nzt)
     1297          ug(nzb)   = ug(nzb+1)
     1298          vg(nzb)   = vg(nzb+1)
     1299       ENDIF     
    12991300!
    13001301!--    After boundary data is initialized, mask topography at the
     
    13031304       v = MERGE( v, 0.0_wp, BTEST( wall_flags_0, 2 ) )
    13041305       w = MERGE( w, 0.0_wp, BTEST( wall_flags_0, 3 ) )
    1305        
     1306!
     1307!--    Initial calculation of the boundary layer depth from the prescribed
     1308!--    boundary data. This is requiered for initialize the synthetic turbulence
     1309!--    generator correctly.
    13061310       CALL calc_zi
    13071311       
    13081312!
    1309 !--    After boundary data is initialized, ensure mass conservation
    1310        CALL nesting_offl_mass_conservation
     1313!--    After boundary data is initialized, ensure mass conservation. Not
     1314!--    necessary in restart runs.
     1315       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     1316          CALL nesting_offl_mass_conservation
     1317       ENDIF
    13111318
    13121319    END SUBROUTINE nesting_offl_init
Note: See TracChangeset for help on using the changeset viewer.