1 !=======================================================================
3 MODULE module_check_a_mundo
7 ! Contains subroutines that check the consistency of some namelist
8 ! settings. Some namelist settings depend on other values in the
9 ! namelist. The routine check_nml_consistency can detect quite a
10 ! few fatal inconsistencies. These are all bundled up as a convenience.
11 ! The fatal errors are reported, and after the routine completes, then
12 ! a single call to wrf_error_fatal is issued. The setup_physics_suite routine
13 ! has only one fatal call, so that routine does not need this user-
14 ! friendly concept of bundling errors. The set_physics_rconfigs
15 ! routine does not detect any problems that would result in a fatal
16 ! error, so the bundling of errors is also not required there.
18 ! SUBROUTINE check_nml_consistency :
19 ! Check namelist settings for consistency
21 ! SUBROUTINE setup_physics_suite :
22 ! Interpret user setting as referring to which supported schemes
23 ! Currently: conus and tropical
25 ! SUBROUTINE set_physics_rconfigs :
26 ! Check namelist settings that determine memory allocations.
30 USE module_state_description
31 USE module_model_constants
37 !=======================================================================
41 !=======================================================================
43 SUBROUTINE check_nml_consistency
47 ! Check consistency of namelist settings
51 USE module_bep_bem_helper, ONLY: nurbm
55 LOGICAL :: exists, vnest
56 LOGICAL , EXTERNAL :: wrf_dm_on_monitor
57 INTEGER :: i, j, oops, d1_value, EDMFMAX, SCHUMAX
59 LOGICAL :: km_opt_already_done , diff_opt_already_done
61 LOGICAL :: lon_extent_is_global , lat_extent_is_global
62 LOGICAL :: rinblw_already_done
63 LOGICAL :: fsbm_table1_exists, fsbm_table2_exists
64 INTEGER :: count_fatal_error
65 INTEGER :: len1, len2, len_loop
67 ! These functions are located with in the Urban Physics files, but
68 ! not within the confines of the modules. Since we are in the share
69 ! directory, we need to break possible circular build dependencies.
72 INTEGER FUNCTION bep_nurbm()
73 END FUNCTION bep_nurbm
75 INTEGER FUNCTION bep_ndm()
78 INTEGER FUNCTION bep_nz_um()
79 END FUNCTION bep_nz_um
81 INTEGER FUNCTION bep_ng_u()
84 INTEGER FUNCTION bep_nwr_u()
85 END FUNCTION bep_nwr_u
87 INTEGER FUNCTION bep_bem_nurbm()
88 END FUNCTION bep_bem_nurbm
90 INTEGER FUNCTION bep_bem_ndm()
91 END FUNCTION bep_bem_ndm
93 INTEGER FUNCTION bep_bem_nz_um()
94 END FUNCTION bep_bem_nz_um
96 INTEGER FUNCTION bep_bem_ng_u()
97 END FUNCTION bep_bem_ng_u
99 INTEGER FUNCTION bep_bem_nwr_u()
100 END FUNCTION bep_bem_nwr_u
102 INTEGER FUNCTION bep_bem_nf_u()
103 END FUNCTION bep_bem_nf_u
105 INTEGER FUNCTION bep_bem_ngb_u()
106 END FUNCTION bep_bem_ngb_u
108 INTEGER FUNCTION bep_bem_nbui_max()
109 END FUNCTION bep_bem_nbui_max
111 INTEGER FUNCTION bep_bem_ngr_u()
112 END FUNCTION bep_bem_ngr_u
116 !-----------------------------------------------------------------------
117 ! Set up the WRF Hydro namelist option to allow dynamic allocation of
119 !-----------------------------------------------------------------------
120 count_fatal_error = 0
122 model_config_rec % wrf_hydro = 1
124 model_config_rec % wrf_hydro = 0
128 !-----------------------------------------------------------------------
129 ! AFWA diagnostics require each domain is treated the same. If
130 ! any domain has an option activated, all domains must have that
132 !-----------------------------------------------------------------------
133 do i=1,model_config_rec%max_dom
134 if ( model_config_rec%afwa_diag_opt(i) .EQ. 1 ) then
135 model_config_rec%afwa_diag_opt(:) = 1
139 do i=1,model_config_rec%max_dom
140 if ( model_config_rec%afwa_ptype_opt(i) .EQ. 1 ) then
141 model_config_rec%afwa_ptype_opt(:) = 1
145 do i=1,model_config_rec%max_dom
146 if ( model_config_rec%afwa_vil_opt(i) .EQ. 1 ) then
147 model_config_rec%afwa_vil_opt(:) = 1
151 do i=1,model_config_rec%max_dom
152 if ( model_config_rec%afwa_radar_opt(i) .EQ. 1 ) then
153 model_config_rec%afwa_radar_opt(:) = 1
157 do i=1,model_config_rec%max_dom
158 if ( model_config_rec%afwa_severe_opt(i) .EQ. 1 ) then
159 model_config_rec%afwa_severe_opt(:) = 1
163 do i=1,model_config_rec%max_dom
164 if ( model_config_rec%afwa_icing_opt(i) .EQ. 1 ) then
165 model_config_rec%afwa_icing_opt(:) = 1
169 do i=1,model_config_rec%max_dom
170 if ( model_config_rec%afwa_cloud_opt(i) .EQ. 1 ) then
171 model_config_rec%afwa_cloud_opt(:) = 1
175 do i=1,model_config_rec%max_dom
176 if ( model_config_rec%afwa_vis_opt(i) .EQ. 1 ) then
177 model_config_rec%afwa_vis_opt(:) = 1
181 do i=1,model_config_rec%max_dom
182 if ( model_config_rec%afwa_therm_opt(i) .EQ. 1 ) then
183 model_config_rec%afwa_therm_opt(:) = 1
187 do i=1,model_config_rec%max_dom
188 if ( model_config_rec%afwa_turb_opt(i) .EQ. 1 ) then
189 model_config_rec%afwa_turb_opt(:) = 1
193 do i=1,model_config_rec%max_dom
194 if ( model_config_rec%afwa_buoy_opt(i) .EQ. 1 ) then
195 model_config_rec%afwa_buoy_opt(:) = 1
200 !-----------------------------------------------------------------------
201 ! If any AFWA diagnostics are activated, there is a minimum that
202 ! must always be activated.
203 !-----------------------------------------------------------------------
204 do i=1,model_config_rec%max_dom
205 if ( ( model_config_rec%afwa_ptype_opt(i) .EQ. 1 ) .OR. &
206 ( model_config_rec%afwa_vil_opt(i) .EQ. 1 ) .OR. &
207 ( model_config_rec%afwa_radar_opt(i) .EQ. 1 ) .OR. &
208 ( model_config_rec%afwa_severe_opt(i) .EQ. 1 ) .OR. &
209 ( model_config_rec%afwa_icing_opt(i) .EQ. 1 ) .OR. &
210 ( model_config_rec%afwa_cloud_opt(i) .EQ. 1 ) .OR. &
211 ( model_config_rec%afwa_vis_opt(i) .EQ. 1 ) .OR. &
212 ( model_config_rec%afwa_therm_opt(i) .EQ. 1 ) .OR. &
213 ( model_config_rec%afwa_turb_opt(i) .EQ. 1 ) .OR. &
214 ( model_config_rec%afwa_buoy_opt(i) .EQ. 1 ) ) then
215 model_config_rec%afwa_diag_opt(i)=1
219 !-----------------------------------------------------------------------
220 ! LBC: Always the case, nested setup up: F, T, T, T
221 !-----------------------------------------------------------------------
222 model_config_rec%nested(1) = .FALSE.
223 DO i=2,model_config_rec%max_dom
224 model_config_rec%nested(i) = .TRUE.
227 !-----------------------------------------------------------------------
228 ! LBC: Always the case, nested domain BCs are always false.
229 !-----------------------------------------------------------------------
230 DO i=2,model_config_rec%max_dom
231 model_config_rec%periodic_x(i) = .FALSE.
232 model_config_rec%symmetric_xs(i) = .FALSE.
233 model_config_rec%symmetric_xe(i) = .FALSE.
234 model_config_rec%open_xs(i) = .FALSE.
235 model_config_rec%open_xe(i) = .FALSE.
236 model_config_rec%periodic_y(i) = .FALSE.
237 model_config_rec%symmetric_ys(i) = .FALSE.
238 model_config_rec%symmetric_ye(i) = .FALSE.
239 model_config_rec%open_ys(i) = .FALSE.
240 model_config_rec%open_ye(i) = .FALSE.
241 model_config_rec%polar(i) = .FALSE.
242 model_config_rec%specified(i) = .FALSE.
245 !-----------------------------------------------------------------------
246 ! LBC: spec_bdy_width = spec_zone + relax_zone
247 !-----------------------------------------------------------------------
248 IF ( model_config_rec%specified(1) ) THEN
249 model_config_rec%spec_zone = 1
250 model_config_rec%relax_zone = model_config_rec%spec_bdy_width - model_config_rec%spec_zone
255 !-----------------------------------------------------------------------
256 ! The nominal grid distance on each child domain is ENTIRELY a function
257 ! of the MOAD grid distance and the accumulated recursive parent grid ratios
258 ! of each child domain. Even if the child grid distance values are specified
259 ! in the namelist file, overwrite the dx and dy namelist input with the
260 ! computed grid distance values.
261 !-----------------------------------------------------------------------
263 DO i = 1, model_config_rec % max_dom
264 IF ( .NOT. model_config_rec % grid_allowed(i) ) THEN
265 WRITE(wrf_err_message,FMT='(A,I2,A)') 'Domain #',i,': grid turned OFF'
266 CALL wrf_debug ( 0, wrf_err_message )
271 call get_moad_factor ( id, model_config_rec % parent_id, &
272 model_config_rec % parent_grid_ratio, &
273 model_config_rec % max_dom, factor )
274 model_config_rec % dx(i) = model_config_rec % dx(1) / REAL(factor)
275 model_config_rec % dy(i) = model_config_rec % dy(1) / REAL(factor)
276 WRITE(wrf_err_message,FMT='(A,I2,A,F9.3,A)') 'Domain #',i,': dx = ',model_config_rec % dx(i),' m'
277 CALL wrf_debug ( 0, wrf_err_message )
280 !-----------------------------------------------------------------------
281 ! Check that all values of diff_opt and km_opt are filled in. A flag
282 ! value of "-1" from the nml file means that this column (domain) is not
283 ! filled as a max_doamins variable. Since we changed these two variables
284 ! from being single entries to max_domain entries, we need to do special
285 ! checking. If there are missing values (if we find any -1 entries), we
286 ! fill those columns with the value from the entry from column (domain) #1.
287 !-----------------------------------------------------------------------
289 km_opt_already_done = .FALSE.
290 diff_opt_already_done = .FALSE.
291 DO i = 2, model_config_rec % max_dom
292 IF ( model_config_rec % km_opt(i) .EQ. -1 ) THEN
293 model_config_rec % km_opt(i) = model_config_rec % km_opt(1)
294 IF ( .NOT. km_opt_already_done ) THEN
295 wrf_err_message = 'Setting blank km_opt entries to domain #1 values.'
296 CALL wrf_debug ( 1, wrf_err_message )
297 wrf_err_message = ' --> The km_opt entry in the namelist.input is now max_domains.'
298 CALL wrf_debug ( 1, wrf_err_message )
300 km_opt_already_done = .TRUE.
302 IF ( model_config_rec % diff_opt(i) .EQ. -1 ) THEN
303 model_config_rec % diff_opt(i) = model_config_rec % diff_opt(1)
304 IF ( .NOT. diff_opt_already_done ) THEN
305 wrf_err_message = 'Setting blank diff_opt entries to domain #1 values.'
306 CALL wrf_debug ( 1, wrf_err_message )
307 wrf_err_message = ' --> The diff_opt entry in the namelist.input is now max_domains.'
308 CALL wrf_debug ( 1, wrf_err_message )
310 diff_opt_already_done = .TRUE.
315 !-----------------------------------------------------------------------
316 ! Check that km_opt and diff_opt are not -1. If the first column is set
317 ! to -1, that means this entry is NOT in the namelist file at all.
318 !-----------------------------------------------------------------------
320 IF ( ( model_config_rec % km_opt(1) .EQ. -1 ) .OR. &
321 ( model_config_rec % diff_opt(1) .EQ. -1 ) ) THEN
322 wrf_err_message = '--- ERROR: Both km_opt and diff_opt need to be set in the namelist.input file.'
323 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
324 count_fatal_error = count_fatal_error + 1
327 !-----------------------------------------------------------------------
328 ! Check that multi_perturb and adptive time setp are not both activated
329 !-----------------------------------------------------------------------
331 DO i = 1, model_config_rec % max_dom
332 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
333 IF ((model_config_rec%multi_perturb(i) == 1) .and. model_config_rec%use_adaptive_time_step) then
334 wrf_err_message = '--- ERROR: multi_perturb and adpative time step are not compatible.'
335 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
336 count_fatal_error = count_fatal_error + 1
340 !-----------------------------------------------------------------------
341 ! Check that SMS-3DTKE scheme (km_opt=5) Must work with diff_opt=2
342 !-----------------------------------------------------------------------
343 DO i = 1, model_config_rec % max_dom
344 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
345 IF ( model_config_rec % km_opt(i) .EQ. 5 .AND. &
346 model_config_rec % diff_opt(i) .NE. 2 ) THEN
347 wrf_err_message = '--- ERROR: SMS-3DTKE scheme can only work with diff_opt=2 '
348 CALL wrf_message ( wrf_err_message )
349 wrf_err_message = '--- ERROR: Fix km_opt or diff_opt in namelist.input.'
350 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
351 count_fatal_error = count_fatal_error + 1
355 !-----------------------------------------------------------------------
356 ! Check that SMS-3DTKE scheme (km_opt=5) Must work with bl_pbl_physics=0
357 !-----------------------------------------------------------------------
358 DO i = 1, model_config_rec % max_dom
359 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
360 IF ( model_config_rec % km_opt(i) .EQ. 5 .AND. &
361 model_config_rec % bl_pbl_physics(i) .NE. 0 ) THEN
362 wrf_err_message = '--- ERROR: SMS-3DTKE scheme can only work with bl_pbl_physics=0 '
363 CALL wrf_message ( wrf_err_message )
364 wrf_err_message = '--- ERROR: Fix km_opt or bl_pbl_physics in namelist.input.'
365 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
366 count_fatal_error = count_fatal_error + 1
370 !-----------------------------------------------------------------------
371 ! Check MAD-WRF configuration
372 !-----------------------------------------------------------------------
373 DO i = 1, model_config_rec % max_dom
374 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
375 IF ( model_config_rec % madwrf_opt .EQ. 1 .AND. &
376 (model_config_rec % mp_physics(i) .NE. 96 .or. &
377 model_config_rec % use_mp_re /= 0)) THEN
378 wrf_err_message = '--- ERROR: madwrf_opt = 1 requires mp_physics=96 and use_mp_re=0'
379 CALL wrf_message ( wrf_err_message )
380 count_fatal_error = count_fatal_error + 1
384 !-----------------------------------------------------------------------
385 ! Check that SMS-3DTKE scheme Must work with Revised MM5 surface layer
386 ! scheme (sf_sfclay_physics = 1), MYNN surface (sf_sfclay_physics = 5)
387 ! and old MM5 surface scheme (sf_sfclay_physics = 91). Also, SMS-3DTKE
388 ! Must work with no surface layer scheme.
389 !-----------------------------------------------------------------------
390 DO i = 1, model_config_rec % max_dom
391 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
392 IF ( model_config_rec % km_opt(i) .EQ. 5 .AND. &
393 (model_config_rec % sf_sfclay_physics(i) .NE. nosfcscheme .AND. &
394 model_config_rec % sf_sfclay_physics(i) .NE. sfclayscheme .AND. &
395 model_config_rec % sf_sfclay_physics(i) .NE. sfclayrevscheme .AND. &
396 model_config_rec % sf_sfclay_physics(i) .NE. mynnsfcscheme ) ) THEN
397 wrf_err_message = '--- ERROR: SMS-3DTKE scheme works with sf_sfclay_physics = 0,1,5,91 '
398 CALL wrf_message ( wrf_err_message )
399 wrf_err_message = '--- ERROR: Fix km_opt or sf_sfclay_physics in namelist.input.'
400 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
401 count_fatal_error = count_fatal_error + 1
406 !-----------------------------------------------------------------------
407 ! Check that LES PBL is only paired with acceptable other PBL options.
408 ! Currently, problems occur with any CG PBL option that has a packaged
409 ! scalar component: MYNN2, MYNN3, EEPS. This test is also if a user
410 ! chooses to not run a PBL scheme on a finer domain, but use a PBL
411 ! parameterized scheme on a coarser domain (obviously, just for testing
413 !-----------------------------------------------------------------------
415 DO i = 1, model_config_rec % max_dom
416 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
417 IF ( model_config_rec % bl_pbl_physics(i) .EQ. LESscheme ) THEN
421 IF ( ( exists ) .AND. &
422 ( ( model_config_rec % bl_pbl_physics(1) .EQ. MYNNPBLSCHEME ) .OR. &
423 ( model_config_rec % bl_pbl_physics(1) .EQ. EEPSSCHEME ) ) ) THEN
424 WRITE(wrf_err_message,fmt='(a,i2)') '--- ERROR: LES PBL on fine grid does not work with CG PBL option ',model_config_rec % bl_pbl_physics(1)
425 CALL wrf_message ( TRIM( wrf_err_message ) )
426 wrf_err_message = ' Fix bl_pbl_physics in namelist.input: choose a CG PBL option without any scalar components'
427 CALL wrf_message ( TRIM( wrf_err_message ) )
428 wrf_err_message = ' Alternatively, remove all of the packaged variables from the CG PBL selection'
429 CALL wrf_message ( TRIM( wrf_err_message ) )
430 count_fatal_error = count_fatal_error + 1
434 !-----------------------------------------------------------------------
435 ! Check that if the user has requested to use the shallow water surface
436 ! roughness drag option, then the only surface layer scheme permitted
437 ! to be used is the revised MM5 MO option.
438 !-----------------------------------------------------------------------
439 DO i = 1, model_config_rec % max_dom
440 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
441 IF ( ( model_config_rec % shalwater_z0(i) .NE. 0 ) .AND. &
442 ( model_config_rec % sf_sfclay_physics(i) .NE. sfclayrevscheme ) ) THEN
443 wrf_err_message = '--- ERROR: Shallow water surface roughness only works with sfclay_physics = 1'
444 CALL wrf_message ( TRIM( wrf_err_message ) )
445 wrf_err_message = ' Fix shalwater_z0 or sf_sfclay_physics in namelist.input.'
446 CALL wrf_message ( TRIM( wrf_err_message ) )
447 count_fatal_error = count_fatal_error + 1
451 !-----------------------------------------------------------------------
452 ! Urban physics set up. If the run-time option for use_wudapt_lcz = 0,
453 ! then the number of urban classes is 3. Else, if the use_wudapt_lcz = 1,
454 ! then the number increases to 11. The seemingly local variable
455 ! assignment, "nurbm", is actually USE associated from the BEP BEM
457 !-----------------------------------------------------------------------
458 IF ( model_config_rec%use_wudapt_lcz .EQ. 0 ) THEN
460 ELSE IF ( model_config_rec%use_wudapt_lcz .EQ. 1 ) THEN
464 !-----------------------------------------------------------------------
465 ! Assign the dimensions for the urban options to the values defined in
466 ! each of those respective modules.
467 !-----------------------------------------------------------------------
468 DO i = 1, model_config_rec % max_dom
469 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
470 IF ( model_config_rec % sf_urban_physics(i) == bepscheme ) THEN
471 model_config_rec % num_urban_ndm = bep_ndm()
472 model_config_rec % num_urban_nz = bep_nz_um()
473 model_config_rec % num_urban_ng = bep_ng_u()
474 model_config_rec % num_urban_nwr = bep_nwr_u()
476 IF ( model_config_rec % sf_urban_physics(i) == bep_bemscheme ) THEN
477 model_config_rec % num_urban_ndm = bep_bem_ndm()
478 model_config_rec % num_urban_nz = bep_bem_nz_um()
479 model_config_rec % num_urban_ng = bep_bem_ng_u()
480 model_config_rec % num_urban_nwr = bep_bem_nwr_u()
481 model_config_rec % num_urban_nf = bep_bem_nf_u()
482 model_config_rec % num_urban_ngb = bep_bem_ngb_u()
483 model_config_rec % num_urban_nbui = bep_bem_nbui_max()
484 model_config_rec % num_urban_ngr = bep_bem_ngr_u()
489 !-----------------------------------------------------------------------
490 ! Check that mosiac option cannot turn on when sf_urban_physics = 2 and 3
491 !-----------------------------------------------------------------------
492 DO i = 1, model_config_rec % max_dom
493 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
494 IF ( model_config_rec % sf_surface_mosaic .EQ. 1 .AND. &
495 (model_config_rec % sf_urban_physics(i) .EQ. 2 .OR. &
496 model_config_rec % sf_urban_physics(i) .EQ. 3 ) ) THEN
497 wrf_err_message = '--- ERROR: mosaic option cannot work with urban options 2 and 3 '
498 CALL wrf_message ( wrf_err_message )
499 wrf_err_message = '--- ERROR: Fix sf_surface_mosaic and sf_urban_physics in namelist.input.'
500 CALL wrf_message ( wrf_err_message )
501 wrf_err_message = '--- ERROR: Either: use Noah LSM without the mosaic option, OR change the urban option to 1 '
502 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
503 count_fatal_error = count_fatal_error + 1
507 !-----------------------------------------------------------------------
508 ! Check that only compatible options are set when slucm_distributed_drag is set
509 !-----------------------------------------------------------------------
510 IF (model_config_rec % slucm_distributed_drag) THEN
512 IF (model_config_rec % use_wudapt_lcz .EQ. 1) THEN
513 wrf_err_message = '--- ERROR: slucm_distributed_drag cannot work with use_wudapt_lcz'
514 CALL wrf_message ( wrf_err_message )
515 count_fatal_error = count_fatal_error + 1
518 DO i = 1, model_config_rec % max_dom
519 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
520 IF ( model_config_rec % sf_urban_physics(i) > 1 ) THEN
521 wrf_err_message = '--- ERROR: slucm_distributed_drag only works with urban options 1'
522 CALL wrf_message ( wrf_err_message )
523 count_fatal_error = count_fatal_error + 1
529 !-----------------------------------------------------------------------
530 ! Check that channel irrigation is run with Noah
531 !-----------------------------------------------------------------------
532 DO i = 1, model_config_rec % max_dom
533 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
534 IF ( model_config_rec % sf_surface_physics(i) .NE. LSMSCHEME .AND. &
535 model_config_rec % sf_surf_irr_scheme(i) .EQ. CHANNEL ) THEN
536 wrf_err_message = '--- ERROR: irrigation Opt 1 works only with Noah-LSM'
537 CALL wrf_message ( wrf_err_message )
538 count_fatal_error = count_fatal_error + 1
542 !-----------------------------------------------------------------------
543 ! Check that number of hours of daily irrigation is greater than zero.
544 ! This value is used in the denominator to compute the amount of
545 ! irrigated water per timestep, and the default value from the Registry
546 ! is zero. This is a reminder to the user that this value needs to be
548 !-----------------------------------------------------------------------
550 DO i = 1, model_config_rec % max_dom
551 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
552 IF ( ( ( model_config_rec % sf_surf_irr_scheme(i) .EQ. CHANNEL ) .OR. &
553 ( model_config_rec % sf_surf_irr_scheme(i) .EQ. SPRINKLER ) .OR. &
554 ( model_config_rec % sf_surf_irr_scheme(i) .EQ. DRIP ) ) .AND. &
555 ( model_config_rec % irr_num_hours(i) .LE. 0 ) ) THEN
560 IF ( oops .GT. 0 ) THEN
561 wrf_err_message = '--- ERROR: irr_num_hours must be greater than zero to work with irrigation'
562 CALL wrf_message ( wrf_err_message )
563 count_fatal_error = count_fatal_error + 1
566 !-----------------------------------------------------------------------
567 ! Fix derived setting for irrigation. Since users may only want the irrigation
568 ! to be active in the inner-most domain, we have a separate variable that is
569 ! used to define packaging for the irrigation fields.
570 !-----------------------------------------------------------------------
571 DO i = 1, model_config_rec % max_dom
572 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
573 IF ( model_config_rec % sf_surf_irr_scheme(i) .EQ. CHANNEL ) THEN
574 model_config_rec % sf_surf_irr_alloc = CHANNEL
576 IF ( model_config_rec % sf_surf_irr_scheme(i) .EQ. SPRINKLER ) THEN
577 model_config_rec % sf_surf_irr_alloc = SPRINKLER
579 IF ( model_config_rec % sf_surf_irr_scheme(i) .EQ. DRIP ) THEN
580 model_config_rec % sf_surf_irr_alloc = DRIP
584 !-----------------------------------------------------------------------
585 ! Check that Deng Shallow Convection Must work with MYJ or MYNN PBL
586 !-----------------------------------------------------------------------
587 DO i = 1, model_config_rec % max_dom
588 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
589 IF ( model_config_rec % shcu_physics(i) == dengshcuscheme .AND. &
590 (model_config_rec % bl_pbl_physics(i) /= myjpblscheme .AND. &
591 model_config_rec % bl_pbl_physics(i) /= mynnpblscheme ) ) THEN
592 wrf_err_message = '--- ERROR: Deng shallow convection can only work with MYJ or MYNN (with bl_mynn_edmf off) PBL '
593 CALL wrf_message ( wrf_err_message )
594 wrf_err_message = '--- ERROR: Fix shcu_physics or bl_pbl_physics in namelist.input.'
595 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
596 count_fatal_error = count_fatal_error + 1
600 !-----------------------------------------------------------------------
601 ! If Deng Shallow Convection is on, icloud cannot be 3
602 !-----------------------------------------------------------------------
604 DO i = 1, model_config_rec % max_dom
605 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
606 IF ( ( model_config_rec%shcu_physics(i) .EQ. dengshcuscheme ) .AND. &
607 ( model_config_rec%icloud .EQ. 3 ) ) THEN
612 IF ( oops .GT. 0 ) THEN
613 wrf_err_message = '--- ERROR: Options shcu_physics = 5 and icloud = 3 should not be used together'
614 CALL wrf_message ( wrf_err_message )
615 wrf_err_message = '--- ERROR: Choose either one in namelist.input and rerun the model'
616 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
617 count_fatal_error = count_fatal_error + 1
620 !-----------------------------------------------------------------------
621 ! If Deng Shallow Convection is on, icloud_bl cannot be 1
622 !-----------------------------------------------------------------------
624 DO i = 1, model_config_rec % max_dom
625 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
626 IF ( ( model_config_rec%shcu_physics(i) .EQ. dengshcuscheme ) .AND. &
627 ( model_config_rec%icloud_bl .EQ. 1 ) ) THEN
632 IF ( oops .GT. 0 ) THEN
633 wrf_err_message = '--- ERROR: Options shcu_physics = 5 and icloud_bl = 1 should not be used together'
634 CALL wrf_message ( wrf_err_message )
635 wrf_err_message = '--- ERROR: Choose either one in namelist.input and rerun the model'
636 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
637 count_fatal_error = count_fatal_error + 1
640 !-----------------------------------------------------------------------
641 ! If couple_farms is true, swint_opt must be 2
642 !-----------------------------------------------------------------------
643 IF ( model_config_rec%couple_farms .AND. model_config_rec%swint_opt /= 2 ) THEN
644 wrf_err_message = '--- ERROR: Options couple_farms = T requires swint_opt = 2'
645 CALL wrf_message ( wrf_err_message )
646 wrf_err_message = '--- ERROR: Change either one in namelist.input and rerun the model'
647 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
648 count_fatal_error = count_fatal_error + 1
651 !-----------------------------------------------------------------------
652 ! For ARW users, a request for CU=4 (SAS) should be switched to option
654 !-----------------------------------------------------------------------
656 DO i = 1, model_config_rec % max_dom
657 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
658 IF ( model_config_rec%cu_physics(i) .EQ. scalesasscheme ) THEN
663 IF ( oops .GT. 0 ) THEN
664 wrf_err_message = '--- ERROR: Option cu_physics = 4 should not be used for ARW; cu_physics = 95 is suggested'
665 CALL wrf_message ( wrf_err_message )
666 wrf_err_message = '--- ERROR: Choose a different cu_physics option in the namelist.input file'
667 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
668 count_fatal_error = count_fatal_error + 1
671 !-----------------------------------------------------------------------
672 ! There is a binary file for Goddard radiation. It is single precision.
673 !-----------------------------------------------------------------------
674 # if ( defined(PROMOTE_FLOAT) || ( RWORDSIZE == DWORDSIZE ) )
675 god_r8 : DO i = 1, model_config_rec % max_dom
676 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
677 IF ( ( model_config_rec % ra_lw_physics(i) == goddardlwscheme ) .OR. &
678 ( model_config_rec % ra_sw_physics(i) == goddardswscheme ) ) THEN
679 wrf_err_message = '--- ERROR: Goddard radiation scheme cannot run with real*8 floats'
680 CALL wrf_message ( wrf_err_message )
681 wrf_err_message = '--- Fix ra_lw_physics and ra_sw_physics in namelist.input '
682 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
683 count_fatal_error = count_fatal_error + 1
690 !-----------------------------------------------------------------------
691 ! With CMAQ coupling, if the option "direct_sw_feedback" is activated,
692 ! then the only SW radiation scheme set up to support this is RRTMG.
693 !-----------------------------------------------------------------------
694 # if ( WRF_CMAQ == 1 )
695 cmaq : DO i = 1, model_config_rec % max_dom
696 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
697 IF ( ( model_config_rec % direct_sw_feedback ) .AND. &
698 ( model_config_rec % wrf_cmaq_option .EQ. 1 ) .AND. &
699 ( model_config_rec % ra_sw_physics(i) .NE. rrtmg_swscheme ) ) THEN
700 wrf_err_message = '--- ERROR: With CMAQ coupling, "direct_sw_feedback=T" requires RRTMG SW'
701 CALL wrf_message ( wrf_err_message )
702 count_fatal_error = count_fatal_error + 1
707 cmaq : DO i = 1, model_config_rec % max_dom
708 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
709 IF ( ( model_config_rec % direct_sw_feedback ) .OR. &
710 ( model_config_rec % wrf_cmaq_option .EQ. 1 ) ) THEN
711 wrf_err_message = '--- ERROR: The option "direct_sw_feedback=T" and "wrf_cmaq_option==1" require CMAQ coupling'
712 CALL wrf_message ( wrf_err_message )
713 count_fatal_error = count_fatal_error + 1
719 !-----------------------------------------------------------------------
720 ! Print a warning message for not using a combination of radiation and microphysics from Goddard
721 !-----------------------------------------------------------------------
722 DO i = 1, model_config_rec % max_dom
723 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
724 IF ( ( (model_config_rec % ra_lw_physics(i) == goddardlwscheme .OR. &
725 model_config_rec % ra_sw_physics(i) == goddardswscheme) .AND. &
726 model_config_rec % mp_physics(i) /= nuwrf4icescheme ) .OR. &
727 ( model_config_rec % mp_physics(i) == nuwrf4icescheme .AND. &
728 (model_config_rec % ra_lw_physics(i) /= goddardlwscheme .AND. &
729 model_config_rec % ra_sw_physics(i) /= goddardswscheme) ) ) THEN
730 wrf_err_message = '--- WARNING: Goddard radiation and Goddard 4ice microphysics are not used together'
731 CALL wrf_message ( wrf_err_message )
732 wrf_err_message = '--- WARNING: These options may be best to use together.'
733 CALL wrf_message ( wrf_err_message )
739 !-----------------------------------------------------------------------
740 ! Check that all values of sf_surface_physics are the same for all domains
741 !-----------------------------------------------------------------------
743 DO i = 2, model_config_rec % max_dom
744 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
745 IF ( model_config_rec % sf_surface_physics(i) .NE. &
746 model_config_rec % sf_surface_physics(1) ) THEN
747 wrf_err_message = '--- ERROR: sf_surface_physics must be equal for all domains '
748 CALL wrf_message ( wrf_err_message )
749 wrf_err_message = '--- Fix sf_surface_physics in namelist.input '
750 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
751 count_fatal_error = count_fatal_error + 1
756 !-----------------------------------------------------------------------
757 ! Check that all values of sf_sfclay_physics are the same for all domains
758 !-----------------------------------------------------------------------
760 DO i = 2, model_config_rec % max_dom
761 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
762 IF ( model_config_rec % sf_sfclay_physics(i) .NE. &
763 model_config_rec % sf_sfclay_physics(1) ) THEN
764 wrf_err_message = '--- ERROR: sf_sfclay_physics must be equal for all domains '
765 CALL wrf_message ( wrf_err_message )
766 wrf_err_message = '--- Fix sf_sfclay_physics in namelist.input '
767 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
768 count_fatal_error = count_fatal_error + 1
773 !-----------------------------------------------------------------------
774 ! Check that all values of mp_physics are the same for all domains
775 !-----------------------------------------------------------------------
777 DO i = 2, model_config_rec % max_dom
778 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
779 IF ( model_config_rec % mp_physics(i) .NE. &
780 model_config_rec % mp_physics(1) ) THEN
781 wrf_err_message = '--- NOTE: mp_physics must be equal for all domains '
782 CALL wrf_debug ( 1, wrf_err_message )
783 wrf_err_message = '--- NOTE: ----> Setting all mp_physics entries to value defined in the inner most domain'
784 CALL wrf_debug ( 1, wrf_err_message )
787 d1_value = model_config_rec%mp_physics(model_config_rec % max_dom)
788 DO i = 1, model_config_rec % max_dom-1
789 model_config_rec%mp_physics(i) = d1_value
793 !--------------------------------------------------------------------------------------------------
794 ! Input tables must exist in running directory for fast bin microphysics scheme (mp_physics = 30)
795 !--------------------------------------------------------------------------------------------------
796 # if ( BUILD_SBM_FAST == 1 )
797 IF ( model_config_rec % mp_physics(1) .EQ. FAST_KHAIN_LYNN_SHPUND ) THEN
798 INQUIRE(FILE='./SBM_input_33/BLKD_SDC.dat', EXIST=fsbm_table1_exists)
799 IF (.not.fsbm_table1_exists ) THEN
800 wrf_err_message = "--- ERROR: Input directory SBM_input_33 doesn't exist !!!"
801 CALL wrf_message ( wrf_err_message )
802 wrf_err_message = '--- ERROR: Download this directory of table files from http://www2.mmm.ucar.edu/wrf/src/wrf_files/'
803 CALL wrf_message ( wrf_err_message )
804 count_fatal_error = count_fatal_error + 1
806 INQUIRE(FILE='./scattering_tables_2layer_high_quad_1dT_1%fw_110/GRAUPEL_+00C_000fvw.sct', EXIST=fsbm_table2_exists)
807 IF (.not.fsbm_table2_exists ) THEN
808 wrf_err_message = "--- ERROR: Input directory scattering_tables_2layer_high_quad_1dT_1%fw_110 doesn't exist !!!"
809 CALL wrf_message ( TRIM( wrf_err_message ) )
810 wrf_err_message = '--- ERROR: Download this directory of input table files from http://www2.mmm.ucar.edu/wrf/src/wrf_files/'
811 CALL wrf_message ( wrf_err_message )
812 count_fatal_error = count_fatal_error + 1
816 !-----------------------------------------------------------------------
817 ! There are restrictions on the AFWA diagnostics regarding the choice
818 ! of microphysics scheme. These are hard coded in the AFWA diags driver,
819 ! so while this is inelegant, it is about as good as we can do.
820 !-----------------------------------------------------------------------
821 IF ( model_config_rec%afwa_diag_opt(1) .EQ. 1 ) THEN
822 IF ( ( model_config_rec % mp_physics(1) .EQ. GSFCGCESCHEME ) .OR. &
823 ( model_config_rec % mp_physics(1) .EQ. ETAMPNEW ) .OR. &
824 ( model_config_rec % mp_physics(1) .EQ. THOMPSON ) .OR. &
825 ( model_config_rec % mp_physics(1) .EQ. WSM5SCHEME ) .OR. &
826 ( model_config_rec % mp_physics(1) .EQ. WSM6SCHEME ) .OR. &
827 ( model_config_rec % mp_physics(1) .EQ. WDM6SCHEME ) .OR. &
828 ( model_config_rec % mp_physics(1) .EQ. MORR_TWO_MOMENT ) .OR. &
829 ( model_config_rec % mp_physics(1) .EQ. MORR_TM_AERO ) ) THEN
832 wrf_err_message = '--- WARNING: the AFWA diagnostics option knows only about the following MP schemes:'
833 CALL wrf_message ( wrf_err_message )
834 wrf_err_message = '--- GSFCGCESCHEME, ETAMPNEW, THOMPSON, WSM5SCHEME, WSM6SCHEME, MORR_TWO_MOMENT, MORR_TM_AERO, WDM6SCHEME'
835 CALL wrf_message ( wrf_err_message )
841 !-----------------------------------------------------------------------
842 ! Check that all values of ra_physics are the same for all domains
843 !-----------------------------------------------------------------------
845 DO i = 2, model_config_rec % max_dom
846 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
847 IF ( model_config_rec % ra_lw_physics(i) .NE. &
848 model_config_rec % ra_lw_physics(1) ) THEN
849 wrf_err_message = '--- ERROR: ra_lw_physics must be equal for all domains '
850 CALL wrf_message ( wrf_err_message )
851 wrf_err_message = '--- Fix ra_lw_physics in namelist.input '
852 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
853 count_fatal_error = count_fatal_error + 1
857 DO i = 2, model_config_rec % max_dom
858 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
859 IF ( model_config_rec % ra_sw_physics(i) .NE. &
860 model_config_rec % ra_sw_physics(1) ) THEN
861 wrf_err_message = '--- ERROR: ra_sw_physics must be equal for all domains '
862 CALL wrf_message ( wrf_err_message )
863 wrf_err_message = '--- Fix ra_sw_physics in namelist.input '
864 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
865 count_fatal_error = count_fatal_error + 1
870 !------------------------------------------------------------------------------
871 ! Check that a value for time_step is given, and is not just set to default (-1)
872 !------------------------------------------------------------------------------
874 IF ( ( model_config_rec % use_wps_input == 0 ) .AND. &
875 ( model_config_rec % time_step .EQ. -1 ) ) THEN
877 wrf_err_message = '--- ERROR: Known problem. time_step must be set to a positive integer'
878 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
879 count_fatal_error = count_fatal_error + 1
883 !-----------------------------------------------------------------------
884 ! Check that all values of bl_pbl_physics are the same for all domains
885 !-----------------------------------------------------------------------
887 DO i = 2, model_config_rec % max_dom
888 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
889 IF ( ( model_config_rec % bl_pbl_physics(i) .NE. model_config_rec % bl_pbl_physics(1) ) .AND. &
890 ( model_config_rec % bl_pbl_physics(i) .NE. 0 ) ) THEN
891 wrf_err_message = '--- ERROR: bl_pbl_physics must be equal for all domains (or = zero)'
892 CALL wrf_message ( wrf_err_message )
893 wrf_err_message = '--- Fix bl_pbl_physics in namelist.input '
894 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
895 count_fatal_error = count_fatal_error + 1
899 !-----------------------------------------------------------------------
900 ! Check that all values of gwd_opt are the same for all domains
901 !-----------------------------------------------------------------------
903 DO i = 2, model_config_rec % max_dom
904 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
905 IF ( ( model_config_rec % gwd_opt(i) .NE. model_config_rec % gwd_opt(1) ) .AND. &
906 ( model_config_rec % gwd_opt(i) .NE. 0 ) ) THEN
907 wrf_err_message = '--- ERROR: gwd_opt must be equal for all domains (or = zero)'
908 CALL wrf_message ( wrf_err_message )
909 wrf_err_message = '--- Fix gwd_opt in namelist.input '
910 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
911 count_fatal_error = count_fatal_error + 1
915 !-----------------------------------------------------------------------
916 ! Check that all values of cu_physics are the same for all domains
917 ! Note that a zero option is OK.
918 !-----------------------------------------------------------------------
920 DO i = 2, model_config_rec % max_dom
921 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
922 IF ( ( model_config_rec % cu_physics(i) .NE. model_config_rec % cu_physics(1) ) .AND. &
923 ( model_config_rec % cu_physics(i) .NE. 0 ) ) THEN
924 wrf_err_message = '--- ERROR: cu_physics must be equal for all domains (or = zero)'
925 CALL wrf_message ( wrf_err_message )
926 wrf_err_message = '--- Fix cu_physics in namelist.input '
927 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
928 count_fatal_error = count_fatal_error + 1
933 #if ( defined NO_GAMMA_SUPPORT )
934 !-----------------------------------------------------------------------
935 ! GF CU scheme requires an intrinsic gamma function. This is a 2008
936 ! feature that not all compilers yet support.
937 !-----------------------------------------------------------------------
939 GF_test : DO i = 1, model_config_rec % max_dom
940 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
941 IF ( model_config_rec % cu_physics(i) .EQ. GFSCHEME ) THEN
942 wrf_err_message = '--- ERROR: cu_physics GF uses an intrinsic gamma function that is not available with this compiler'
943 CALL wrf_message ( TRIM( wrf_err_message ) )
944 wrf_err_message = '--- Change compilers, or change cu_physics option in the namelist.input file.'
945 CALL wrf_message ( TRIM( wrf_err_message ) )
946 count_fatal_error = count_fatal_error + 1
952 !-----------------------------------------------------------------------
953 ! Climate GHG from an input file requires coordinated pairing of
954 ! LW and SW schemes, and restricts which schemes are eligible.
955 ! Only radiation schemes CAM, RRTM, RRTMG, RRTMG_fast may be used.
956 ! CAM LW and CAM SW must be used together.
957 ! RRTM, RRTMG, RRTMG_fast LW and SW may be wildly mixed and matched
959 !-----------------------------------------------------------------------
961 IF ( model_config_rec % ghg_input .EQ. 1 ) THEN
963 DO i = 1, model_config_rec % max_dom
964 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
965 IF ( ( ( model_config_rec % ra_lw_physics(i) .EQ. CAMLWSCHEME ) .AND. &
966 ( model_config_rec % ra_sw_physics(i) .EQ. CAMSWSCHEME ) ) .OR. &
967 ( ( ( model_config_rec % ra_lw_physics(i) .EQ. RRTMSCHEME ) .OR. &
968 ( model_config_rec % ra_lw_physics(i) .EQ. RRTMG_LWSCHEME ) .OR. &
969 ( model_config_rec % ra_lw_physics(i) .EQ. RRTMG_LWSCHEME_FAST ) ) .AND. &
970 ( ( model_config_rec % ra_sw_physics(i) .EQ. SWRADSCHEME ) .OR. &
971 ( model_config_rec % ra_sw_physics(i) .EQ. RRTMG_SWSCHEME ) .OR. &
972 ( model_config_rec % ra_sw_physics(i) .EQ. RRTMG_SWSCHEME_FAST ) ) ) ) THEN
973 ! This is OK, no way would a negation have been understandable!
979 IF ( oops .GT. 0 ) THEN
980 wrf_err_message = '--- ERROR: ghg_input available only for these radiation schemes: CAM, RRTM, RRTMG, RRTMG_fast'
981 CALL wrf_message ( TRIM( wrf_err_message ) )
982 wrf_err_message = ' And the LW and SW schemes must be reasonably paired together:'
983 CALL wrf_message ( TRIM( wrf_err_message ) )
984 wrf_err_message = ' OK = CAM LW with CAM SW'
985 CALL wrf_message ( TRIM( wrf_err_message ) )
986 wrf_err_message = ' OK = RRTM, RRTMG LW or SW, RRTMG_fast LW or SW may be mixed'
987 CALL wrf_message ( TRIM( wrf_err_message ) )
991 !-----------------------------------------------------------------------
992 ! If fractional_seaice = 0, and tice2tsk_if2cold = .true, nothing will happen
993 !-----------------------------------------------------------------------
995 IF ( ( model_config_rec%fractional_seaice .EQ. 0 ).AND. &
996 ( model_config_rec%tice2tsk_if2cold ) ) THEN
997 wrf_err_message = '--- WARNING: You set tice2tsk_if2cold = .true., but fractional_seaice = 0'
998 CALL wrf_debug ( 1, wrf_err_message )
999 wrf_err_message = '--- WARNING: tice2tsk_if2cold will have no effect on results.'
1000 CALL wrf_debug ( 1, wrf_err_message )
1003 !-----------------------------------------------------------------------
1004 ! If fractional_seaice == 1, cannot have the simple land model slab
1006 !-----------------------------------------------------------------------
1008 IF ( ( model_config_rec%fractional_seaice .EQ. 1 ) .AND. &
1009 ( model_config_rec%sf_surface_physics(1) .EQ. SLABSCHEME ) ) THEN
1010 wrf_err_message = '--- ERROR: fractional seaice does not work with simple slab thermal diffusion land model'
1011 CALL wrf_message ( TRIM( wrf_err_message ) )
1012 wrf_err_message = '--- ERROR: Change either fractional_seaice=1 OR sf_surface_physics=1'
1013 CALL wrf_message ( TRIM( wrf_err_message ) )
1014 count_fatal_error = count_fatal_error + 1
1017 !-----------------------------------------------------------------------
1018 ! Check that if fine_input_stream /= 0, io_form_auxinput2 must also be in use
1019 !-----------------------------------------------------------------------
1021 DO i = 1, model_config_rec % max_dom
1022 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1023 IF ( ( model_config_rec%fine_input_stream(i) .NE. 0 ).AND. &
1024 ( model_config_rec%io_form_auxinput2 .EQ. 0 ) ) THEN
1025 wrf_err_message = '--- ERROR: If fine_input_stream /= 0, io_form_auxinput2 must be /= 0'
1026 CALL wrf_message ( wrf_err_message )
1027 wrf_err_message = '--- Set io_form_auxinput2 in the time_control namelist (probably to 2).'
1028 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1029 count_fatal_error = count_fatal_error + 1
1035 !-----------------------------------------------------------------------
1036 ! Check that if num_metgrid_levels < 20, lagrange_order should be 1
1037 !-----------------------------------------------------------------------
1038 IF ( model_config_rec%num_metgrid_levels .LE. 20 ) THEN
1039 wrf_err_message = 'Linear vertical interpolation is recommended with input vertical resolution this coarse, changing lagrange_order to 1'
1040 CALL wrf_debug ( 1, wrf_err_message )
1041 model_config_rec%lagrange_order = 1
1044 !-----------------------------------------------------------------------
1045 ! Check for domain consistency for urban options.
1046 !-----------------------------------------------------------------------
1048 d1_value = model_config_rec%sf_urban_physics(1)
1049 DO i = 2, model_config_rec % max_dom
1050 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1051 IF ( model_config_rec%sf_urban_physics(i) /= d1_value ) THEN
1052 wrf_err_message = '--- NOTE: sf_urban_physics option must be identical in each domain'
1053 CALL wrf_debug ( 1, wrf_err_message )
1054 wrf_err_message = '--- NOTE: ----> Resetting namelist values to that defined on the inner most domain'
1055 CALL wrf_debug ( 1, wrf_err_message )
1058 d1_value = model_config_rec%sf_urban_physics(model_config_rec % max_dom)
1059 DO i = 1, model_config_rec % max_dom-1
1060 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1061 model_config_rec%sf_urban_physics(i) = d1_value
1064 !------------------------------------------------------------------------
1065 ! Mills (2011) sea-ice albedo treatment only for Noah LSM and Noah-MP LSM
1066 !------------------------------------------------------------------------
1067 IF ( model_config_rec%seaice_albedo_opt == 1 ) THEN
1068 DO i = 1, model_config_rec % max_dom
1069 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1070 IF ( ( model_config_rec%sf_surface_physics(i) /= LSMSCHEME ) .AND. &
1071 ( model_config_rec%sf_surface_physics(i) /= NOAHMPSCHEME ) ) THEN
1073 write (wrf_err_message, '(" --- ERROR: seaice_albedo_opt == 1 works only with ")')
1074 CALL wrf_message ( TRIM ( wrf_err_message ) )
1075 write (wrf_err_message, '(" sf_surface_physics == ", I2, " (Noah) or ", I2, " (Noah-MP).")') &
1076 LSMSCHEME, NOAHMPSCHEME
1077 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1078 count_fatal_error = count_fatal_error + 1
1089 !-----------------------------------------------------------------------
1090 ! Check that NSAS shallow convection is not allowed to turn on simultaneously with NSAS
1091 !-----------------------------------------------------------------------
1092 DO i = 1, model_config_rec % max_dom
1093 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1094 IF ( model_config_rec%shcu_physics(i) == nscvshcuscheme .AND. model_config_rec%cu_physics(i) == nsasscheme) THEN
1095 WRITE(wrf_err_message, '(" --- ERROR: NSCV shallow convection scheme is already included in NSAS ")')
1096 CALL wrf_message ( TRIM ( wrf_err_message ) )
1097 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1098 count_fatal_error = count_fatal_error + 1
1104 !-----------------------------------------------------------------------
1105 ! Check if the bucket size for rain is > 0. If so, then we need to activate
1106 ! a derived namelist variable: bucketr_opt.
1107 !-----------------------------------------------------------------------
1109 IF ( model_config_rec%bucket_mm .GT. 0. ) THEN
1110 model_config_rec%bucketr_opt = 1
1113 !-----------------------------------------------------------------------
1114 ! Check if the bucket size for radiation is > 0. If so, then we need to activate
1115 ! a derived namelist variable: bucketf_opt.
1116 !-----------------------------------------------------------------------
1118 IF ( model_config_rec%bucket_J .GT. 0. ) THEN
1119 model_config_rec%bucketf_opt = 1
1122 !-----------------------------------------------------------------------
1123 ! Check if the precip bucket reset time interval > 0. If so, then we need to
1124 ! activate a derived namelist variable: prec_acc_opt
1125 !-----------------------------------------------------------------------
1127 DO i = 1, model_config_rec % max_dom
1128 IF ( model_config_rec%prec_acc_dt(i) .GT. 0. ) THEN
1129 model_config_rec%prec_acc_opt = 1
1133 !-----------------------------------------------------------------------
1134 ! Check if any stochastic perturbation scheme is turned on in any domain,
1135 ! if so, set derived variable sppt_on=1 and/or rand_perturb_on and/or skebs_on=1
1136 !-----------------------------------------------------------------------
1138 DO i = 1, model_config_rec % max_dom
1139 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1140 IF ( model_config_rec % sppt(i) .ne. 0) then
1141 model_config_rec % sppt_on=1
1142 IF (( model_config_rec%KMINFORCT .ne. 1) .or. (model_config_rec%KMAXFORCT .ne. 1000000) .or. &
1143 ( model_config_rec%LMINFORCT .ne. 1) .or. (model_config_rec%LMAXFORCT .ne. 1000000)) then
1144 wrf_err_message = '--- Warning: the namelist parameter "kminforct" etc. are for SKEBS only'
1145 CALL wrf_message ( wrf_err_message )
1146 wrf_err_message = ' and should not be changed from their default value for SPPT'
1147 CALL wrf_message ( wrf_err_message )
1148 wrf_err_message = '--- ERROR: If you really want to modify "kminforct" etc., edit module_check a_mundo.'
1149 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1150 count_fatal_error = count_fatal_error + 1
1154 DO i = 1, model_config_rec % max_dom
1155 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1156 IF ( model_config_rec % rand_perturb(i) .ne. 0) then
1157 model_config_rec % rand_perturb_on=1
1158 IF (( model_config_rec%KMINFORCT .ne. 1) .or. (model_config_rec%KMAXFORCT .ne. 1000000) .or. &
1159 ( model_config_rec%LMINFORCT .ne. 1) .or. (model_config_rec%LMAXFORCT .ne. 1000000)) then
1160 wrf_err_message = '--- Warning: the namelist parameter "kminforct" etc are for SKEBS only'
1161 CALL wrf_message ( wrf_err_message )
1162 wrf_err_message = ' and should not be changed from their default value for RAND_PERTURB'
1163 CALL wrf_message ( wrf_err_message )
1164 wrf_err_message = '--- ERROR: If you really want to modify "kminforct" etc., edit module_check a_mundo.'
1165 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1166 count_fatal_error = count_fatal_error + 1
1170 DO i = 1, model_config_rec % max_dom
1171 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1172 IF (( model_config_rec % spp_conv(i) .ne. 0).or.( model_config_rec % spp_pbl(i) .ne. 0).or. (model_config_rec % spp_lsm(i) .ne. 0) &
1173 .or. ( model_config_rec % spp(i) .ne. 0)) then
1174 model_config_rec % spp_on=1
1175 IF (( model_config_rec%KMINFORCT .ne. 1) .or. (model_config_rec%KMAXFORCT .ne. 1000000) .or. &
1176 ( model_config_rec%LMINFORCT .ne. 1) .or. (model_config_rec%LMAXFORCT .ne. 1000000)) then
1177 wrf_err_message = '--- Warning: the namelist parameter "kminforct" etc are for SKEBS only'
1178 CALL wrf_message ( wrf_err_message )
1179 wrf_err_message = ' and should not be changed from their default value for RAND_PERTURB'
1180 CALL wrf_message ( wrf_err_message )
1181 wrf_err_message = '--- ERROR: If you really want to modify "kminforct" etc., edit module_check a_mundo.'
1182 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1183 count_fatal_error = count_fatal_error + 1
1186 IF ( model_config_rec % spp(i) .ne. 0) then
1187 model_config_rec % spp_conv=1
1188 model_config_rec % spp_pbl=1
1189 model_config_rec % spp_lsm=1
1192 DO i = 1, model_config_rec % max_dom
1193 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1194 IF ( model_config_rec % stoch_vertstruc_opt(i) ==1 ) then
1195 model_config_rec % skebs_vertstruc=1 ! parameter stoch_vertstruc_opt is being replaced with skebs_vertstruc
1196 ! stoch_vertstruc_opt is obsolete starting with V3.7
1197 wrf_err_message = '--- WARNING: the namelist parameter "stoch_vertstruc_opt" is obsolete.'
1198 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1199 wrf_err_message = ' Please replace with namelist parameter "skebs_vertstruc" in V3.7 and later versions.'
1200 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1204 DO i = 1, model_config_rec % max_dom
1205 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1206 IF ( model_config_rec % stoch_force_opt(i) ==1 ) THEN
1207 model_config_rec % skebs(i)=1 ! parameter stoch_forc_opt is being replaced with skebs;
1208 ! stoch_vertstruc_opt is obsolete starting with V3.7
1209 wrf_err_message = '--- WARNING: the namelist parameter "stoch_force_opt" is obsolete.'
1210 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1211 wrf_err_message = ' Please replace with namelist parameter "skebs" in V3.7 and later versions.'
1212 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1215 DO i = 1, model_config_rec % max_dom
1216 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1217 IF ( model_config_rec % skebs(i) .ne. 0) then
1218 model_config_rec % skebs_on=1
1222 !-----------------------------------------------------------------------
1223 ! Random fields are by default thin 3D arrays (:,1,:).
1224 ! If random fields have vertical structures (stoch_vertstruc_opt .ne. 0)
1225 ! make them full 3D array arrays
1226 !-----------------------------------------------------------------------
1227 IF ( model_config_rec % skebs_vertstruc .ne. 99 ) then
1228 model_config_rec % num_stoch_levels = model_config_rec %e_vert(1)
1230 IF ( model_config_rec % sppt_vertstruc .ne. 99 ) then
1231 model_config_rec % num_stoch_levels = model_config_rec %e_vert(1)
1233 IF ( model_config_rec % rand_pert_vertstruc .ne. 99 ) then
1234 model_config_rec % num_stoch_levels = model_config_rec %e_vert(1)
1237 !--------------------------------------------------------------------------------
1238 ! Check if boundary perturbations is turned on and set to '1' (perturb_bdy=1).
1239 ! If so, make sure skebs_on is also turned on.
1240 !--------------------------------------------------------------------------------
1241 IF ( model_config_rec % perturb_bdy .EQ. 1 ) then
1242 model_config_rec % skebs_on=1
1243 wrf_err_message = '--- WARNING: perturb_bdy=1 option uses SKEBS pattern and may'
1244 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1245 wrf_err_message = ' increase computation time.'
1246 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1249 !--------------------------------------------------------------------------------
1250 ! Check if chemistry boundary perturbations is turned on and set to '1' (perturb_chem_bdy=1).
1251 ! If so, make sure rand_perturb_on is also turned on.
1252 ! perturb_chem_bdy can be turned on only if WRF_CHEM is also compiled.
1253 ! If perturb_chem_bdy=1, then have_bcs_chem should be turned on as well.
1254 !--------------------------------------------------------------------------------
1256 IF ( model_config_rec % perturb_chem_bdy .EQ. 1 ) then
1259 wrf_err_message = '--- ERROR: This option is only for WRF_CHEM.'
1260 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1261 count_fatal_error = count_fatal_error + 1
1264 !NOTE model_config_rec % rand_perturb_on=1
1265 wrf_err_message = '--- WARNING: perturb_chem_bdy=1 option uses RAND pattern and may'
1266 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1267 wrf_err_message = ' increase computation time.'
1268 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1271 IF ( .NOT. model_config_rec % have_bcs_chem(1) ) THEN
1272 wrf_err_message = '--- ERROR: This perturb_chem_bdy option needs '// &
1273 'have_bcs_chem = .true. in chem.'
1274 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1275 count_fatal_error = count_fatal_error + 1
1281 !----------------------------------------------------------------------------
1282 ! If trajectory option is turned off, make sure the number of trajectories is
1284 !----------------------------------------------------------------------------
1285 IF ( ( model_config_rec%traj_opt .EQ. 0 ) .AND. &
1286 ( model_config_rec%num_traj .NE. 0 ) ) THEN
1287 wrf_err_message = '--- WARNING: traj_opt is zero, but num_traj is not zero; setting num_traj to zero.'
1288 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1289 model_config_rec%num_traj = 0
1292 !-----------------------------------------------------------------------
1293 ! Catch old method for using multi-file LBCs. Let folks know the
1294 ! new way to get the same functionality with run-time options.
1295 !-----------------------------------------------------------------------
1296 #if _MULTI_BDY_FILES_
1297 wrf_err_message = '--- ERROR: Do not use the compile-time -D_MULTI_BDY_FILES_ option for multi-file LBCs.'
1298 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1299 wrf_err_message = '--- ERROR: Use the run-time namelist option multi_bdy_files in nml record bdy_control.'
1300 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1301 count_fatal_error = count_fatal_error + 1
1304 !----------------------------------------------------------------------------
1305 ! If using multi_bdy_files option or not, make the lateral bdy file root name
1306 ! correct. For example, we want "wrfbdy_d01" for NON multi_bdy_files and we
1307 ! want "wrfbdy_d01_SOME_DATE" when using the multi_bdy_files option.
1308 !----------------------------------------------------------------------------
1309 IF ( model_config_rec%multi_bdy_files ) THEN
1310 IF ( INDEX ( TRIM(model_config_rec%bdy_inname) , "_<date>" ) .GT. 0 ) THEN
1313 wrf_err_message = '--- ERROR: Need bdy_inname = "wrfbdy_d<domain>_<date>"'
1314 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1315 count_fatal_error = count_fatal_error + 1
1316 ! len1 = LEN_TRIM(model_config_rec%bdy_inname)
1318 ! model_config_rec%bdy_inname(1:len1+len2) = TRIM(model_config_rec%bdy_inname) // "_<date>"
1320 ELSE IF ( .NOT. model_config_rec%multi_bdy_files ) THEN
1321 IF ( INDEX ( TRIM(model_config_rec%bdy_inname) , "_<date>" ) .EQ. 0 ) THEN
1324 wrf_err_message = '--- ERROR: Remove bdy_inname = "wrfbdy_d<domain>_<date>"'
1325 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1326 count_fatal_error = count_fatal_error + 1
1327 ! len1 = LEN_TRIM(model_config_rec%bdy_inname)
1329 ! DO len_loop len1-len2+1 , len1
1330 ! model_config_rec%bdy_inname(len_loop:len_loop) = " "
1338 !-----------------------------------------------------------------------
1339 ! In program real, if hypsometric_opt = 2, adjust_heights cannot be set to .true.
1340 !-----------------------------------------------------------------------
1341 IF ( model_config_rec%hypsometric_opt .EQ. 2 &
1342 .AND. model_config_rec%adjust_heights ) THEN
1343 wrf_err_message = '--- NOTE: hypsometric_opt is 2, setting adjust_heights = F'
1344 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1345 model_config_rec%adjust_heights = .false.
1350 !-----------------------------------------------------------------------
1351 ! scale-aware KF cannot work with 3DTKE (km_opt=5)
1352 !-----------------------------------------------------------------------
1355 DO i = 1, model_config_rec % max_dom
1356 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1357 IF ( ( model_config_rec%km_opt(i) .EQ. SMS_3DTKE ) .AND. &
1358 ( model_config_rec%cu_physics(i) .EQ. MSKFSCHEME ) ) THEN
1361 ENDDO ! Loop over domains
1362 IF ( oops .GT. 0 ) THEN
1363 wrf_err_message = '--- ERROR: cu_physics = 11 cannot work with 3DTKE scheme '
1364 CALL wrf_message ( wrf_err_message )
1365 wrf_err_message = '--- Choose another bl_pbl_physics OR use another cu_physics option '
1366 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1367 count_fatal_error = count_fatal_error + 1
1370 !-----------------------------------------------------------------------
1371 ! IF cu_physics = 11 (scale-aware KF), THEN set other required flags. This
1372 ! is not an error, just a convenience for the user.
1373 !-----------------------------------------------------------------------
1375 DO i = 1, model_config_rec % max_dom
1376 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1377 IF ( model_config_rec%cu_physics(i) .EQ. MSKFSCHEME ) THEN
1378 wrf_err_message = '--- NOTE: cu_physics is 11, setting icloud = 1 and cu_rad_feedback = T'
1379 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1380 model_config_rec%cu_rad_feedback(i) = .true.
1381 model_config_rec%icloud = 1
1385 !-----------------------------------------------------------------------
1386 ! aercu_opt = 1 (CESM-aerosal) only works with MSKF, special Morrison
1387 !-----------------------------------------------------------------------
1390 DO i = 1, model_config_rec % max_dom
1391 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1392 IF ( model_config_rec%aercu_opt .GT. 0 .AND. &
1393 ( model_config_rec%cu_physics(i) .NE. MSKFSCHEME .OR. &
1394 model_config_rec%mp_physics(i) .NE. MORR_TM_AERO ) ) THEN
1399 IF ( oops .GT. 0 ) THEN
1400 wrf_err_message = '--- ERROR: aercu_opt requires cu_physics = 11, and mp_physics = 40 '
1401 CALL wrf_message ( wrf_err_message )
1402 wrf_err_message = '--- Fix these options in namelist.input if you would like to use aercu_opt'
1403 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1404 count_fatal_error = count_fatal_error + 1
1407 !-----------------------------------------------------------------------
1408 ! Set the namelist parameters for the aercu_opt > 0
1409 !-----------------------------------------------------------------------
1411 IF ( model_config_rec % aercu_opt .GT. 0 ) THEN
1412 model_config_rec % alevsiz_cu = 30
1413 model_config_rec % no_src_types_cu = 10
1414 DO i = 1, model_config_rec % max_dom
1415 model_config_rec % scalar_pblmix(i) = 1
1418 wrf_err_message = '--- NOTE: aercu_opt is in use, setting: ' // &
1419 'alevsiz_cu=30, no_src_types_cu=10, scalar_pblmix = 1'
1420 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1426 !-----------------------------------------------------------------------
1427 ! If sst_update = 0, set io_form_auxinput4 to 0 so WRF will not try to
1428 ! input the data; auxinput_interval must also be 0
1429 !-----------------------------------------------------------------------
1431 IF ( model_config_rec%sst_update .EQ. 0 ) THEN
1432 model_config_rec%io_form_auxinput4 = 0
1433 DO i = 1, model_config_rec % max_dom
1434 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1435 wrf_err_message = '--- NOTE: sst_update is 0, ' // &
1436 'setting io_form_auxinput4 = 0 and auxinput4_interval = 0 for all domains'
1437 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1438 model_config_rec%auxinput4_interval(i) = 0
1439 model_config_rec%auxinput4_interval_y(i) = 0
1440 model_config_rec%auxinput4_interval_d(i) = 0
1441 model_config_rec%auxinput4_interval_h(i) = 0
1442 model_config_rec%auxinput4_interval_m(i) = 0
1443 model_config_rec%auxinput4_interval_s(i) = 0
1446 IF ( model_config_rec%io_form_auxinput4 .EQ. 0 ) THEN
1447 wrf_err_message = '--- ERROR: If sst_update /= 0, io_form_auxinput4 must be /= 0'
1448 CALL wrf_message ( wrf_err_message )
1449 wrf_err_message = '--- Set io_form_auxinput4 in the time_control namelist (probably to 2).'
1450 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1451 count_fatal_error = count_fatal_error + 1
1455 !-----------------------------------------------------------------------
1456 ! If sst_update = 1, we need to make sure that two nml items are set:
1457 ! 1. io_form_auxinput4 = 2 (only for one domain)
1458 ! 2. auxinput4_interval = NON-ZERO (just check most coarse domain)
1459 !-----------------------------------------------------------------------
1461 IF ( model_config_rec%sst_update .EQ. 1 ) THEN
1462 IF ( model_config_rec%io_form_auxinput4 .EQ. 0 ) THEN
1463 wrf_err_message = '--- ERROR: If sst_update /= 0, io_form_auxinput4 must be /= 0'
1464 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1465 wrf_err_message = '--- Set io_form_auxinput4 in the time_control namelist (probably to 2).'
1466 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1467 count_fatal_error = count_fatal_error + 1
1470 IF ( ( model_config_rec%auxinput4_interval(1) .EQ. 0 ) .AND. &
1471 ( model_config_rec%auxinput4_interval_y(1) .EQ. 0 ) .AND. &
1472 ( model_config_rec%auxinput4_interval_d(1) .EQ. 0 ) .AND. &
1473 ( model_config_rec%auxinput4_interval_h(1) .EQ. 0 ) .AND. &
1474 ( model_config_rec%auxinput4_interval_m(1) .EQ. 0 ) .AND. &
1475 ( model_config_rec%auxinput4_interval_s(1) .EQ. 0 ) ) THEN
1476 wrf_err_message = '--- ERROR: If sst_update /= 0, one of the auxinput4_interval settings must be /= 0'
1477 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1478 wrf_err_message = '--- Set auxinput4_interval_s to the same value as interval_seconds (usually a pretty good guess).'
1479 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1480 count_fatal_error = count_fatal_error + 1
1484 !-----------------------------------------------------------------------
1485 ! If qna_update = 0, set io_form_auxinput17 to 0 so WRF will not try to
1486 ! input the data; auxinput_interval must also be 0
1487 !-----------------------------------------------------------------------
1489 IF ( model_config_rec%qna_update .EQ. 0 ) THEN
1490 model_config_rec%io_form_auxinput17 = 0
1491 DO i = 1, model_config_rec % max_dom
1492 wrf_err_message = '--- NOTE: qna_update is 0, ' // &
1493 'setting io_form_auxinput17 = 0 and auxinput17_interval = 0 for all domains'
1494 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1495 model_config_rec%auxinput17_interval(i) = 0
1496 model_config_rec%auxinput17_interval_y(i) = 0
1497 model_config_rec%auxinput17_interval_d(i) = 0
1498 model_config_rec%auxinput17_interval_h(i) = 0
1499 model_config_rec%auxinput17_interval_m(i) = 0
1500 model_config_rec%auxinput17_interval_s(i) = 0
1503 IF ( model_config_rec%io_form_auxinput17 .EQ. 0 ) THEN
1504 wrf_err_message = '--- ERROR: If qna_update /= 0, io_form_auxinput17 must be /= 0'
1505 CALL wrf_message ( wrf_err_message )
1506 wrf_err_message = '--- Set io_form_auxinput17 in the time_control namelist (probably to 2).'
1507 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1508 count_fatal_error = count_fatal_error + 1
1512 !-----------------------------------------------------------------------
1513 ! If qna_update = 1, we need to make sure that two nml items are set:
1514 ! 1. io_form_auxinput17 = 2 (only for one domain)
1515 ! 2. auxinput17_interval = NON-ZERO (just check most coarse domain)
1516 !-----------------------------------------------------------------------
1518 IF ( model_config_rec%qna_update .EQ. 1 ) THEN
1519 IF ( model_config_rec%io_form_auxinput17 .EQ. 0 ) THEN
1520 wrf_err_message = '--- ERROR: If qna_update /= 0, io_form_auxinput17 must be /= 0'
1521 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1522 wrf_err_message = '--- Set io_form_auxinput17 in the time_control namelist (probably to 2).'
1523 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1524 count_fatal_error = count_fatal_error + 1
1527 IF ( ( model_config_rec%auxinput17_interval(1) .EQ. 0 ) .AND. &
1528 ( model_config_rec%auxinput17_interval_y(1) .EQ. 0 ) .AND. &
1529 ( model_config_rec%auxinput17_interval_d(1) .EQ. 0 ) .AND. &
1530 ( model_config_rec%auxinput17_interval_h(1) .EQ. 0 ) .AND. &
1531 ( model_config_rec%auxinput17_interval_m(1) .EQ. 0 ) .AND. &
1532 ( model_config_rec%auxinput17_interval_s(1) .EQ. 0 ) ) THEN
1533 wrf_err_message = '--- ERROR: If qna_update /= 0, one of the auxinput17_interval settings must be /= 0'
1534 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1535 wrf_err_message = '--- Set auxinput17_interval_s to the same value as interval_seconds (usually a pretty good guess).'
1536 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1537 count_fatal_error = count_fatal_error + 1
1541 !-----------------------------------------------------------------------
1542 ! The qndropsource relies on the flag PROGN (when not running chemistry)
1543 ! and is always allocated when running WRF Chem.
1544 !-----------------------------------------------------------------------
1546 #if ( (EM_CORE == 1) && (WRF_CHEM != 1) )
1547 model_config_rec%alloc_qndropsource = 0
1548 DO i = 1, model_config_rec % max_dom
1549 IF ( model_config_rec%progn(i) .EQ. 1 ) THEN
1550 model_config_rec%alloc_qndropsource = 1
1554 #elif (WRF_CHEM == 1)
1555 model_config_rec%alloc_qndropsource = 1
1558 #if ((EM_CORE == 1) && (DA_CORE != 1))
1559 !-----------------------------------------------------------------------
1560 ! Check that if grid_sfdda is one, grid_fdda is also 1
1561 !-----------------------------------------------------------------------
1563 DO i = 1, model_config_rec % max_dom
1564 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1565 IF ( ( model_config_rec%grid_sfdda(i) .GT. 0 ).AND. &
1566 ( model_config_rec%grid_fdda (i) .NE. 1 ) ) THEN
1567 wrf_err_message = '--- ERROR: If grid_sfdda >= 1, then grid_fdda must also = 1 for that domain '
1568 CALL wrf_message ( wrf_err_message )
1569 wrf_err_message = '--- Change grid_fdda or grid_sfdda in namelist.input '
1570 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1571 count_fatal_error = count_fatal_error + 1
1575 !-----------------------------------------------------------------------
1576 ! If grid_fdda or grid_sfdda is 0 for any domain, all interval and
1577 ! ending time information that domain must be set to zero. For
1578 ! surface fdda, we also need to make sure that the PXLSM soil nudging
1579 ! switch is also zero. Either surface fdda or soil nudging with the
1580 ! PX scheme are enough to allow the surface fdda file to be read.
1581 !-----------------------------------------------------------------------
1583 DO i = 1, model_config_rec % max_dom
1584 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1586 IF ( model_config_rec%grid_fdda(i) .EQ. 0 ) THEN
1587 WRITE (wrf_err_message, FMT='(A,I6,A)') '--- NOTE: grid_fdda is 0 for domain ', &
1588 i, ', setting gfdda interval and ending time to 0 for that domain.'
1589 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1591 model_config_rec%gfdda_end_y(i) = 0
1592 model_config_rec%gfdda_end_d(i) = 0
1593 model_config_rec%gfdda_end_h(i) = 0
1594 model_config_rec%gfdda_end_m(i) = 0
1595 model_config_rec%gfdda_end_s(i) = 0
1596 model_config_rec%gfdda_interval(i) = 0
1597 model_config_rec%gfdda_interval_y(i) = 0
1598 model_config_rec%gfdda_interval_d(i) = 0
1599 model_config_rec%gfdda_interval_h(i) = 0
1600 model_config_rec%gfdda_interval_m(i) = 0
1601 model_config_rec%gfdda_interval_s(i) = 0
1604 IF ( ( model_config_rec%grid_sfdda(i) .EQ. 0 ) .AND. &
1605 ( model_config_rec%pxlsm_soil_nudge(i) .EQ. 0 ) ) THEN
1606 WRITE (wrf_err_message, FMT='(A,I6,A)') &
1607 '--- NOTE: both grid_sfdda and pxlsm_soil_nudge are 0 for domain ', &
1608 i, ', setting sgfdda interval and ending time to 0 for that domain.'
1609 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1611 model_config_rec%sgfdda_end_y(i) = 0
1612 model_config_rec%sgfdda_end_d(i) = 0
1613 model_config_rec%sgfdda_end_h(i) = 0
1614 model_config_rec%sgfdda_end_m(i) = 0
1615 model_config_rec%sgfdda_end_s(i) = 0
1616 model_config_rec%sgfdda_interval(i) = 0
1617 model_config_rec%sgfdda_interval_y(i) = 0
1618 model_config_rec%sgfdda_interval_d(i) = 0
1619 model_config_rec%sgfdda_interval_h(i) = 0
1620 model_config_rec%sgfdda_interval_m(i) = 0
1621 model_config_rec%sgfdda_interval_s(i) = 0
1624 IF ( model_config_rec%obs_nudge_opt(i) .EQ. 0 ) THEN
1625 WRITE (wrf_err_message, FMT='(A,I6,A)') '--- NOTE: obs_nudge_opt is 0 for domain ', &
1626 i, ', setting obs nudging interval and ending time to 0 for that domain.'
1627 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1629 model_config_rec%fdda_end(i) = 0
1630 model_config_rec%auxinput11_interval(i) = 0
1631 model_config_rec%auxinput11_interval_y(i) = 0
1632 model_config_rec%auxinput11_interval_d(i) = 0
1633 model_config_rec%auxinput11_interval_h(i) = 0
1634 model_config_rec%auxinput11_interval_m(i) = 0
1635 model_config_rec%auxinput11_interval_s(i) = 0
1636 model_config_rec%auxinput11_end(i) = 0
1637 model_config_rec%auxinput11_end_y(i) = 0
1638 model_config_rec%auxinput11_end_d(i) = 0
1639 model_config_rec%auxinput11_end_h(i) = 0
1640 model_config_rec%auxinput11_end_m(i) = 0
1641 model_config_rec%auxinput11_end_s(i) = 0
1644 ENDDO ! Loop over domains
1646 !-----------------------------------------------------------------------
1647 ! If grid_sfdda = 2, we turn it into derived namelist fasdas
1648 !-----------------------------------------------------------------------
1650 DO i = 1, model_config_rec % max_dom
1651 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1652 model_config_rec%fasdas(i) = 0
1653 IF ( model_config_rec%grid_sfdda(i) .EQ. 2 ) THEN
1654 model_config_rec%fasdas(i) = 1
1658 !-----------------------------------------------------------------------
1659 ! FASDAS: Check that rinblw is set for max_domains in the namelist if sffdda is active
1660 !-----------------------------------------------------------------------
1661 rinblw_already_done = .FALSE.
1662 DO j = 1, model_config_rec%max_dom
1663 IF ( .NOT. model_config_rec % grid_allowed(j) ) CYCLE
1664 IF (model_config_rec%grid_sfdda(j) .EQ. 1 ) THEN
1665 DO i = 2, model_config_rec%max_dom
1666 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1667 IF ( model_config_rec%rinblw(i) .EQ. -1 ) THEN
1668 model_config_rec%rinblw(i) = model_config_rec % rinblw(1)
1669 IF ( .NOT. rinblw_already_done ) THEN
1670 wrf_err_message = 'Setting blank rinblw entries to domain #1 values.'
1671 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1672 wrf_err_message = ' --> The rinblw entry in the namelist.input is now max_domains.'
1673 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1675 rinblw_already_done = .TRUE.
1679 !------------------------------------------------------------------------
1680 ! Check that rinblw is not -1 if sfdda is active
1681 !------------------------------------------------------------------------
1682 IF ( model_config_rec%rinblw(1) .EQ. -1 ) THEN
1683 wrf_err_message = '--- ERROR: rinblw needs to be set in the namelist.input file.'
1684 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1685 count_fatal_error = count_fatal_error + 1
1690 !------------------------------------------------------------------------
1691 ! Check to see if FASDAS is active
1692 !------------------------------------------------------------------------
1693 DO i = 1, model_config_rec%max_dom
1694 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1695 IF (model_config_rec%fasdas(i) .EQ. 1 ) THEN
1696 wrf_err_message = 'FASDAS is active. Mixed Layer fdda is inactive'
1697 CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1700 !------------------------------------------------------------------------
1701 ! Check to make sure sfdda is active if FASDAS is in namelist
1702 !------------------------------------------------------------------------
1703 ! IF (model_config_rec%fasdas(i) .EQ. 1 ) THEN
1704 ! IF (model_config_rec%grid_sfdda(i) .EQ. 0) THEN
1705 ! wrf_err_message = '--- ERROR: sfdda needs to be set in the namelist.input file to run FASDAS.'
1706 ! CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1707 ! count_fatal_error = count_fatal_error + 1
1714 !-----------------------------------------------------------------------
1715 ! Only implement the mfshconv option if the QNSE PBL is activated.
1716 !-----------------------------------------------------------------------
1719 DO i = 1, model_config_rec % max_dom
1720 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1721 IF ( ( model_config_rec%bl_pbl_physics(i) .NE. QNSEPBLSCHEME ) .AND. &
1722 ( model_config_rec%mfshconv(i) .NE. 0 ) ) THEN
1723 model_config_rec%mfshconv(i) = 0
1726 ENDDO ! Loop over domains
1727 IF ( oops .GT. 0 ) THEN
1728 wrf_err_message = '--- NOTE: bl_pbl_physics /= 4, implies mfshconv must be 0, resetting'
1729 CALL wrf_debug ( 1, wrf_err_message )
1732 !-----------------------------------------------------------------------
1733 ! shcu_physics = 3 (grimsshcuscheme) only works with YSU & MYNN PBL.
1734 !-----------------------------------------------------------------------
1737 DO i = 1, model_config_rec % max_dom
1738 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1739 IF ( model_config_rec%shcu_physics(i) .EQ. GRIMSSHCUSCHEME ) THEN
1740 IF ( (model_config_rec%bl_pbl_physics(i) .EQ. YSUSCHEME) .OR. &
1741 (model_config_rec%bl_pbl_physics(i) .EQ. SHINHONGSCHEME) .OR. &
1742 (model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME ) ) THEN
1745 model_config_rec%shcu_physics(i) = 0
1749 ENDDO ! Loop over domains
1750 IF ( oops .GT. 0 ) THEN
1751 wrf_err_message = '--- NOTE: bl_pbl_physics /= 1,5,6,11 implies shcu_physics cannot be 3, resetting'
1752 CALL wrf_debug ( 1, wrf_err_message )
1755 !-----------------------------------------------------------------------
1756 ! If MYNN PBL is not used, set bl_mynn_edmf = 0 so that shallow convection
1757 ! options can be set and we don't get additional output
1758 !-----------------------------------------------------------------------
1760 DO i = 1, model_config_rec % max_dom
1761 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1762 IF ( ( model_config_rec % bl_pbl_physics(i) .NE. MYNNPBLSCHEME ) ) THEN
1763 model_config_rec % bl_mynn_edmf(i) = 0
1764 model_config_rec % bl_mynn_output(i) = 0
1768 !-----------------------------------------------------------------------
1769 ! bl_mynn_edmf > 0 over-rules both shcu_physics & ishallow
1770 !-----------------------------------------------------------------------
1773 EDMFMAX = MAXVAL(model_config_rec%bl_mynn_edmf(1:model_config_rec%max_dom))
1774 SCHUMAX = MAXVAL(model_config_rec%shcu_physics(1:model_config_rec%max_dom))
1775 IF ( ( ( EDMFMAX .GT. 0 ) .AND. ( SCHUMAX .GT. 0 ) ) .OR. &
1776 ( ( EDMFMAX .GT. 0 ) .AND. ( model_config_rec%ishallow .GT. 0 ) ) ) THEN
1777 wrf_err_message = '--- ERROR: bl_mynn_edmf > 0 requires both shcu_physics=0 & ishallow=0'
1778 CALL wrf_message(wrf_err_message)
1779 wrf_err_message = 'when using MYNN PBL, by default bl_mynn_edmf is turned on'
1780 CALL wrf_message(wrf_err_message)
1781 wrf_err_message = 'Modify namelist.input so that shcu_physics nor ishallow is used when bl_mynn_edmf is turned on'
1782 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1783 count_fatal_error = count_fatal_error + 1
1786 !-----------------------------------------------------------------------
1787 ! Make sure icloud_bl is only used when MYNN is chosen.
1788 !-----------------------------------------------------------------------
1791 DO i = 1, model_config_rec % max_dom
1792 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1793 IF ( model_config_rec%icloud_bl .eq. 1) THEN
1794 IF ( model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME ) THEN
1795 !CORRECTLY CONFIGURED
1797 model_config_rec%icloud_bl = 0
1801 ENDDO ! Loop over domains
1802 IF ( oops .GT. 0 ) THEN
1803 wrf_err_message = 'Need MYNN PBL for icloud_bl = 1, resetting to 0'
1804 CALL wrf_debug ( 1, wrf_err_message )
1808 !-----------------------------------------------------------------------
1809 ! Make sure phot_blcld is only used when icloud_bl==1 and MYNN is chosen.
1810 !-----------------------------------------------------------------------
1813 DO i = 1, model_config_rec % max_dom
1814 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1815 IF ( model_config_rec%phot_blcld(i) ) THEN
1816 IF ( ( model_config_rec%icloud_bl .eq. 1 ) .AND. &
1817 ( ( model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME ) ) ) THEN
1818 !CORRECTLY CONFIGURED
1823 ENDDO ! Loop over domains
1824 IF ( oops .GT. 0 ) THEN
1825 wrf_err_message = '--- ERROR: Need MYNN PBL and icloud_bl = 1 for phot_blcld = .true.'
1826 CALL wrf_message(wrf_err_message)
1827 count_fatal_error = count_fatal_error + 1
1831 !-----------------------------------------------------------------------
1832 ! We need to know if any of the cumulus schemes are active. This
1833 ! allows the model to allocate space.
1834 !-----------------------------------------------------------------------
1836 model_config_rec%cu_used = 0
1837 DO i = 1, model_config_rec % max_dom
1838 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1839 IF ( model_config_rec%cu_physics(i) .NE. NOCUSCHEME ) THEN
1840 model_config_rec%cu_used = 1
1844 !-----------------------------------------------------------------------
1845 ! We need to know if any of the shallow cumulus schemes are active. This
1846 ! allows the model to allocate space.
1847 !-----------------------------------------------------------------------
1849 model_config_rec%shcu_used = 0
1850 DO i = 1, model_config_rec % max_dom
1851 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1852 IF ( model_config_rec%shcu_physics(i) .NE. NOSHCUSCHEME ) THEN
1853 model_config_rec%shcu_used = 1
1857 !-----------------------------------------------------------------------
1858 ! We need to know if the any of the orographic gravity wave drag schemes
1859 ! are active on any domains. This allows the model to allocate space.
1860 !-----------------------------------------------------------------------
1862 model_config_rec%gwd_used = 0
1863 DO i = 1, model_config_rec % max_dom
1864 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1865 IF ( model_config_rec%gwd_opt(i) .EQ. 1 ) THEN
1866 model_config_rec%gwd_used = 1
1869 DO i = 1, model_config_rec % max_dom
1870 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1871 IF ( model_config_rec%gwd_opt(i) .EQ. 3 ) THEN
1872 model_config_rec%gwd_used = 3
1875 ! Check if user is requesting extra gravity-wave-drag diagnostics
1876 ! for a given GWD scheme
1877 ! Only assigned to gwd_opts that have diagnostics available
1878 model_config_rec%gwd_diags_used = 0
1879 IF ( model_config_rec%gwd_used .EQ. 3 .AND. &
1880 model_config_rec%gwd_diags .EQ. 1 ) THEN
1881 model_config_rec%gwd_diags_used = 3
1884 !-----------------------------------------------------------------------
1885 ! Make sure microphysics option without QICE array cannot be used with icloud=3
1886 !-----------------------------------------------------------------------
1889 DO i = 1, model_config_rec % max_dom
1890 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1891 IF ( model_config_rec%icloud .eq. 3) THEN
1892 IF ( model_config_rec%mp_physics(i) .EQ. WSM3SCHEME .OR. &
1893 model_config_rec%mp_physics(i) .EQ. KESSLERSCHEME ) THEN
1897 ENDDO ! Loop over domains
1898 IF ( oops .GT. 0 ) THEN
1899 wrf_err_message = '--- ERROR: Need microphysics schemes with QICE array for icloud = 3'
1900 CALL wrf_message ( wrf_err_message )
1901 wrf_err_message = '--- Choose a microphysics scheme other than WSM3 and Kessler'
1902 CALL wrf_message ( wrf_err_message )
1903 count_fatal_error = count_fatal_error + 1
1906 !-----------------------------------------------------------------------
1907 ! If analysis FDDA is turned off, reset the io_forms to zero so that
1908 ! there is no chance that WRF tries to input the data.
1909 !-----------------------------------------------------------------------
1911 IF ( MAXVAL( model_config_rec%grid_fdda ) .EQ. 0 ) THEN
1912 model_config_rec%io_form_gfdda = 0
1914 IF ( model_config_rec%io_form_gfdda .EQ. 0 ) THEN
1915 wrf_err_message = '--- ERROR: If grid_fdda /= 0, io_form_gfdda must be /= 0'
1916 CALL wrf_message ( wrf_err_message )
1917 wrf_err_message = '--- Set io_form_gfdda in the time_control namelist (probably to 2).'
1918 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1919 count_fatal_error = count_fatal_error + 1
1922 IF ( MAXVAL( model_config_rec%grid_sfdda ) .EQ. 0 ) THEN
1923 model_config_rec%io_form_sgfdda = 0
1925 IF ( model_config_rec%io_form_sgfdda .EQ. 0 ) THEN
1926 wrf_err_message = '--- ERROR: If grid_sfdda /= 0, io_form_sgfdda must be /= 0'
1927 CALL wrf_message ( wrf_err_message )
1928 wrf_err_message = '--- Set io_form_sgfdda in the time_control namelist (probably to 2).'
1929 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1930 count_fatal_error = count_fatal_error + 1
1934 !-----------------------------------------------------------------------
1935 ! If we have asked for the pressure-level diagnostics, make sure we can output them
1936 !-----------------------------------------------------------------------
1938 IF ( model_config_rec%p_lev_diags .EQ. 1 ) THEN
1939 DO i = 1, model_config_rec % max_dom
1940 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1941 IF ( ( MAX ( model_config_rec%auxhist23_interval (i) , &
1942 model_config_rec%auxhist23_interval_d(i) , &
1943 model_config_rec%auxhist23_interval_h(i) , &
1944 model_config_rec%auxhist23_interval_m(i) , &
1945 model_config_rec%auxhist23_interval_s(i) ) == 0 ) .OR. &
1946 ( model_config_rec%io_form_auxhist23 == 0 ) ) THEN
1947 wrf_err_message = '--- ERROR: p_lev_diags requires auxhist23 file information'
1948 CALL wrf_message ( wrf_err_message )
1949 wrf_err_message = '--- ERROR: provide: auxhist23_interval (max_dom) and io_form_auxhist23'
1950 CALL wrf_message ( wrf_err_message )
1951 wrf_err_message = '--- Add supporting IO for stream 23 for pressure-level diags'
1952 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1953 count_fatal_error = count_fatal_error + 1
1956 DO i = 1, model_config_rec % max_dom
1957 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1958 model_config_rec%p_lev_interval(i) = model_config_rec%auxhist23_interval (i)* 60 + &
1959 model_config_rec%auxhist23_interval_d(i)*86400 + &
1960 model_config_rec%auxhist23_interval_h(i)* 3600 + &
1961 model_config_rec%auxhist23_interval_m(i)* 60 + &
1962 model_config_rec%auxhist23_interval_s(i)
1967 !-----------------------------------------------------------------------
1968 ! If we have asked for the height-level diagnostics, make sure we can output them
1969 !-----------------------------------------------------------------------
1971 IF ( model_config_rec%z_lev_diags .EQ. 1 ) THEN
1972 DO i = 1, model_config_rec % max_dom
1973 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1974 IF ( ( MAX ( model_config_rec%auxhist22_interval (i) , &
1975 model_config_rec%auxhist22_interval_d(i) , &
1976 model_config_rec%auxhist22_interval_h(i) , &
1977 model_config_rec%auxhist22_interval_m(i) , &
1978 model_config_rec%auxhist22_interval_s(i) ) == 0 ) .OR. &
1979 ( model_config_rec%io_form_auxhist22 == 0 ) ) THEN
1980 wrf_err_message = '--- ERROR: z_lev_diags requires auxhist22 file information'
1981 CALL wrf_message ( wrf_err_message )
1982 wrf_err_message = '--- ERROR: provide: auxhist22_interval (max_dom) and io_form_auxhist22'
1983 CALL wrf_message ( wrf_err_message )
1984 wrf_err_message = '--- Add supporting IO for stream 22 for height-level diags'
1985 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1986 count_fatal_error = count_fatal_error + 1
1989 DO i = 1, model_config_rec % max_dom
1990 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1991 model_config_rec%z_lev_interval(i) = model_config_rec%auxhist22_interval (i)* 60 + &
1992 model_config_rec%auxhist22_interval_d(i)*86400 + &
1993 model_config_rec%auxhist22_interval_h(i)* 3600 + &
1994 model_config_rec%auxhist22_interval_m(i)* 60 + &
1995 model_config_rec%auxhist22_interval_s(i)
1999 !-----------------------------------------------------------------------
2000 ! For RASM Diagnostics
2001 ! -verify that only one time interval is specified
2002 ! -change the intervals to values used in RASM Diagnotics
2003 ! -verify that a time interval has been set
2004 !-----------------------------------------------------------------------
2006 ! 1. Only one time interval type specified
2008 DO i = 1, model_config_rec % max_dom
2009 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2011 IF ( model_config_rec%mean_diag_interval_s (i) .GT. 0 ) THEN
2012 count_opt = count_opt + 1
2014 IF ( model_config_rec%mean_diag_interval_m (i) .GT. 0 ) THEN
2015 count_opt = count_opt + 1
2017 IF ( model_config_rec%mean_diag_interval_h (i) .GT. 0 ) THEN
2018 count_opt = count_opt + 1
2020 IF ( model_config_rec%mean_diag_interval_d (i) .GT. 0 ) THEN
2021 count_opt = count_opt + 1
2023 IF ( model_config_rec%mean_diag_interval_mo(i) .GT. 0 ) THEN
2024 count_opt = count_opt + 1
2026 IF ( model_config_rec%mean_diag_interval (i) .GT. 0 ) THEN
2027 count_opt = count_opt + 1
2029 IF ( count_opt .GT. 1 ) THEN
2030 wrf_err_message = '--- ERROR: Only use one of: mean_diag_interval, _s, _m, _h, _d, _mo '
2031 CALL wrf_message ( wrf_err_message )
2032 count_fatal_error = count_fatal_error + 1
2036 ! 2. Put canonical intervals into RASM expected form
2038 DO i = 1, model_config_rec % max_dom
2039 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2040 IF ( model_config_rec%mean_diag_interval_s (i) .GT. 0 ) THEN
2041 model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_s (i)
2042 model_config_rec%mean_freq = 1
2044 IF ( model_config_rec%mean_diag_interval_m (i) .GT. 0 ) THEN
2045 model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_m (i)
2046 model_config_rec%mean_freq = 2
2048 IF ( model_config_rec%mean_diag_interval_h (i) .GT. 0 ) THEN
2049 model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_h (i)
2050 model_config_rec%mean_freq = 3
2052 IF ( model_config_rec%mean_diag_interval_d (i) .GT. 0 ) THEN
2053 model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_d (i)
2054 model_config_rec%mean_freq = 4
2056 IF ( model_config_rec%mean_diag_interval_mo(i) .GT. 0 ) THEN
2057 model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_mo(i)
2058 model_config_rec%mean_freq = 5
2060 IF ( model_config_rec%mean_diag_interval (i) .GT. 0 ) THEN
2061 model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval (i)
2062 model_config_rec%mean_freq = 2
2066 ! 3. If requested, need an interval.
2068 IF ( model_config_rec%mean_diag .EQ. 1 ) THEN
2070 DO i = 1, model_config_rec % max_dom
2071 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2072 IF ( model_config_rec%mean_interval (i) .GT. 0 ) THEN
2073 count_opt = count_opt + 1
2076 IF ( count_opt .LT. 1 ) THEN
2077 wrf_err_message = '--- ERROR: mean_diag = 1, but no computation interval given'
2078 CALL wrf_message ( wrf_err_message )
2079 wrf_err_message = ' Use one of: mean_diag_interval, _s, _m, _h, _d, _mo '
2080 CALL wrf_message ( wrf_err_message )
2081 count_fatal_error = count_fatal_error + 1
2085 !-----------------------------------------------------------------------
2086 ! For nwp_diagnostics = 1, history_interval must be used.
2087 !-----------------------------------------------------------------------
2089 IF ( ( model_config_rec%nwp_diagnostics .NE. 0 ) .AND. &
2090 ( model_config_rec%history_interval(1) .EQ. 0 ) ) THEN
2091 wrf_err_message = '--- ERROR: nwp_diagnostics requires the use of "history_interval" namelist.'
2092 CALL wrf_message ( wrf_err_message )
2093 wrf_err_message = '--- Replace interval variable with "history_interval".'
2094 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2095 count_fatal_error = count_fatal_error + 1
2098 !-----------------------------------------------------------------------
2099 ! If a user sets nwp_diagnostics = 1, then radar reflectivity computation
2101 !-----------------------------------------------------------------------
2103 IF ( model_config_rec % nwp_diagnostics == 1 ) model_config_rec % do_radar_ref = 1
2105 !-----------------------------------------------------------------------
2106 ! If hailcast_opt = 1 for any domain, convective parameterization must be off for that domain.
2107 !-----------------------------------------------------------------------
2109 DO i = 1, model_config_rec % max_dom
2110 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2111 IF ( ( model_config_rec%hailcast_opt(i) .NE. 0 ) .AND. &
2112 (model_config_rec%cu_physics(i) .NE. 0) ) THEN
2113 wrf_err_message = '--- hailcast_opt and cu_physics cannot both be turned on for the same domain. You must turn one of them off (=0).'
2114 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2115 count_fatal_error = count_fatal_error + 1
2119 !-----------------------------------------------------------------------
2120 ! Name change in the namelist.input file. We used to only have the
2121 ! ocean mixed layer option (omlcall=1). With the addition of a 3D ocean,
2122 ! now let's change the name of the option. If the old name is present,
2123 ! tell the user to swap their namelist, and then stop.
2124 !-----------------------------------------------------------------------
2126 IF ( model_config_rec%omlcall .NE. 0 ) THEN
2127 wrf_err_message = '--- ERROR: The namelist.input variable "omlcall" has been renamed.'
2128 CALL wrf_message ( wrf_err_message )
2129 wrf_err_message = '--- Replace "omlcall" with the new name "sf_ocean_physics".'
2130 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2131 count_fatal_error = count_fatal_error + 1
2134 !-----------------------------------------------------------------------
2135 ! For adaptive time stepping, certain physics schemes are not allowed
2136 ! to have intermittent frequencies. So, for those schemes below, we just
2137 ! turn the frequencies so that the schemes are called for each time step.
2138 !-----------------------------------------------------------------------
2140 IF ( model_config_rec%use_adaptive_time_step ) THEN
2141 IF ( ( model_config_rec%cu_physics(1) .EQ. BMJSCHEME ) .OR. &
2142 ( model_config_rec%cu_physics(1) .EQ. SCALESASSCHEME) .OR. &
2143 ( model_config_rec%cu_physics(1) .EQ. SASSCHEME ) .OR. &
2144 ( model_config_rec%cu_physics(1) .EQ. OSASSCHEME ) .OR. &
2145 ( model_config_rec%cu_physics(1) .EQ. KSASSCHEME ) .OR. &
2146 ( model_config_rec%cu_physics(1) .EQ. NSASSCHEME ) .OR. &
2147 ( model_config_rec%cu_physics(1) .EQ. TIEDTKESCHEME ) ) THEN
2148 wrf_err_message = '--- WARNING: If use_adaptive_time_step, must use cudt=0 for the following CU schemes:'
2149 CALL wrf_debug ( 1, wrf_err_message )
2150 wrf_err_message = '--- BMJ, all SAS, Tiedtke'
2151 CALL wrf_debug ( 1, wrf_err_message )
2152 wrf_err_message = '--- CUDT=0 has been done for you.'
2153 CALL wrf_debug ( 1, wrf_err_message )
2154 DO i = 1, model_config_rec % max_dom
2155 model_config_rec%cudt(i) = 0
2160 !-----------------------------------------------------------------------
2161 ! When digital filtering is turned on, if no specific time step is given to be
2162 ! used during the digitial filtering period, then the standard WRF time
2163 ! step is used. If neither time steps are specified, then fatal error.
2164 !-----------------------------------------------------------------------
2166 IF ( .NOT. model_config_rec%dfi_opt .EQ. DFI_NODFI ) THEN
2167 IF ( model_config_rec%time_step_dfi .EQ. -1 ) THEN
2168 model_config_rec%time_step_dfi = model_config_rec%time_step
2169 IF ( model_config_rec%time_step_dfi .EQ. -1 ) THEN
2170 wrf_err_message = '--- ERROR: DFI Timestep or standard WRF time step must be specified.'
2171 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2172 count_fatal_error = count_fatal_error + 1
2177 !-----------------------------------------------------------------------
2178 ! The cu_rad_feedback namelist flag with the two Grell cumulus parameterization
2179 ! schemes needs to have the namelist flag cu_diag=1
2180 !-----------------------------------------------------------------------
2182 DO i = 1, model_config_rec % max_dom
2183 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2184 IF ( ( model_config_rec%cu_rad_feedback(i) .EQV. .TRUE. ) .OR. &
2185 ( model_config_rec%cu_rad_feedback(i) .EQV. .true. ) ) THEN
2186 IF ( ( model_config_rec%cu_physics(1) .EQ. GFSCHEME ) .OR. &
2187 ( model_config_rec%cu_physics(1) .EQ. G3SCHEME ) .OR. &
2188 ( model_config_rec%cu_physics(1) .EQ. GDSCHEME ) ) THEN
2189 wrf_err_message = '--- WARNING: Turning on cu_rad_feedback also requires setting cu_diag== 1'
2190 CALL wrf_debug ( 1, wrf_err_message )
2191 model_config_rec%cu_diag(i) = 1
2193 model_config_rec%cu_diag(i) = 0
2198 !-----------------------------------------------------------------------
2199 ! The namelist flag cu_diag=1 must have one of the two Grell cumulus parameterizations
2200 ! turned on. All other cumulus parameterizations need to have cu_diag=0
2201 !-----------------------------------------------------------------------
2203 DO i = 1, model_config_rec % max_dom
2204 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2205 IF ( model_config_rec%cu_diag(i) .EQ. G3TAVE ) THEN
2206 IF ( ( model_config_rec%cu_physics(i) .NE. GDSCHEME ) .AND. &
2207 ( model_config_rec%cu_physics(i) .NE. GFSCHEME ) .AND. &
2208 ( model_config_rec%cu_physics(i) .NE. KFCUPSCHEME ) .AND. &
2209 ( model_config_rec%cu_physics(i) .NE. G3SCHEME ) ) THEN
2210 wrf_err_message = '--- ERROR: Using cu_diag=1 requires use of one of the following CU schemes:'
2211 CALL wrf_message ( wrf_err_message )
2212 wrf_err_message = '--- Grell-Freitas (GF) CU scheme'
2213 CALL wrf_message ( wrf_err_message )
2214 wrf_err_message = '--- Grell 3D (G3) CU scheme'
2215 CALL wrf_message ( wrf_err_message )
2216 wrf_err_message = '--- Kain-Fritsch Cumulus Potential (KF-CuP) CU scheme'
2217 CALL wrf_message ( wrf_err_message )
2218 wrf_err_message = '--- Grell-Devenyi (GD) CU scheme'
2219 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2220 count_fatal_error = count_fatal_error + 1
2225 !-----------------------------------------------------------------------
2226 ! The namelist flag kf_edrates=1 must have one of the three KF cumulus parameterizations
2227 ! turned on. All other cumulus parameterizations need to have kf_edrates=0
2228 !-----------------------------------------------------------------------
2230 DO i = 1, model_config_rec % max_dom
2231 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2232 IF ( model_config_rec%kf_edrates(i) .EQ. KFEDRATES ) THEN
2233 IF ( ( model_config_rec%cu_physics(i) .NE. KFETASCHEME ) .AND. &
2234 ( model_config_rec%cu_physics(i) .NE. MSKFSCHEME ) .AND. &
2235 ( model_config_rec%cu_physics(i) .NE. KFSCHEME ) ) THEN
2236 wrf_err_message = '--- ERROR: Using kf_edrates=1 requires use of one of the following KF schemes:'
2237 CALL wrf_message ( wrf_err_message )
2238 wrf_err_message = '--- Kain-Fritsch (cu_physics=1)'
2239 CALL wrf_message ( wrf_err_message )
2240 wrf_err_message = '--- Multi-scale Kain-Fritsch (cu_physics=11)'
2241 CALL wrf_message ( wrf_err_message )
2242 wrf_err_message = '--- old Kain-Fritsch (cu_physics=99)'
2243 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2244 count_fatal_error = count_fatal_error + 1
2249 !-----------------------------------------------------------------------
2250 ! Test to see if we allocate space for the time series.
2251 !-----------------------------------------------------------------------
2253 IF ( wrf_dm_on_monitor() ) THEN
2254 CALL wrf_tsin_exist ( exists )
2256 IF ( model_config_rec%solar_diagnostics == 1 ) THEN
2257 model_config_rec%process_time_series = 2
2259 model_config_rec%process_time_series = 1
2262 model_config_rec%process_time_series = 0
2266 CALL wrf_dm_bcast_integer(model_config_rec%process_time_series, 1)
2268 !-----------------------------------------------------------------------
2269 ! The three Grell cumulus parameterization schemes need to have the
2270 ! namelist flag cu_diag=1, and all other cumulus schemes must have
2272 !-----------------------------------------------------------------------
2274 DO i = 1, model_config_rec % max_dom
2275 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2276 IF ( ( model_config_rec%cu_physics(i) .EQ. GDSCHEME ) .OR. &
2277 ( model_config_rec%cu_physics(i) .EQ. GFSCHEME ) .OR. &
2278 ( model_config_rec%cu_physics(i) .EQ. KFCUPSCHEME ) .OR. &
2279 ( model_config_rec%cu_physics(i) .EQ. G3SCHEME ) ) THEN
2280 model_config_rec%cu_diag(i) = 1
2282 model_config_rec%cu_diag(i) = 0
2286 !-----------------------------------------------------------------------
2287 ! Only implement the TEMF PBL scheme with the TEMP SFCLAY scheme.
2288 !-----------------------------------------------------------------------
2290 DO i = 1, model_config_rec % max_dom
2291 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2292 IF ( ( model_config_rec%bl_pbl_physics(i) .EQ. TEMFPBLSCHEME ) .AND. &
2293 ( model_config_rec%sf_sfclay_physics(i) .NE. TEMFSFCSCHEME ) ) THEN
2294 wrf_err_message = '--- ERROR: Using bl_pbl_physics=10 requires sf_sfclay_physics=10 '
2295 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2296 count_fatal_error = count_fatal_error + 1
2297 ELSEIF ( ( model_config_rec%bl_pbl_physics(i) .NE. TEMFPBLSCHEME ) .AND. &
2298 ( model_config_rec%sf_sfclay_physics(i) .EQ. TEMFSFCSCHEME ) ) THEN
2299 wrf_err_message = '--- ERROR: Using sf_sfclay_physics=10 requires bl_pbl_physics=10 '
2300 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2301 count_fatal_error = count_fatal_error + 1
2303 ENDDO ! Loop over domains
2305 !-----------------------------------------------------------------------
2306 ! Need to set lagday to 150 if tmn_update is 1
2307 !-----------------------------------------------------------------------
2309 IF ( model_config_rec%tmn_update .EQ. 1 .AND. &
2310 model_config_rec%lagday .EQ. 1 ) THEN
2311 wrf_err_message = '--- ERROR: Using tmn_update=1 requires lagday=150 '
2312 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2313 count_fatal_error = count_fatal_error + 1
2316 !-----------------------------------------------------------------------
2317 ! Do not allow digital filtering to be run with TEMF.
2318 !-----------------------------------------------------------------------
2320 DO i = 1, model_config_rec % max_dom
2321 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2322 IF ( ( model_config_rec%bl_pbl_physics(i) .EQ. TEMFPBLSCHEME ) .AND. &
2323 (model_config_rec%dfi_opt .NE. DFI_NODFI) ) THEN
2324 wrf_err_message = '--- ERROR: DFI not available for bl_pbl_physics=10 '
2325 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2326 count_fatal_error = count_fatal_error + 1
2328 ENDDO ! Loop over domains
2330 !-----------------------------------------------------------------------
2331 ! If this is a restart, shut off the DFI.
2332 !-----------------------------------------------------------------------
2334 IF ( model_config_rec%restart ) THEN
2335 model_config_rec%dfi_opt = DFI_NODFI
2338 !-----------------------------------------------------------------------
2339 ! The CLM scheme may not even be compiled, so make sure it is not allowed
2340 ! to be run if the code is not available.
2341 !-----------------------------------------------------------------------
2343 !#if !defined ( WRF_USE_CLM )
2345 ! DO i = 1, model_config_rec % max_dom
2346 ! IF ( model_config_rec%sf_surface_physics(i) .EQ. CLMSCHEME ) THEN
2349 ! ENDDO ! Loop over domains
2350 ! IF ( oops .GT. 0 ) THEN
2351 ! wrf_err_message = '--- ERROR: The CLM surface scheme was requested in the namelist.input file.'
2352 ! CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2353 ! wrf_err_message = '--- ERROR: However, the WRF CLM scheme was not compiled in WRF.'
2354 ! CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2355 ! wrf_err_message = '--- ERROR: Please place the -DWRF_USE_CLM option in configure.wrf file, and recompile.'
2356 ! ! CALL wrf_error_fatal ( wrf_err_message )
2357 ! CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2358 ! fatal_error = .true.
2359 ! count_fatal_error = count_fatal_error + 1
2362 #if (WRF_USE_CLM != 1)
2364 DO i = 1, model_config_rec % max_dom
2365 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2366 IF ( model_config_rec%sf_surface_physics(i) .EQ. CLMSCHEME ) THEN
2369 ENDDO ! Loop over domains
2370 IF ( oops .GT. 0 ) THEN
2371 wrf_err_message = '--- ERROR: The CLM surface scheme was requested in the namelist.input file.'
2372 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2373 wrf_err_message = '--- ERROR: However, the WRF CLM scheme was not compiled in WRF.'
2374 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2375 wrf_err_message = '--- ERROR: Please place the -DWRF_USE_CLM option in configure.wrf file, and recompile.'
2376 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2377 count_fatal_error = count_fatal_error + 1
2379 #if ( WRF_CHEM == 1)
2380 DO i = 1, model_config_rec % max_dom
2381 IF ( model_config_rec%bio_emiss_opt(i) == MEGAN2_CLM ) THEN
2386 IF ( oops .GT. 0 ) THEN
2387 wrf_err_message = '--- ERROR: The CLM Megan2.1 bio emission scheme was requested in the namelist.input file.'
2388 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2389 wrf_err_message = '--- ERROR: However, the WRF CLM scheme was not compiled in WRF.'
2390 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2391 wrf_err_message = '--- ERROR: Please place the -DWRF_USE_CLM option in configure.wrf file, and recompile.'
2392 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2393 count_fatal_error = count_fatal_error + 1
2397 !-----------------------------------------------------------------------
2398 ! The CLM scheme has been compiled.
2399 ! Check for possible logic errors with namelist settings.
2400 !-----------------------------------------------------------------------
2401 #if ( WRF_CHEM == 1 )
2403 DO i = 1, model_config_rec % max_dom
2404 IF ( model_config_rec%bio_emiss_opt(i) == MEGAN2_CLM .and. &
2405 model_config_rec%sf_surface_physics(i) /= CLMSCHEME ) THEN
2409 IF ( oops .GT. 0 ) THEN
2410 wrf_err_message = '--- ERROR: The CLM Megan2.1 bio emission scheme was requested in the namelist.input file.'
2411 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2412 wrf_err_message = '--- ERROR: However, the CLM surface physics scheme was not requested in the namelist.input file.'
2413 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2414 wrf_err_message = '--- ERROR: Please set the physics namelist variable sf_surface_physics to 5 in the namelist.input file.'
2415 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2416 count_fatal_error = count_fatal_error + 1
2420 DO i = 1, model_config_rec % max_dom
2421 IF ( model_config_rec%SF_SURFACE_PHYSICS(i) == CLMSCHEME .and. &
2422 model_config_rec%SF_URBAN_PHYSICS(i) >= 1 .and. &
2423 model_config_rec%SF_URBAN_PHYSICS(i) <= 3 ) THEN
2427 IF ( oops .GT. 0 ) THEN
2428 wrf_err_message = '--- ERROR: CLM does not work with any URBAN PHYSICS SCHEME'
2429 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2430 count_fatal_error = count_fatal_error + 1
2434 !-----------------------------------------------------------------------
2435 ! The CTSM scheme may not even be compiled, so make sure it is not allowed
2436 ! to be run if the code is not available.
2437 !-----------------------------------------------------------------------
2439 #if !defined ( WRF_USE_CTSM )
2441 DO i = 1, model_config_rec % max_dom
2442 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2443 IF ( model_config_rec%sf_surface_physics(i) .EQ. CTSMSCHEME ) THEN
2446 ENDDO ! Loop over domains
2447 IF ( oops .GT. 0 ) THEN
2448 wrf_err_message = '--- ERROR: The CTSM surface scheme was requested in the namelist.input file.'
2449 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2450 wrf_err_message = '--- ERROR: However, the WRF CTSM scheme was not compiled in WRF.'
2451 CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2452 wrf_err_message = '--- ERROR: Please read doc/README.CTSM for how to compile WRF with CTSM.'
2453 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2454 count_fatal_error = count_fatal_error + 1
2458 !-----------------------------------------------------------------------
2459 ! grav_settling = 1 must be turned off for mp_physics=28.
2460 !-----------------------------------------------------------------------
2462 DO i = 1, model_config_rec % max_dom
2463 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2464 IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2465 IF ( model_config_rec%grav_settling(i) .NE. FOGSETTLING0 ) THEN
2466 model_config_rec%grav_settling(i) = 0
2470 ENDDO ! Loop over domains
2471 IF ( oops .GT. 0 ) THEN
2472 wrf_err_message = '--- NOTE: mp_physics == 28, already has gravitational fog settling; resetting grav_settling to 0'
2473 CALL wrf_debug ( 1, wrf_err_message )
2476 !-----------------------------------------------------------------------
2477 ! scalar_pblmix = 1 should be turned on for mp_physics=28. But can be off for MYNN (when bl_mynn_mixscalars = 1)
2478 !-----------------------------------------------------------------------
2480 DO i = 1, model_config_rec % max_dom
2481 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2482 IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2483 IF ( (model_config_rec%use_aero_icbc .OR. model_config_rec%use_rap_aero_icbc) &
2484 .AND. model_config_rec%scalar_pblmix(i) .NE. 1 ) THEN
2485 model_config_rec%scalar_pblmix(i) = 1
2489 ENDDO ! Loop over domains
2490 IF ( oops .GT. 0 ) THEN
2491 wrf_err_message = '--- WARNING: For mp_physics == 28 and use_aero_icbc is true, recommend to turn on scalar_pblmix'
2492 CALL wrf_debug ( 1, wrf_err_message )
2493 wrf_err_message = 'resetting scalar_pblmix = 1'
2494 CALL wrf_debug ( 1, wrf_err_message )
2499 DO i = 1, model_config_rec % max_dom
2500 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2501 IF ((model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME) ) THEN
2502 IF ( model_config_rec%bl_mynn_mixscalars(i) .EQ. 1 ) THEN
2503 model_config_rec%scalar_pblmix(i) = 0
2507 ENDDO ! Loop over domains
2508 IF ( oops .GT. 0 ) THEN
2509 wrf_err_message = '--- WARNING: MYNN is set to mix scalars, turning off scalar_pblmix'
2510 CALL wrf_message ( wrf_err_message )
2513 !-----------------------------------------------------------------------
2514 ! Set aer_init_opt for Thompson-MP-Aero (mp_physics=28)
2515 !-----------------------------------------------------------------------
2516 DO i = 1, model_config_rec % max_dom
2517 IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2518 IF ( model_config_rec%use_aero_icbc ) THEN
2519 model_config_rec%aer_init_opt = 1
2520 ELSE IF ( model_config_rec%use_rap_aero_icbc ) THEN
2521 model_config_rec%aer_init_opt = 2
2526 !-----------------------------------------------------------------------
2527 ! Check if qna_update=0 when aer_init_opt>1 for Thompson-MP-Aero (mp_physics=28)
2528 !-----------------------------------------------------------------------
2529 DO i = 1, model_config_rec % max_dom
2530 IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2531 IF ( model_config_rec%aer_init_opt .GT. 1 .and. model_config_rec%qna_update .EQ. 0 ) THEN
2532 wrf_err_message = '--- ERROR: Time-varying sfc aerosol emissions not set for mp_physics=28 '
2533 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2534 wrf_err_message = '--- ERROR: Please set qna_update=1 and control through auxinput17 options '
2535 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2536 count_fatal_error = count_fatal_error + 1
2541 !-----------------------------------------------------------------------
2542 ! Set aer_fire_emit_opt for Thompson-MP-Aero (mp_physics=28)
2543 !-----------------------------------------------------------------------
2544 DO i = 1, model_config_rec % max_dom
2545 IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO .AND. model_config_rec%wif_fire_emit) THEN
2546 IF ( model_config_rec%aer_init_opt .EQ. 2) THEN
2547 IF ( model_config_rec%wif_input_opt .EQ. 1 ) THEN
2548 model_config_rec%aer_fire_emit_opt = 1
2549 ELSE IF ( model_config_rec%wif_input_opt .EQ. 2 ) THEN
2550 model_config_rec%aer_fire_emit_opt = 2
2552 ELSE IF ( model_config_rec%aer_init_opt .EQ. 0 .OR. model_config_rec%aer_init_opt .EQ. 1) THEN
2553 wrf_err_message = '--- ERROR: wif_fire_emit=.true. but selected aerosol source does not contain fire emissions '
2554 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2555 wrf_err_message = '--- ERROR: Please use first guess aerosol source with fire emissions and set use_rap_aero_icbc=.true. '
2556 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2557 count_fatal_error = count_fatal_error + 1
2562 !-----------------------------------------------------------------------
2563 ! Set warning message if wif_fire_inj for Thompson-MP-Aero (mp_physics=28)
2564 ! is turned on when no PBL scheme is active
2565 !-----------------------------------------------------------------------
2566 DO i = 1, model_config_rec % max_dom
2567 IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO .AND. model_config_rec%wif_fire_emit) THEN
2568 IF ( model_config_rec%bl_pbl_physics(i) .EQ. 0 ) THEN
2569 wrf_err_message = '--- WARNING: PBL scheme not active but wif_fire_inj=1 for mp_physics=28 '
2570 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2575 !-----------------------------------------------------------------------
2576 ! Stop the model if full_khain_lynn or mp_physics = 32 is selected
2577 !-----------------------------------------------------------------------
2578 DO i = 1, model_config_rec % max_dom
2579 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2580 IF ( model_config_rec%mp_physics(i) .eq. full_khain_lynn) THEN
2582 wrf_err_message = '--- ERROR: full bin spectral microphysics should not be used '
2583 CALL wrf_message ( wrf_err_message )
2584 wrf_err_message = '--- ERROR: use fast version instead (mp_physics=30)'
2585 CALL wrf_message ( wrf_err_message )
2586 count_fatal_error = count_fatal_error + 1
2588 ENDDO ! Loop over domains
2590 !-----------------------------------------------------------------------
2591 ! DJW Check that we're not using ndown and vertical nesting.
2592 !-----------------------------------------------------------------------
2593 DO i=1,model_config_rec%max_dom
2594 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2595 IF ((model_config_rec%vert_refine_method(i) .NE. 0) .AND. (model_config_rec%vert_refine_fact .NE. 1)) THEN
2596 wrf_err_message = '--- ERROR: vert_refine_fact is ndown specific and cannot be used with vert_refine_method, and vice versa.'
2597 CALL wrf_debug ( 1, wrf_err_message )
2601 !-----------------------------------------------------------------------
2602 ! DJW Check that only one type of vertical nesting is enabled.
2603 !-----------------------------------------------------------------------
2604 DO i=1,model_config_rec%max_dom
2605 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2606 IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2607 DO j=1,model_config_rec%max_dom
2608 IF ((model_config_rec%vert_refine_method(i) .NE. model_config_rec%vert_refine_method(j)) .AND. (model_config_rec%vert_refine_method(j) .NE. 0)) THEN
2609 write(wrf_err_message,'(A,I1,A,I2,A,I1,A,I2,A)') '--- ERROR: vert_refine_method differs on grid ids ',model_config_rec%grid_id(i),' and ',model_config_rec%grid_id(j),'. Only one type of vertical grid nesting can be used at a time.'
2610 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2611 count_fatal_error = count_fatal_error + 1
2617 !-----------------------------------------------------------------------
2618 ! DJW Check that e_vert is the same for nested domains not using
2619 ! vertical nesting. Don't do this check if we're using ndown.
2620 !-----------------------------------------------------------------------
2621 IF ((model_config_rec%max_dom .GT. 1) .AND. (model_config_rec%vert_refine_fact .EQ. 1)) THEN
2622 DO i=1,model_config_rec%max_dom
2623 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2624 IF (((model_config_rec%parent_id(i) .NE. 0) .AND. (model_config_rec%parent_id(i) .NE. model_config_rec%grid_id(i))) .AND. (model_config_rec%vert_refine_method(i) .EQ. 0)) THEN
2625 DO j=1,model_config_rec%max_dom
2626 IF ((i .NE. j) .AND. (model_config_rec%parent_id(i) .EQ. model_config_rec%grid_id(j))) THEN
2627 IF (model_config_rec%e_vert(i) .NE. model_config_rec%e_vert(j)) THEN
2628 write(wrf_err_message,'(A,I2,A,I2,A)') '--- ERROR: e_vert differs on grid ids ',model_config_rec%grid_id(i),' and ',model_config_rec%grid_id(j),'. Set vert_refine_method or make e_vert consistent.'
2629 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2630 count_fatal_error = count_fatal_error + 1
2638 !-----------------------------------------------------------------------
2639 ! Check that vertical levels are defined in a logical way.
2640 ! DJW Check that domains without a parent do not have vertical
2642 !-----------------------------------------------------------------------
2643 DO i=1,model_config_rec%max_dom
2644 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2645 IF ((model_config_rec%parent_id(i) .EQ. 0) .OR. (model_config_rec%parent_id(i) .EQ. model_config_rec%grid_id(i))) THEN
2646 IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2647 write(wrf_err_message,'(A,I1,A,I2,A)') '--- ERROR: vert_refine_method=',model_config_rec%vert_refine_method(i),' for grid_id=',model_config_rec%grid_id(i),', must be 0 for a non-nested domain.'
2648 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2649 count_fatal_error = count_fatal_error + 1
2654 !-----------------------------------------------------------------------
2655 ! DJW Check that we've got appropriate e_vert for integer refinement.
2656 !-----------------------------------------------------------------------
2657 DO i = 1, model_config_rec % max_dom
2658 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2659 IF (model_config_rec%vert_refine_method(i) .EQ. 1) THEN
2660 j = model_config_rec%parent_id(i)
2661 IF (MOD(model_config_rec%e_vert(i)-1, model_config_rec%e_vert(j)-1) .NE. 0) THEN
2662 write(wrf_err_message,'(A,I2,A,I2,A)') "--- ERROR: grid_id=",i," and parent (grid_id=",j,") have incompatible e_vert's for vertical nesting with integer refinement."
2663 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2664 count_fatal_error = count_fatal_error + 1
2669 !-----------------------------------------------------------------------
2670 ! Check that max_ts_level is smaller than the number of half levels
2671 !-----------------------------------------------------------------------
2672 IF ( model_config_rec % max_ts_level .gt. model_config_rec %e_vert(1)-1 ) then
2673 wrf_err_message = ' max_ts_level must be <= number of znu half layers '
2674 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2675 wrf_err_message = ' max_ts_level is reset to the number of znu half layers '
2676 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2677 model_config_rec % max_ts_level = model_config_rec %e_vert(1)-1
2680 !-----------------------------------------------------------------------
2681 ! Consistency checks between vertical refinement and radiation
2682 ! scheme selection. For "choose any vertical levels" for the nest,
2683 ! only option 1 (RRTM/Dudhia) or option 4 (RRTMG) are eligible.
2684 !-----------------------------------------------------------------------
2685 DO i = 2, model_config_rec % max_dom
2686 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2687 IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2688 IF ( ( ( model_config_rec%ra_lw_physics(i) .EQ. 0 ) .OR. &
2689 ( model_config_rec%ra_lw_physics(i) .EQ. RRTMSCHEME ) .OR. &
2690 ( model_config_rec%ra_lw_physics(i) .EQ. RRTMG_LWSCHEME ) ) .AND. &
2691 ( ( model_config_rec%ra_sw_physics(i) .EQ. 0 ) .OR. &
2692 ( model_config_rec%ra_sw_physics(i) .EQ. SWRADSCHEME ) .OR. &
2693 ( model_config_rec%ra_sw_physics(i) .EQ. RRTMG_SWSCHEME ) ) ) THEN
2694 ! We are OK, I just hate writing backwards / negative / convoluted if tests
2695 ! that are not easily comprehensible.
2697 wrf_err_message = '--- ERROR: vert_refine_method=2 only works with ra_lw/sw_physics=1 (RRTM/Dudhia) or ra_lw/sw_physics=4 (RRTMG)'
2698 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2699 count_fatal_error = count_fatal_error + 1
2704 !-----------------------------------------------------------------------
2705 ! Consistency checks for vertical refinement:
2706 ! feedback has to be turned off
2707 !-----------------------------------------------------------------------
2709 DO i = 2, model_config_rec % max_dom
2710 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2711 IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2712 IF ( model_config_rec%feedback .NE. 0 ) THEN
2718 IF ( oops .GT. 0 ) THEN
2719 wrf_err_message = '--- ERROR: vert_refine_method=2 only works with feedback = 0 '
2720 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2721 count_fatal_error = count_fatal_error + 1
2724 !-----------------------------------------------------------------------
2725 ! Consistency checks for vertical refinement:
2726 ! rebalance must be set to 1
2727 !-----------------------------------------------------------------------
2729 DO i = 2, model_config_rec % max_dom
2730 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2731 IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2732 IF ( model_config_rec%rebalance .NE. 1 ) THEN
2738 IF ( oops .GT. 0 ) THEN
2739 wrf_err_message = '--- ERROR: vert_refine_method=2 only works with rebalance=1 '
2740 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2741 count_fatal_error = count_fatal_error + 1
2744 !-----------------------------------------------------------------------
2745 ! This WRF version does not support trajectories on a global domain
2746 !-----------------------------------------------------------------------
2747 IF ( model_config_rec % polar(1) .AND. &
2748 model_config_rec % fft_filter_lat .LT. 90. .AND. &
2749 model_config_rec % traj_opt .NE. 0 ) THEN
2750 CALL wrf_debug ( 0, '--- ERROR: Trajectories not supported on global domain' )
2751 count_fatal_error = count_fatal_error + 1
2754 !-----------------------------------------------------------------------
2755 ! If the user did not specify a global setting in the lateral BC
2756 ! portion of the namelist file (polar), but the distance around the
2757 ! equator is approximately equal to the entire globe, then it is likely
2758 ! that the user probably forgot to flip that polar switch on.
2759 !-----------------------------------------------------------------------
2760 lon_extent_is_global = .FALSE.
2761 IF ( ABS ( model_config_rec % e_we(1) * model_config_rec % dx(1) - 2. * piconst / reradius ) .LT. model_config_rec % dx(1) ) THEN
2762 lon_extent_is_global = .TRUE.
2765 lat_extent_is_global = .FALSE.
2766 IF ( ABS ( model_config_rec % e_sn(1) * model_config_rec % dy(1) - piconst / reradius ) .LT. model_config_rec % dy(1) ) THEN
2767 lat_extent_is_global = .TRUE.
2770 IF ( ( .NOT. model_config_rec % polar(1) ) .AND. &
2771 ( lon_extent_is_global .AND. lat_extent_is_global ) ) THEN
2772 CALL wrf_debug ( 0, '--- ERROR: Domain size is global, set &bdy_control polar=.TRUE.' )
2773 count_fatal_error = count_fatal_error + 1
2776 !-----------------------------------------------------------------------
2777 ! Remapping namelist variables for gridded and surface fdda to aux streams 9 and 10.
2778 ! Relocated here so that the remappings are after checking the namelist for inconsistencies.
2779 !-----------------------------------------------------------------------
2781 # include "../dyn_em/namelist_remappings_em.h"
2786 !-----------------------------------------------------------------------
2787 ! For the real program (ARW only), check that the vertical interpolation options
2788 ! selected by the user are consistent.
2789 ! 1. If the user has turned-off using the surface level, do not allow the force
2790 ! option to select how many layers the surface is to be used through.
2791 ! 2. If the user has turned-off using the surface level, do not allow the
2792 ! lowest level from surface option to be activated.
2793 !-----------------------------------------------------------------------
2795 IF ( model_config_rec % use_wps_input .EQ. 1 ) THEN
2796 IF ( ( .NOT. model_config_rec % use_surface ) .AND. &
2797 ( model_config_rec % force_sfc_in_vinterp .GT. 0 ) ) THEN
2798 wrf_err_message = '--- NOTE: Inconsistent vertical interpolation settings in program real.'
2799 CALL wrf_debug ( 1, wrf_err_message )
2800 wrf_err_message = '--- NOTE: With use_surface=F, automatically setting force_sfc_in_vinterp=0.'
2801 CALL wrf_debug ( 1, wrf_err_message )
2802 model_config_rec % force_sfc_in_vinterp = 0
2804 IF ( ( .NOT. model_config_rec % use_surface ) .AND. &
2805 ( model_config_rec % lowest_lev_from_sfc ) ) THEN
2806 wrf_err_message = '--- NOTE: Inconsistent vertical interpolation settings in program real.'
2807 CALL wrf_debug ( 1, wrf_err_message )
2808 wrf_err_message = '--- NOTE: With use_surface=F, automatically setting lowest_lev_from_sfc=F.'
2809 CALL wrf_debug ( 1, wrf_err_message )
2810 model_config_rec % lowest_lev_from_sfc = .FALSE.
2815 #if (EM_CORE == 1 && WRFPLUS == 1 )
2816 IF ( ( model_config_rec%jcdfi_use ).AND. &
2817 ( model_config_rec%jcdfi_diag .NE. 1 ) ) THEN
2818 wrf_err_message = '--- ERROR: If jcdfi_use = 1, then jcdfi_diag must also = 1 '
2819 CALL wrf_message ( wrf_err_message )
2820 wrf_err_message = '--- Change jcdfi_diag in namelist.input '
2821 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2822 count_fatal_error = count_fatal_error + 1
2824 ! derived namelist for packaged a_/g_ variables
2825 model_config_rec%mp_physics_plus = 0
2826 DO i = 1, model_config_rec % max_dom
2827 model_config_rec%mp_physics_plus(i) = model_config_rec%mp_physics(i)
2829 model_config_rec%cu_used_plus = 0
2830 DO i = 1, model_config_rec % max_dom
2831 IF ( model_config_rec%cu_physics(i) .NE. NOCUSCHEME ) THEN
2832 model_config_rec%cu_used_plus = 1
2835 model_config_rec%shcu_used_plus = 0
2836 DO i = 1, model_config_rec % max_dom
2837 IF ( model_config_rec%shcu_physics(i) .NE. NOSHCUSCHEME ) THEN
2838 model_config_rec%shcu_used_plus = 1
2844 # if( BUILD_SBM_FAST != 1)
2845 !-----------------------------------------------------------------------
2846 ! If the FAST SBM scheme is requested and it is not compiled, let the
2848 !-----------------------------------------------------------------------
2850 IF ( model_config_rec % mp_physics(1) .EQ. FAST_KHAIN_LYNN_SHPUND ) THEN
2851 wrf_err_message = '--- ERROR: FAST SBM scheme must be built with a default compile-time flag'
2852 CALL wrf_message ( wrf_err_message )
2853 wrf_err_message = '--- ERROR: Run ./clean -a, ./configure, ./compile scripts again'
2854 CALL wrf_message ( wrf_err_message )
2855 count_fatal_error = count_fatal_error + 1
2860 !-----------------------------------------------------------------------
2861 ! If the RRTMG FAST schemes are requested, check that the code with
2862 ! built to use them.
2863 !-----------------------------------------------------------------------
2865 #if( BUILD_RRTMG_FAST != 1)
2866 IF ( ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME_FAST ) .OR. &
2867 ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME_FAST ) ) THEN
2868 wrf_err_message = '--- ERROR: RRTMG FAST schemes must be built with a default compile-time flag'
2869 CALL wrf_message ( wrf_err_message )
2870 wrf_err_message = '--- ERROR: Run ./clean -a, ./configure, ./compile scripts again'
2871 CALL wrf_message ( wrf_err_message )
2872 count_fatal_error = count_fatal_error + 1
2876 !-----------------------------------------------------------------------
2877 ! If the RRTMG KIAPS schemes are requested, check that the code with
2878 ! built to use them.
2879 !-----------------------------------------------------------------------
2881 #if( BUILD_RRTMK != 1)
2882 IF ( ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_LWSCHEME ) .OR. &
2883 ( model_config_rec % ra_sw_physics(1) .EQ. RRTMK_SWSCHEME ) ) THEN
2884 wrf_err_message = '--- ERROR: RRTMG-based KIAPS schemes must be built with a default compile-time flag'
2885 CALL wrf_message ( wrf_err_message )
2886 wrf_err_message = '--- ERROR: Run ./clean -a, ./configure, ./compile scripts again'
2887 CALL wrf_message ( wrf_err_message )
2888 count_fatal_error = count_fatal_error + 1
2892 !-----------------------------------------------------------------------
2893 ! Set the namelist parameter o3input to 0 for the radiation schemes other
2894 ! than RRTMG_LWSCHEME and RRTMG_SWSCHEME.
2895 !-----------------------------------------------------------------------
2897 IF ( ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME ) .OR. &
2898 ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME ) .OR. &
2899 ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_LWSCHEME ) .OR. &
2900 ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_SWSCHEME ) .OR. &
2901 ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME_FAST ) .OR. &
2902 ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME_FAST ) ) THEN
2903 wrf_err_message = '--- NOTE: RRTMG radiation is used, namelist ' // &
2904 'value for o3input (ozone input) is used '
2905 CALL wrf_debug ( 1, wrf_err_message )
2907 model_config_rec % o3input = 0
2908 wrf_err_message = '--- NOTE: RRTMG radiation is not used, setting: ' // &
2909 'o3input=0 to avoid data pre-processing'
2910 CALL wrf_debug ( 1, wrf_err_message )
2913 !-----------------------------------------------------------------------
2914 ! Consistency checks between eclipse option and shortwave radiation
2915 ! scheme selection. Eclipse option only applies to
2916 ! RRTMG_SWSCHEME, SWRADSCHEME, GSFCSWSCHEME and GODDARDSWSCHEME
2917 !-----------------------------------------------------------------------
2918 DO i = 1, model_config_rec % max_dom
2919 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2920 IF ( model_config_rec%ra_sw_eclipse == 1 ) THEN
2921 IF ( ( model_config_rec%ra_sw_physics(i) .EQ. RRTMG_SWSCHEME ) .OR. &
2922 ( model_config_rec%ra_sw_physics(i) .EQ. SWRADSCHEME ) .OR. &
2923 ( model_config_rec%ra_sw_physics(i) .EQ. GSFCSWSCHEME ) .OR. &
2924 ( model_config_rec%ra_sw_physics(i) .EQ. GODDARDSWSCHEME ) ) THEN
2925 ! We are OK, these sw radiation schemes have eclipse physics
2927 wrf_err_message = '--- ERROR: ra_sw_eclipse=1 only works with ra_sw_physics=1 (Dudhia), ' // &
2928 '=2 (Old Goddard), =4 (RRTMG) and =5 (new Goddard) '
2929 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2930 count_fatal_error = count_fatal_error + 1
2935 #if (WRF_CHEM == 1 && WRF_KPP == 1 )
2936 !-----------------------------------------------------------------------
2937 ! Check for consistent chem_opt and irr_opt
2938 !-----------------------------------------------------------------------
2939 DO i = 1, model_config_rec % max_dom
2940 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2941 IF ( model_config_rec%irr_opt(i) > 0 .and. &
2942 (model_config_rec%chem_opt(i) /= mozcart_kpp .and. &
2943 model_config_rec%chem_opt(i) /= t1_mozcart_kpp .and. &
2944 model_config_rec%chem_opt(i) /= mozart_mosaic_4bin_kpp .and. &
2945 model_config_rec%chem_opt(i) /= mozart_mosaic_4bin_aq_kpp ) ) THEN
2946 wrf_err_message = '--- ERROR: IRR diagnostics can only be used with the following chem_opt settings:'
2947 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2948 wrf_err_message = ' MOZCART_KPP, T1_MOZCART_KPP, MOZART_MOSAIC_4BIN_KPP, MOZART_MOSAIC_4BIN_AQ_KPP'
2949 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2950 write(wrf_err_message,'('' chem_opt = '',i3,'', '',i3,'', '',i3,'', or '',i3)') &
2951 MOZCART_KPP, T1_MOZCART_KPP, MOZART_MOSAIC_4BIN_KPP, MOZART_MOSAIC_4BIN_AQ_KPP
2952 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2953 count_fatal_error = count_fatal_error + 1
2958 #if ( ( EM_CORE == 1) && ( defined(DM_PARALLEL) )&& ( ! defined(STUBMPI) ) )
2959 !-----------------------------------------------------------------------
2960 ! Did the user ask for too many MPI tasks, or are those tasks poorly distributed.
2961 !-----------------------------------------------------------------------
2964 DO i = 1, model_config_rec % max_dom
2965 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2966 IF ( ( model_config_rec % e_we(i) / model_config_rec % nproc_x .LT. 10 ) .OR. &
2967 ( model_config_rec % e_sn(i) / model_config_rec % nproc_y .LT. 10 ) ) THEN
2968 WRITE ( wrf_err_message , * ) 'For domain ',i,', the domain size is too small for this many processors, ', &
2969 'or the decomposition aspect ratio is poor.'
2970 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2971 WRITE ( wrf_err_message , * ) 'Minimum decomposed computational patch size, either x-dir or y-dir, is 10 grid cells.'
2972 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2973 WRITE ( wrf_err_message , fmt='(a,i5,a,i4,a,i4)' ) &
2974 'e_we = ', model_config_rec % e_we(i),', nproc_x = ',model_config_rec % nproc_x, &
2975 ', with cell width in x-direction = ', &
2976 model_config_rec % e_we(i) / model_config_rec % nproc_x
2977 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2978 WRITE ( wrf_err_message , fmt='(a,i5,a,i4,a,i4)' ) &
2979 'e_sn = ', model_config_rec % e_sn(i),', nproc_y = ',model_config_rec % nproc_y, &
2980 ', with cell width in y-direction = ', &
2981 model_config_rec % e_sn(i) / model_config_rec % nproc_y
2982 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2983 wrf_err_message = '--- ERROR: Reduce the MPI rank count, or redistribute the tasks.'
2984 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2988 IF ( oops .GT. 0 ) THEN
2989 count_fatal_error = count_fatal_error + 1
2996 !---------------------------------------------------------------------
2997 ! The "clean" atmosphere radiative flux diagnostics can only be used
2999 !---------------------------------------------------------------------
3001 IF ( model_config_rec%clean_atm_diag > 0 ) THEN
3004 wrf_err_message = '--- NOTE: "Clean" atmosphere diagnostics can only be used in WRF-Chem'
3005 CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
3006 model_config_rec%calc_clean_atm_diag = 0
3008 model_config_rec%calc_clean_atm_diag = 1
3013 !-----------------------------------------------------------------------
3014 ! MUST BE AFTER ALL OF THE PHYSICS CHECKS.
3015 !-----------------------------------------------------------------------
3017 IF ( count_fatal_error .GT. 0 ) THEN
3018 WRITE (wrf_err_message, FMT='(A,I6, A)') 'NOTE: ', count_fatal_error, &
3019 ' namelist settings are wrong. Please check and reset these options'
3020 CALL wrf_error_fatal ( wrf_err_message )
3023 END SUBROUTINE check_nml_consistency
3025 !=======================================================================
3027 SUBROUTINE setup_physics_suite
3031 ! Based on the selection of physics suite provided in the namelist, sets the
3032 ! values of other namelist options (mp_physics, cu_physics, ra_lw_physics,
3033 ! ra_sw_physics, bl_pbl_physics, sf_sfclay_physics, and sf_surface_physics)
3034 ! to reflect that suite.
3038 USE module_domain, ONLY : change_to_lower_case
3041 #if ( EM_CORE == 1 )
3045 LOGICAL :: have_mods
3046 INTEGER, DIMENSION( max_domains ) :: orig_mp_physics, orig_cu_physics, orig_ra_lw_physics, orig_ra_sw_physics, &
3047 orig_bl_pbl_physics, orig_sf_sfclay_physics, orig_sf_surface_physics
3048 CHARACTER, DIMENSION( max_domains ) :: modified_mp_option, modified_cu_option, modified_ra_lw_option, modified_ra_sw_option, &
3049 modified_bl_pbl_option, modified_sf_sfclay_option, modified_sf_surface_option
3050 CHARACTER (LEN=256) :: physics_suite_lowercase
3051 CHARACTER (LEN=32) :: formatstring
3054 ! Initialize the debug level so that it can be used in the namelist testing.
3055 ! wrf_debug_level is a global value in module_wrf_error.
3058 wrf_debug_level = model_config_rec%debug_level
3060 max_dom = model_config_rec % max_dom
3063 ! Save physics selections as given by the user to later determine if the
3064 ! user has overridden any options
3066 modified_mp_option(1:max_dom) = ' '
3067 orig_mp_physics(1:max_dom) = model_config_rec % mp_physics(1:max_dom)
3069 modified_cu_option(1:max_dom) = ' '
3070 orig_cu_physics(1:max_dom) = model_config_rec % cu_physics(1:max_dom)
3072 modified_ra_lw_option(1:max_dom) = ' '
3073 orig_ra_lw_physics(1:max_dom) = model_config_rec % ra_lw_physics(1:max_dom)
3075 modified_ra_sw_option(1:max_dom) = ' '
3076 orig_ra_sw_physics(1:max_dom) = model_config_rec % ra_sw_physics(1:max_dom)
3078 modified_bl_pbl_option(1:max_dom) = ' '
3079 orig_bl_pbl_physics(1:max_dom) = model_config_rec % bl_pbl_physics(1:max_dom)
3081 modified_sf_sfclay_option(1:max_dom) = ' '
3082 orig_sf_sfclay_physics(1:max_dom) = model_config_rec % sf_sfclay_physics(1:max_dom)
3084 modified_sf_surface_option(1:max_dom) = ' '
3085 orig_sf_surface_physics(1:max_dom) = model_config_rec % sf_surface_physics(1:max_dom)
3087 CALL change_to_lower_case(trim(model_config_rec % physics_suite), physics_suite_lowercase)
3090 ! If physics suite is 'none', we can return early
3092 IF ( trim(physics_suite_lowercase) == 'none' ) THEN
3093 wrf_err_message = '*************************************'
3094 call wrf_debug ( 1, wrf_err_message )
3095 wrf_err_message = 'No physics suite selected.'
3096 call wrf_debug ( 1, wrf_err_message )
3097 wrf_err_message = 'Physics options will be used directly from the namelist.'
3098 call wrf_debug ( 1, wrf_err_message )
3099 wrf_err_message = '*************************************'
3100 call wrf_debug ( 1, wrf_err_message )
3104 CALL wrf_message ('*************************************')
3105 CALL wrf_message ('Configuring physics suite '''//trim(physics_suite_lowercase)//'''')
3106 CALL wrf_message ('')
3109 ! Set options based on the suite selection
3111 SELECT CASE ( trim(physics_suite_lowercase) )
3119 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3120 IF ( model_config_rec % cu_physics(i) == -1 ) model_config_rec % cu_physics(i) = TIEDTKESCHEME ! Tiedtke
3121 IF ( model_config_rec % mp_physics(i) == -1 ) model_config_rec % mp_physics(i) = THOMPSON ! Thompson
3122 IF ( model_config_rec % ra_lw_physics(i) == -1 ) model_config_rec % ra_lw_physics(i) = RRTMG_LWSCHEME ! RRTMG LW
3123 IF ( model_config_rec % ra_sw_physics(i) == -1 ) model_config_rec % ra_sw_physics(i) = RRTMG_SWSCHEME ! RRTMG SW
3124 IF ( model_config_rec % bl_pbl_physics(i) == -1 ) model_config_rec % bl_pbl_physics(i) = MYJPBLSCHEME ! MYJ
3125 IF ( model_config_rec % sf_sfclay_physics(i) == -1 ) model_config_rec % sf_sfclay_physics(i) = MYJSFCSCHEME ! MYJ
3126 IF ( model_config_rec % sf_surface_physics(i) == -1 ) model_config_rec % sf_surface_physics(i) = LSMSCHEME ! Noah
3136 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3137 IF ( model_config_rec % cu_physics(i) == -1 ) model_config_rec % cu_physics(i) = NTIEDTKESCHEME ! New Tiedtke
3138 IF ( model_config_rec % mp_physics(i) == -1 ) model_config_rec % mp_physics(i) = WSM6SCHEME ! WSM6
3139 IF ( model_config_rec % ra_lw_physics(i) == -1 ) model_config_rec % ra_lw_physics(i) = RRTMG_LWSCHEME ! RRTMG LW
3140 IF ( model_config_rec % ra_sw_physics(i) == -1 ) model_config_rec % ra_sw_physics(i) = RRTMG_SWSCHEME ! RRTMG SW
3141 IF ( model_config_rec % bl_pbl_physics(i) == -1 ) model_config_rec % bl_pbl_physics(i) = YSUSCHEME ! YSU
3142 IF ( model_config_rec % sf_sfclay_physics(i) == -1 ) model_config_rec % sf_sfclay_physics(i) = SFCLAYSCHEME ! MM5
3143 IF ( model_config_rec % sf_surface_physics(i) == -1 ) model_config_rec % sf_surface_physics(i) = LSMSCHEME ! Noah
3148 CALL wrf_error_fatal ( 'Unrecognized physics suite' )
3152 WRITE (formatstring, '(A,I3,A)') '(A21,', max_dom, '(I6,A1))'
3155 ! Print microphysics options
3157 WHERE (model_config_rec % mp_physics(1:max_dom) == orig_mp_physics(1:max_dom)) modified_mp_option(1:max_dom) = '*'
3158 WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'mp_physics: ', &
3159 (model_config_rec % mp_physics(i), modified_mp_option(i), i=1,max_dom)
3160 CALL wrf_message (wrf_err_message)
3163 ! Print cumulus options
3165 WHERE (model_config_rec % cu_physics(1:max_dom) == orig_cu_physics(1:max_dom)) modified_cu_option(1:max_dom) = '*'
3166 WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'cu_physics: ', &
3167 (model_config_rec % cu_physics(i), modified_cu_option(i), i=1,max_dom)
3168 CALL wrf_message (wrf_err_message)
3171 ! Print LW radiation options
3173 WHERE (model_config_rec % ra_lw_physics(1:max_dom) == orig_ra_lw_physics(1:max_dom)) modified_ra_lw_option(1:max_dom) = '*'
3174 WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'ra_lw_physics: ', &
3175 (model_config_rec % ra_lw_physics(i), modified_ra_lw_option(i), i=1,max_dom)
3176 CALL wrf_message (wrf_err_message)
3179 ! Print SW radiation options
3181 WHERE (model_config_rec % ra_sw_physics(1:max_dom) == orig_ra_sw_physics(1:max_dom)) modified_ra_sw_option(1:max_dom) = '*'
3182 WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'ra_sw_physics: ', &
3183 (model_config_rec % ra_sw_physics(i), modified_ra_sw_option(i), i=1,max_dom)
3184 CALL wrf_message (wrf_err_message)
3187 ! Print boundary layer options
3189 WHERE (model_config_rec % bl_pbl_physics(1:max_dom) == orig_bl_pbl_physics(1:max_dom)) modified_bl_pbl_option(1:max_dom) = '*'
3190 WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'bl_pbl_physics: ', &
3191 (model_config_rec % bl_pbl_physics(i), modified_bl_pbl_option(i), i=1,max_dom)
3192 CALL wrf_message (wrf_err_message)
3195 ! Print surface layer options
3197 WHERE (model_config_rec % sf_sfclay_physics(1:max_dom) == orig_sf_sfclay_physics(1:max_dom)) &
3198 modified_sf_sfclay_option(1:max_dom) = '*'
3199 WRITE (wrf_err_message, FMT=TRIM(formatstring)) &
3200 'sf_sfclay_physics: ', (model_config_rec % sf_sfclay_physics(i), modified_sf_sfclay_option(i), i=1,max_dom)
3201 CALL wrf_message (wrf_err_message)
3204 ! Print surface options
3206 WHERE (model_config_rec % sf_surface_physics(1:max_dom) == orig_sf_surface_physics(1:max_dom)) &
3207 modified_sf_surface_option(1:max_dom) = '*'
3208 WRITE (wrf_err_message, FMT=TRIM(formatstring)) &
3209 'sf_surface_physics: ', (model_config_rec % sf_surface_physics(i), modified_sf_surface_option(i), i=1,max_dom)
3210 CALL wrf_message (wrf_err_message)
3213 ! Print footnote if any physics schemes were overridden by the user
3215 have_mods = ANY (modified_mp_option(1:max_dom) == '*') &
3216 .OR. ANY (modified_cu_option(1:max_dom) == '*') &
3217 .OR. ANY (modified_ra_lw_option(1:max_dom) == '*') &
3218 .OR. ANY (modified_ra_sw_option(1:max_dom) == '*') &
3219 .OR. ANY (modified_bl_pbl_option(1:max_dom) == '*') &
3220 .OR. ANY (modified_sf_sfclay_option(1:max_dom) == '*') &
3221 .OR. ANY (modified_sf_surface_option(1:max_dom) == '*')
3224 CALL wrf_message ('')
3225 CALL wrf_message ('(* = option overrides suite setting)')
3228 CALL wrf_message ('*************************************')
3232 END SUBROUTINE setup_physics_suite
3234 !=======================================================================
3236 SUBROUTINE set_physics_rconfigs
3240 ! Some derived rconfig entries need to be set based on the value of other,
3241 ! non-derived entries before package-dependent memory allocation takes place.
3242 ! This works around depending on the user to set these specific settings in the
3249 INTEGER :: numsoiltemp , nummosaictemp
3253 !-----------------------------------------------------------------------
3254 ! Set the namelist urban dimensions if sf_urban_physics > 0
3255 !-----------------------------------------------------------------------
3257 IF ( any(model_config_rec%sf_urban_physics > 0 ) ) THEN
3259 model_config_rec%urban_map_zrd = model_config_rec%num_urban_ndm * &
3260 model_config_rec%num_urban_nwr * &
3261 model_config_rec%num_urban_nz
3262 model_config_rec%urban_map_zwd = model_config_rec%num_urban_ndm * &
3263 model_config_rec%num_urban_nwr * &
3264 model_config_rec%num_urban_nz * &
3265 model_config_rec%num_urban_nbui
3266 model_config_rec%urban_map_gd = model_config_rec%num_urban_ndm * &
3267 model_config_rec%num_urban_ng
3268 model_config_rec%urban_map_zd = model_config_rec%num_urban_ndm * &
3269 model_config_rec%num_urban_nz * &
3270 model_config_rec%num_urban_nbui
3271 model_config_rec%urban_map_zdf = model_config_rec%num_urban_ndm * &
3272 model_config_rec%num_urban_nz
3273 model_config_rec%urban_map_bd = model_config_rec%num_urban_nz * &
3274 model_config_rec%num_urban_nbui
3275 model_config_rec%urban_map_wd = model_config_rec%num_urban_ndm * &
3276 model_config_rec%num_urban_nz * &
3277 model_config_rec%num_urban_nbui
3278 model_config_rec%urban_map_gbd = model_config_rec%num_urban_ndm * &
3279 model_config_rec%num_urban_ngb * &
3280 model_config_rec%num_urban_nbui
3281 model_config_rec%urban_map_fbd = model_config_rec%num_urban_ndm * &
3282 (model_config_rec%num_urban_nz - 1) * &
3283 model_config_rec%num_urban_nf * &
3284 model_config_rec%num_urban_nbui
3285 model_config_rec%urban_map_zgrd = model_config_rec%num_urban_ndm * &
3286 model_config_rec%num_urban_ngr * &
3287 model_config_rec%num_urban_nz
3291 !-----------------------------------------------------------------------
3292 ! Set the namelist mosaic_cat_soil parameter for the Noah-mosaic scheme if sf_surface_mosaic == 1.
3293 !-----------------------------------------------------------------------
3295 IF ( model_config_rec % sf_surface_mosaic .EQ. 1 ) THEN
3297 numsoiltemp = model_config_rec % num_soil_layers
3298 nummosaictemp = model_config_rec % mosaic_cat
3300 model_config_rec % mosaic_cat_soil = numsoiltemp * nummosaictemp
3302 wrf_err_message = '--- NOTE: Noah-mosaic is in use, setting: ' // &
3303 'mosaic_cat_soil = mosaic_cat * num_soil_layers'
3304 CALL wrf_debug ( 1, wrf_err_message )
3309 !-----------------------------------------------------------------------
3310 ! How big to allocate random seed arrays.
3311 !-----------------------------------------------------------------------
3313 CALL RANDOM_SEED ( SIZE = model_config_rec % seed_dim )
3315 !-----------------------------------------------------------------------
3316 ! If this is a WRF run with polar boundary conditions, then this is a
3317 ! global domain. A global domain needs to have the FFT arrays allocated.
3318 !-----------------------------------------------------------------------
3320 model_config_rec % fft_used = 0
3321 IF ( ( model_config_rec % polar(1) ) .AND. &
3322 ( model_config_rec % fft_filter_lat .LT. 90. ) ) THEN
3323 model_config_rec % fft_used = 1
3326 !-----------------------------------------------------------------------
3327 ! Need to know if this run has aercu_opt set to either 1 or 2,
3328 ! so that we can set a derived namelist for packaging arrays.
3329 !-----------------------------------------------------------------------
3331 model_config_rec % aercu_used = 0
3332 IF ( model_config_rec %aercu_opt .GT. 0 ) THEN
3333 model_config_rec % aercu_used = 1
3336 !-----------------------------------------------------------------------
3337 ! If any CAM scheme is turned on, then there are a few shared variables.
3338 ! These need to be allocated when any CAM scheme is active.
3339 !-----------------------------------------------------------------------
3341 #if ( (EM_CORE == 1) && (WRF_CHEM != 1) )
3342 model_config_rec % cam_used = 0
3343 DO i = 1, model_config_rec % max_dom
3344 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3345 IF ( ( model_config_rec % mp_physics(i) .EQ. CAMMGMPSCHEME ) .OR. &
3346 ( model_config_rec % bl_pbl_physics(i) .EQ. CAMUWPBLSCHEME ) .OR. &
3347 ( model_config_rec % shcu_physics(i) .EQ. CAMUWSHCUSCHEME ) ) THEN
3348 model_config_rec % cam_used = 1
3352 #elif (WRF_CHEM == 1)
3353 model_config_rec % cam_used = 1
3359 !-----------------------------------------------------------------------
3360 ! Set the namelist parameters for the CAM radiation scheme if either
3361 ! ra_lw_physics = CAMLWSCHEME or ra_sw_physics = CAMSWSCHEME.
3362 !-----------------------------------------------------------------------
3364 IF (( model_config_rec % ra_lw_physics(1) .EQ. CAMLWSCHEME ) .OR. &
3365 ( model_config_rec % ra_sw_physics(1) .EQ. CAMSWSCHEME )) THEN
3366 model_config_rec % paerlev = 29
3367 model_config_rec % levsiz = 59
3368 model_config_rec % cam_abs_dim1 = 4
3369 model_config_rec % cam_abs_dim2 = model_config_rec % e_vert(1)
3371 wrf_err_message = '--- NOTE: CAM radiation is in use, setting: ' // &
3372 'paerlev=29, levsiz=59, cam_abs_dim1=4, cam_abs_dim2=e_vert'
3373 CALL wrf_debug ( 1, wrf_err_message )
3377 !-----------------------------------------------------------------------
3378 ! Check for deprecated options with NSSL-MP
3379 !-----------------------------------------------------------------------
3380 DO i = 1, model_config_rec % max_dom
3381 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3382 IF ( model_config_rec % mp_physics(i) .EQ. 22 ) THEN
3383 model_config_rec % mp_physics(i) = NSSL_2MOM
3384 model_config_rec % nssl_2moment_on = 1
3385 model_config_rec % nssl_hail_on(i) = 0
3386 model_config_rec % nssl_ccn_on = 0
3387 model_config_rec % nssl_density_on = 1 ! set graupel density
3388 WRITE (wrf_err_message, FMT='(A)') ' **CAUTION** mp_physics = 22 has been deprecated. '// &
3389 'Instead you can use mp_physics=18, nssl_hail_on=0, nssl_ccn_on=0'
3390 CALL wrf_debug ( 0, wrf_err_message )
3391 ELSEIF ( model_config_rec % mp_physics(i) .EQ. 17 ) THEN
3392 model_config_rec % mp_physics(i) = NSSL_2MOM
3393 model_config_rec % nssl_2moment_on = 1
3394 model_config_rec % nssl_hail_on(i) = 1
3395 model_config_rec % nssl_ccn_on = 0
3396 model_config_rec % nssl_density_on = 2 ! set graupel+hail density
3397 WRITE (wrf_err_message, FMT='(A)') ' **CAUTION** mp_physics = 17 has been deprecated. '// &
3398 'Instead you can use mp_physics=18, nssl_ccn_on=0'
3399 ! print statement for deprecated option
3400 CALL wrf_debug ( 0, wrf_err_message )
3401 ELSEIF ( model_config_rec % mp_physics(i) .EQ. 19 ) THEN
3402 ! single-moment with hail + graupel density
3403 model_config_rec % mp_physics(i) = NSSL_2MOM
3404 model_config_rec % nssl_2moment_on = 0
3405 model_config_rec % nssl_hail_on(i) = 2
3406 model_config_rec % nssl_density_on = 1 ! set graupel density
3407 ! print statement for deprecated option
3408 WRITE (wrf_err_message, FMT='(A)') ' **CAUTION** mp_physics = 19 has been deprecated. '// &
3409 'Instead you can use mp_physics=18, nssl_2moment_on=0, nssl_ccn_on=0'
3410 CALL wrf_debug ( 0, wrf_err_message )
3411 ELSEIF ( model_config_rec % mp_physics(i) .EQ. 21 ) THEN
3412 ! single-moment without
3413 model_config_rec % mp_physics(i) = NSSL_2MOM
3414 model_config_rec % nssl_2moment_on = 0
3415 model_config_rec % nssl_hail_on(i) = 0
3416 model_config_rec % nssl_density_on = 0 ! set graupel density
3417 ! print statement for deprecated option
3418 WRITE (wrf_err_message, FMT='(A)') ' **CAUTION** mp_physics = 21 has been deprecated. '// &
3419 'Instead you can use mp_physics=18, nssl_2moment_on=0, nssl_ccn_on=0, nssl_hail_on=0'
3420 CALL wrf_debug ( 0, wrf_err_message )
3423 IF ( model_config_rec % mp_physics(i) /= NSSL_2MOM ) THEN
3424 ! If not NSSL-MP, make sure extra fields are turned off (in case of stray namelist settings)
3425 model_config_rec % nssl_2moment_on = 0
3426 model_config_rec % nssl_hail_on(i) = 0
3427 model_config_rec % nssl_density_on = 0 ! set graupel density
3428 model_config_rec % nssl_3moment = 0
3429 model_config_rec % nssl_ccn_on = 0
3431 ELSE ! make sure settings are consistent
3433 IF ( model_config_rec % nssl_ccn_on < 0 ) THEN
3434 model_config_rec % nssl_ccn_on = 1
3437 IF ( model_config_rec % nssl_2moment_on < 0 ) THEN ! turn on number concentrations
3438 model_config_rec % nssl_2moment_on = 1
3441 IF ( model_config_rec % nssl_hail_on(i) < 0 ) THEN
3442 IF ( model_config_rec % nssl_2moment_on == 0 ) THEN
3443 model_config_rec % nssl_hail_on(i) = 2
3445 model_config_rec % nssl_hail_on(i) = 1
3449 IF ( model_config_rec % nssl_density_on < 0 ) THEN
3450 IF ( model_config_rec % nssl_hail_on(i) == 1 ) THEN
3451 model_config_rec % nssl_density_on = 2 ! set default of graupel+hail density
3453 model_config_rec % nssl_density_on = 1 ! set graupel density (hail off)
3457 IF ( model_config_rec % nssl_3moment == 1 ) THEN
3458 model_config_rec % nssl_2moment_on = 1
3459 IF ( model_config_rec % nssl_hail_on(i) == 1 ) THEN
3460 model_config_rec % nssl_3moment = 2 ! 3mom rain, graupel and hail
3462 model_config_rec % nssl_3moment = 1 ! 3mom rain and graupel (no hail)
3469 !-----------------------------------------------------------------------
3470 ! If a user requested to compute the radar reflectivity .OR. if this is
3471 ! one of the schemes that ALWAYS computes the radar reflectivity, then
3472 ! turn on the switch that says allocate the space for the refl_10cm array.
3473 !-----------------------------------------------------------------------
3475 DO i = 1, model_config_rec % max_dom
3476 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3477 IF ( ( model_config_rec % mp_physics(i) .EQ. MILBRANDT2MOM ) .OR. &
3478 ( model_config_rec % mp_physics(i) .EQ. NSSL_2MOM ) .OR. &
3479 ( model_config_rec % do_radar_ref .EQ. 1 ) ) THEN
3480 model_config_rec % compute_radar_ref = 1
3485 !-----------------------------------------------------------------------
3486 ! If a user selected LOGICAL fire-related switches, convert those to
3487 ! INTEGER for the package allocation assignment required in the
3489 !-----------------------------------------------------------------------
3492 DO i = 1, model_config_rec % max_dom
3493 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3494 IF ( model_config_rec % fmoist_run(i) .EQV. .TRUE. ) THEN
3495 model_config_rec % fmoisti_run(i) = 1
3497 model_config_rec % fmoisti_run(i) = 0
3499 IF ( model_config_rec % fmoist_interp(i) .EQV. .TRUE. ) THEN
3500 model_config_rec % fmoisti_interp(i) = 1
3502 model_config_rec % fmoisti_interp(i) = 0
3507 !-----------------------------------------------------------------------
3508 ! If MYNN PBL is not used, set bl_mynn_edmf = 0 so that we don't get
3510 !-----------------------------------------------------------------------
3513 DO i = 1, model_config_rec % max_dom
3514 IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3515 IF ( ( model_config_rec % bl_pbl_physics(i) .NE. MYNNPBLSCHEME ) ) THEN
3516 model_config_rec % bl_mynn_edmf = 0
3521 !-----------------------------------------------------------------------
3522 ! Set the namelist parameters for the RRTMG radiation scheme if either
3523 ! ra_lw_physics or ra_sw_physics is set to one of the RRTMG schemes.
3524 !-----------------------------------------------------------------------
3526 IF (( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME ) .OR. &
3527 ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME ) .OR. &
3528 ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_LWSCHEME ) .OR. &
3529 ( model_config_rec % ra_sw_physics(1) .EQ. RRTMK_SWSCHEME ) .OR. &
3530 ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME_FAST ) .OR. &
3531 ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME_FAST )) THEN
3532 model_config_rec % levsiz = 59
3533 model_config_rec % alevsiz = 12
3534 model_config_rec % no_src_types = 6
3536 wrf_err_message = '--- NOTE: One of the RRTMG radiation schemes is in use, setting: ' // &
3537 'levsiz=59, alevsiz=12, no_src_types=6'
3538 CALL wrf_debug ( 1, wrf_err_message )
3542 !-----------------------------------------------------------------------
3543 ! Set namelist parameter num_soil_levels depending on the value of
3544 ! sf_surface_physics
3545 !-----------------------------------------------------------------------
3548 IF ( model_config_rec % sf_surface_physics(1) .EQ. NOLSMSCHEME ) THEN
3549 model_config_rec % num_soil_layers = 5
3550 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. SLABSCHEME ) THEN
3551 model_config_rec % num_soil_layers = 5
3552 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. LSMSCHEME ) THEN
3553 model_config_rec % num_soil_layers = 4
3554 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. NOAHMPSCHEME ) THEN
3555 model_config_rec % num_soil_layers = 4
3556 ELSE IF ( ( model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME ) .AND. &
3557 ( model_config_rec % num_soil_layers .EQ. 6 ) ) THEN
3558 model_config_rec % num_soil_layers = 6
3559 ELSE IF ( ( model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME ) .AND. &
3560 ( model_config_rec % num_soil_layers .EQ. 9 ) ) THEN
3561 model_config_rec % num_soil_layers = 9
3562 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME ) THEN
3563 model_config_rec % num_soil_layers = 6
3564 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. PXLSMSCHEME ) THEN
3565 model_config_rec % num_soil_layers = 2
3566 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. CLMSCHEME ) THEN
3567 model_config_rec % num_soil_layers = 10
3568 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. CTSMSCHEME ) THEN
3569 ! Using 4 for the sake of the sea ice scheme
3570 model_config_rec % num_soil_layers = 4
3571 ELSE IF ( model_config_rec % sf_surface_physics(1) .EQ. SSIBSCHEME ) THEN
3572 model_config_rec % num_soil_layers = 3
3574 CALL wrf_debug ( 0 , '--- ERROR: Unknown sf_surface_physics has no associated number of soil levels' )
3575 WRITE (wrf_err_message, FMT='(A,I6)') '--- ERROR: sf_surface_physics = ' , model_config_rec % sf_surface_physics(1)
3576 CALL wrf_error_fatal ( TRIM(wrf_err_message) )
3580 WRITE (wrf_err_message, FMT='(A,I6)') '--- NOTE: num_soil_layers has been set to ', &
3581 model_config_rec % num_soil_layers
3582 CALL wrf_debug ( 1, wrf_err_message )
3584 END SUBROUTINE set_physics_rconfigs
3586 !=======================================================================
3588 RECURSIVE SUBROUTINE get_moad_factor ( id, parent_id, parent_grid_ratio, max_dom, factor )
3591 INTEGER, DIMENSION(max_dom) :: parent_id, parent_grid_ratio
3592 INTEGER :: factor, id
3594 IF ( id .EQ. 1 ) THEN
3597 factor = factor * parent_grid_ratio(id)
3598 CALL get_moad_factor ( parent_id(id), parent_id, parent_grid_ratio, max_dom, factor )
3600 END SUBROUTINE get_moad_factor
3602 !=======================================================================
3604 END MODULE module_check_a_mundo
3606 !=======================================================================