updated top-level README and version_decl for V4.4.2 (#1795)
[WRF.git] / share / module_check_a_mundo.F
blob4aec76604f7508431068bd547d8bf74cf8732220
1 !=======================================================================
3    MODULE module_check_a_mundo
5 !<DESCRIPTION>
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.
28 !</DESCRIPTION>
30       USE module_state_description
31       USE module_model_constants
32       USE module_wrf_error
33       USE module_configure
35       IMPLICIT NONE
37 !=======================================================================
39    CONTAINS
41 !=======================================================================
43    SUBROUTINE check_nml_consistency
45 !<DESCRIPTION>
47 ! Check consistency of namelist settings
49 !</DESCRIPTION>
51       USE module_bep_bem_helper, ONLY: nurbm
53       IMPLICIT NONE
55       LOGICAL :: exists, vnest
56       LOGICAL , EXTERNAL :: wrf_dm_on_monitor
57       INTEGER :: i, j, oops, d1_value, EDMFMAX, SCHUMAX
58       INTEGER :: id, factor
59       LOGICAL :: km_opt_already_done , diff_opt_already_done
60       INTEGER :: count_opt
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.
71       INTERFACE
72          INTEGER FUNCTION bep_nurbm()
73          END FUNCTION bep_nurbm
75          INTEGER FUNCTION bep_ndm()
76          END FUNCTION bep_ndm
78          INTEGER FUNCTION bep_nz_um()
79          END FUNCTION bep_nz_um
81          INTEGER FUNCTION bep_ng_u()
82          END 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
110          
111          INTEGER FUNCTION bep_bem_ngr_u()
112          END FUNCTION bep_bem_ngr_u
114       END INTERFACE
116 !-----------------------------------------------------------------------
117 ! Set up the WRF Hydro namelist option to allow dynamic allocation of
118 ! variables.
119 !-----------------------------------------------------------------------
120    count_fatal_error = 0
121 #ifdef WRF_HYDRO
122    model_config_rec % wrf_hydro = 1
123 #else
124    model_config_rec % wrf_hydro = 0
125 #endif
127 #if (EM_CORE == 1)
128 !-----------------------------------------------------------------------
129 ! AFWA diagnostics require each domain is treated the same. If
130 ! any domain has an option activated, all domains must have that
131 ! option activated.
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
136       exit
137     endif
138   enddo
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
142       exit
143     endif
144   enddo
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
148       exit
149     endif
150   enddo
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
154       exit
155     endif
156   enddo
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
160       exit
161     endif
162   enddo
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
166       exit
167     endif
168   enddo
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
172       exit
173     endif
174   enddo
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
178       exit
179     endif
180   enddo
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
184       exit
185     endif
186   enddo
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
190       exit
191     endif
192   enddo
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
196       exit
197     endif
198   enddo
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
216     endif
217   enddo
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.
225    END DO 
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.
243    END DO 
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
251    END IF
252 #endif
254 #if (EM_CORE == 1)
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 )
267             CYCLE
268          END IF
269          id = i
270          factor = 1
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 )
278       END DO
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 )
299             END IF
300             km_opt_already_done = .TRUE.
301          END IF
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 )
309             END IF
310             diff_opt_already_done = .TRUE.
311          END IF
312       ENDDO
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
325       END IF
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
337       END IF
338       ENDDO
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
352          END IF
353       ENDDO
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
367          END IF
368       ENDDO
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
381          END IF
382       ENDDO
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
402          END IF
403       ENDDO
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 
412 ! purposes).
413 !-----------------------------------------------------------------------
414       exists = .FALSE.
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
418             exists = .TRUE.
419          END IF
420       END DO
421       IF ( ( exists ) .AND. &
422            ( ( model_config_rec % bl_pbl_physics(1) .EQ. MYNNPBLSCHEME2 ) .OR. &
423              ( model_config_rec % bl_pbl_physics(1) .EQ. MYNNPBLSCHEME3 ) .OR. &
424              ( model_config_rec % bl_pbl_physics(1) .EQ. EEPSSCHEME     ) ) ) THEN
425          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)
426          CALL wrf_message ( TRIM( wrf_err_message ) )
427          wrf_err_message = '           Fix bl_pbl_physics in namelist.input: choose a CG PBL option without any scalar components'
428          CALL wrf_message ( TRIM( wrf_err_message ) )
429          wrf_err_message = '           Alternatively, remove all of the packaged variables from the CG PBL selection'
430          CALL wrf_message ( TRIM( wrf_err_message ) )
431          count_fatal_error = count_fatal_error + 1
432       END IF 
435 !-----------------------------------------------------------------------
436 ! Check that if the user has requested to use the shallow water surface
437 ! roughness drag option, then the only surface layer scheme permitted 
438 ! to be used is the revised MM5 MO option.
439 !-----------------------------------------------------------------------
440       DO i = 1, model_config_rec % max_dom
441          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
442          IF ( ( model_config_rec % shalwater_z0(i)   .NE. 0               ) .AND. &
443               ( model_config_rec % sf_sfclay_physics(i) .NE. sfclayrevscheme ) ) THEN
444             wrf_err_message = '--- ERROR: Shallow water surface roughness only works with sfclay_physics = 1'
445             CALL wrf_message ( TRIM( wrf_err_message ) )
446             wrf_err_message = '           Fix shalwater_z0 or sf_sfclay_physics in namelist.input.'
447             CALL wrf_message ( TRIM( wrf_err_message ) )
448             count_fatal_error = count_fatal_error + 1
449          END IF
450       ENDDO
452 !-----------------------------------------------------------------------
453 ! Urban physics set up. If the run-time option for use_wudapt_lcz = 0,
454 ! then the number of urban classes is 3. Else, if the use_wudapt_lcz = 1, 
455 ! then the number increases to 11. The seemingly local variable 
456 ! assignment, "nurbm", is actually USE associated from the BEP BEM 
457 ! helper module.
458 !-----------------------------------------------------------------------
459       IF      ( model_config_rec%use_wudapt_lcz .EQ. 0 ) THEN
460          nurbm = 3
461       ELSE IF ( model_config_rec%use_wudapt_lcz .EQ. 1 ) THEN
462          nurbm = 11
463       END IF
465 !-----------------------------------------------------------------------
466 ! Assign the dimensions for the urban options to the values defined in 
467 ! each of those respective modules.
468 !-----------------------------------------------------------------------
469       DO i = 1, model_config_rec % max_dom
470          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
471          IF ( model_config_rec % sf_urban_physics(i) == bepscheme     ) THEN
472            model_config_rec % num_urban_ndm  = bep_ndm()
473            model_config_rec % num_urban_nz   = bep_nz_um()
474            model_config_rec % num_urban_ng   = bep_ng_u()
475            model_config_rec % num_urban_nwr  = bep_nwr_u()
476          END IF
477          IF ( model_config_rec % sf_urban_physics(i) == bep_bemscheme ) THEN 
478            model_config_rec % num_urban_ndm  = bep_bem_ndm()
479            model_config_rec % num_urban_nz   = bep_bem_nz_um()
480            model_config_rec % num_urban_ng   = bep_bem_ng_u()
481            model_config_rec % num_urban_nwr  = bep_bem_nwr_u()
482            model_config_rec % num_urban_nf   = bep_bem_nf_u()
483            model_config_rec % num_urban_ngb  = bep_bem_ngb_u()
484            model_config_rec % num_urban_nbui = bep_bem_nbui_max()
485            model_config_rec % num_urban_ngr  = bep_bem_ngr_u()
487          END IF
488       ENDDO
490 !-----------------------------------------------------------------------
491 ! Check that mosiac option cannot turn on when sf_urban_physics = 2 and 3
492 !-----------------------------------------------------------------------
493       DO i = 1, model_config_rec % max_dom
494          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
495          IF ( model_config_rec % sf_surface_mosaic .EQ. 1 .AND. &
496               (model_config_rec % sf_urban_physics(i) .EQ. 2 .OR. &
497                model_config_rec % sf_urban_physics(i) .EQ. 3 ) ) THEN
498             wrf_err_message = '--- ERROR: mosaic option cannot work with urban options 2 and 3 '
499             CALL wrf_message ( wrf_err_message )
500             wrf_err_message = '--- ERROR: Fix sf_surface_mosaic and sf_urban_physics in namelist.input.'
501             CALL wrf_message ( wrf_err_message )
502             wrf_err_message = '--- ERROR: Either: use Noah LSM without the mosaic option, OR change the urban option to 1 '
503          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
504          count_fatal_error = count_fatal_error + 1
505          END IF
506       ENDDO
508 !-----------------------------------------------------------------------
509 ! Check that channel irrigation is run with Noah
510 !-----------------------------------------------------------------------
511       DO i = 1, model_config_rec % max_dom
512          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
513          IF ( model_config_rec % sf_surface_physics(i) .NE. LSMSCHEME .AND.  &
514              model_config_rec % sf_surf_irr_scheme(i) .EQ. CHANNEL ) THEN
515               wrf_err_message = '--- ERROR: irrigation Opt 1 works only with Noah-LSM'
516               CALL wrf_message ( wrf_err_message )
517          count_fatal_error = count_fatal_error + 1
518          END IF
519       ENDDO
521 !-----------------------------------------------------------------------
522 ! Check that number of hours of daily irrigation is greater than zero.
523 ! This value is used in the denominator to compute the amount of 
524 ! irrigated water per timestep, and the default value from the Registry
525 ! is zero. This is a reminder to the user that this value needs to be
526 ! manually set.
527 !-----------------------------------------------------------------------
528       oops = 0
529       DO i = 1, model_config_rec % max_dom
530          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
531          IF ( ( ( model_config_rec % sf_surf_irr_scheme(i) .EQ. CHANNEL   )   .OR. &
532                 ( model_config_rec % sf_surf_irr_scheme(i) .EQ. SPRINKLER )   .OR. &
533                 ( model_config_rec % sf_surf_irr_scheme(i) .EQ. DRIP      ) ) .AND. &
534               ( model_config_rec % irr_num_hours(i) .LE. 0 ) ) THEN
535             oops = oops + 1
536          END IF
537       ENDDO
538       
539       IF ( oops .GT. 0 ) THEN
540          wrf_err_message = '--- ERROR: irr_num_hours must be greater than zero to work with irrigation'
541          CALL wrf_message ( wrf_err_message )
542          count_fatal_error = count_fatal_error + 1
543       END IF
545 !-----------------------------------------------------------------------
546 ! Fix derived setting for irrigation. Since users may only want the irrigation
547 ! to be active in the inner-most domain, we have a separate variable that is
548 ! used to define packaging for the irrigation fields.
549 !-----------------------------------------------------------------------
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   ) THEN
553             model_config_rec % sf_surf_irr_alloc = CHANNEL
554          END IF
555          IF ( model_config_rec % sf_surf_irr_scheme(i) .EQ. SPRINKLER ) THEN
556             model_config_rec % sf_surf_irr_alloc = SPRINKLER
557          END IF
558          IF ( model_config_rec % sf_surf_irr_scheme(i) .EQ. DRIP      ) THEN
559             model_config_rec % sf_surf_irr_alloc = DRIP    
560          END IF
561       ENDDO
563 !-----------------------------------------------------------------------
564 ! Check that Deng Shallow Convection Must work with MYJ or MYNN PBL
565 !-----------------------------------------------------------------------
566       DO i = 1, model_config_rec % max_dom
567          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
568          IF ( model_config_rec % shcu_physics(i) == dengshcuscheme .AND. &
569               (model_config_rec % bl_pbl_physics(i) /= myjpblscheme .AND. &
570                model_config_rec % bl_pbl_physics(i) /= mynnpblscheme2 ) ) THEN
571             wrf_err_message = '--- ERROR: Deng shallow convection can only work with MYJ or MYNN (with bl_mynn_edmf off) PBL '
572             CALL wrf_message ( wrf_err_message )
573             wrf_err_message = '--- ERROR: Fix shcu_physics or bl_pbl_physics in namelist.input.'
574             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
575             count_fatal_error = count_fatal_error + 1
576          END IF
577       ENDDO
579 !-----------------------------------------------------------------------
580 ! If Deng Shallow Convection is on, icloud cannot be 3
581 !-----------------------------------------------------------------------
582       oops = 0
583       DO i = 1, model_config_rec % max_dom
584          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
585          IF ( ( model_config_rec%shcu_physics(i) .EQ. dengshcuscheme ) .AND. &
586               ( model_config_rec%icloud .EQ. 3 ) ) THEN
587               oops = oops + 1
588          END IF
589       ENDDO
591       IF ( oops .GT. 0 ) THEN
592          wrf_err_message = '--- ERROR: Options shcu_physics = 5 and icloud = 3 should not be used together'
593          CALL wrf_message ( wrf_err_message )
594          wrf_err_message = '--- ERROR: Choose either one in namelist.input and rerun the model'
595          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
596          count_fatal_error = count_fatal_error + 1
597       END IF
599 !-----------------------------------------------------------------------
600 ! If Deng Shallow Convection is on, icloud_bl cannot be 1
601 !-----------------------------------------------------------------------
602       oops = 0
603       DO i = 1, model_config_rec % max_dom
604          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
605          IF ( ( model_config_rec%shcu_physics(i) .EQ. dengshcuscheme ) .AND. &
606               ( model_config_rec%icloud_bl .EQ. 1 ) ) THEN
607               oops = oops + 1
608          END IF
609       ENDDO
611       IF ( oops .GT. 0 ) THEN
612          wrf_err_message = '--- ERROR: Options shcu_physics = 5 and icloud_bl = 1 should not be used together'
613          CALL wrf_message ( wrf_err_message )
614          wrf_err_message = '--- ERROR: Choose either one in namelist.input and rerun the model'
615          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
616          count_fatal_error = count_fatal_error + 1
617       END IF
619 !-----------------------------------------------------------------------
620 ! If couple_farms is true, swint_opt must be 2
621 !-----------------------------------------------------------------------
622       IF ( model_config_rec%couple_farms .AND. model_config_rec%swint_opt /= 2 ) THEN
623          wrf_err_message = '--- ERROR: Options couple_farms = T requires swint_opt  = 2'
624          CALL wrf_message ( wrf_err_message )
625          wrf_err_message = '--- ERROR: Change either one in namelist.input and rerun the model'
626          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
627          count_fatal_error = count_fatal_error + 1
628       END IF
630 !-----------------------------------------------------------------------
631 ! For ARW users, a request for CU=4 (SAS) should be switched to option
632 ! CU = 95.
633 !-----------------------------------------------------------------------
634       oops = 0
635       DO i = 1, model_config_rec % max_dom
636          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
637          IF ( model_config_rec%cu_physics(i) .EQ. scalesasscheme ) THEN
638               oops = oops + 1
639          END IF
640       ENDDO
642       IF ( oops .GT. 0 ) THEN
643          wrf_err_message = '--- ERROR: Option cu_physics = 4 should not be used for ARW; cu_physics = 95 is suggested'
644          CALL wrf_message ( wrf_err_message )
645          wrf_err_message = '--- ERROR: Choose a different cu_physics option in the namelist.input file'
646          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
647          count_fatal_error = count_fatal_error + 1
648       END IF
650 !-----------------------------------------------------------------------
651 ! There is a binary file for Goddard radiation. It is single precision.
652 !-----------------------------------------------------------------------
653 # if ( defined(PROMOTE_FLOAT) || ( RWORDSIZE == DWORDSIZE ) )
654       god_r8 : DO i = 1, model_config_rec % max_dom
655          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
656          IF ( ( model_config_rec % ra_lw_physics(i) == goddardlwscheme ) .OR. &
657               ( model_config_rec % ra_sw_physics(i) == goddardswscheme ) ) THEN
658             wrf_err_message = '--- ERROR: Goddard radiation scheme cannot run with real*8 floats'
659             CALL wrf_message ( wrf_err_message )
660             wrf_err_message = '--- Fix ra_lw_physics and ra_sw_physics in namelist.input '
661             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
662             count_fatal_error = count_fatal_error + 1
663             EXIT god_r8
664          END IF
665       ENDDO god_r8
667 # endif
669 !-----------------------------------------------------------------------
670 ! With CMAQ coupling, if the option "direct_sw_feedback" is activated,
671 ! then the only SW radiation scheme set up to support this is RRTMG.
672 !-----------------------------------------------------------------------
673 # if ( WRF_CMAQ == 1 ) 
674       cmaq : DO i = 1, model_config_rec % max_dom
675          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
676          IF ( ( model_config_rec % direct_sw_feedback ) .AND. &
677               ( model_config_rec % wrf_cmaq_option .EQ. 1 ) .AND. &
678               ( model_config_rec % ra_sw_physics(i) .NE. rrtmg_swscheme ) ) THEN
679             wrf_err_message = '--- ERROR: With CMAQ coupling, "direct_sw_feedback=T" requires RRTMG SW'
680             CALL wrf_message ( wrf_err_message )
681             count_fatal_error = count_fatal_error + 1
682             EXIT cmaq
683          END IF
684       ENDDO cmaq
685 # else
686       cmaq : DO i = 1, model_config_rec % max_dom
687          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
688          IF ( ( model_config_rec % direct_sw_feedback ) .OR. & 
689               ( model_config_rec % wrf_cmaq_option .EQ. 1 ) ) THEN
690             wrf_err_message = '--- ERROR: The option "direct_sw_feedback=T" and "wrf_cmaq_option==1" require CMAQ coupling'
691             CALL wrf_message ( wrf_err_message )
692             count_fatal_error = count_fatal_error + 1
693             EXIT cmaq
694          END IF
695       ENDDO cmaq
696 # endif
698 !-----------------------------------------------------------------------
699 ! Print a warning message for not using a combination of radiation and microphysics from Goddard
700 !-----------------------------------------------------------------------
701       DO i = 1, model_config_rec % max_dom
702          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
703          IF ( ( (model_config_rec % ra_lw_physics(i) == goddardlwscheme .OR. &
704                  model_config_rec % ra_sw_physics(i) == goddardswscheme) .AND. &
705                  model_config_rec % mp_physics(i) /= nuwrf4icescheme ) .OR. &
706               (  model_config_rec % mp_physics(i) == nuwrf4icescheme .AND. &
707                 (model_config_rec % ra_lw_physics(i) /= goddardlwscheme .AND. &
708                  model_config_rec % ra_sw_physics(i) /= goddardswscheme) ) ) THEN
709             wrf_err_message = '--- WARNING: Goddard radiation and Goddard 4ice microphysics are not used together'
710             CALL wrf_message ( wrf_err_message )
711             wrf_err_message = '--- WARNING: These options may be best to use together.'
712             CALL wrf_message ( wrf_err_message )
713          END IF
714       ENDDO
716 #endif
718 !-----------------------------------------------------------------------
719 ! Check that all values of sf_surface_physics are the same for all domains
720 !-----------------------------------------------------------------------
722       DO i = 2, model_config_rec % max_dom
723          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
724          IF ( model_config_rec % sf_surface_physics(i)     .NE. &
725               model_config_rec % sf_surface_physics(1) ) THEN
726             wrf_err_message = '--- ERROR: sf_surface_physics must be equal for all domains '
727             CALL wrf_message ( wrf_err_message )
728             wrf_err_message = '--- Fix sf_surface_physics in namelist.input '
729          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
730          count_fatal_error = count_fatal_error + 1
731          END IF
732       ENDDO
735 !-----------------------------------------------------------------------
736 ! Check that all values of sf_sfclay_physics are the same for all domains
737 !-----------------------------------------------------------------------
739       DO i = 2, model_config_rec % max_dom
740          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
741          IF ( model_config_rec % sf_sfclay_physics(i)     .NE. &
742               model_config_rec % sf_sfclay_physics(1) ) THEN
743             wrf_err_message = '--- ERROR: sf_sfclay_physics must be equal for all domains '
744             CALL wrf_message ( wrf_err_message )
745             wrf_err_message = '--- Fix sf_sfclay_physics in namelist.input '
746          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
747          count_fatal_error = count_fatal_error + 1
748          END IF
749       ENDDO
752 !-----------------------------------------------------------------------
753 ! Check that all values of mp_physics are the same for all domains
754 !-----------------------------------------------------------------------
756       DO i = 2, model_config_rec % max_dom
757          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
758          IF ( model_config_rec % mp_physics(i)     .NE. &
759               model_config_rec % mp_physics(1) ) THEN
760             wrf_err_message = '--- NOTE: mp_physics must be equal for all domains '
761             CALL wrf_debug ( 1, wrf_err_message )
762             wrf_err_message = '--- NOTE:     ----> Setting all mp_physics entries to value defined in the inner most domain'
763             CALL wrf_debug ( 1, wrf_err_message )
764          END IF
765       ENDDO
766       d1_value = model_config_rec%mp_physics(model_config_rec % max_dom)
767       DO i = 1, model_config_rec % max_dom-1
768          model_config_rec%mp_physics(i) = d1_value
769       END DO
771 #if (EM_CORE == 1)
772 !--------------------------------------------------------------------------------------------------
773 ! Input tables must exist in running directory for fast bin microphysics scheme (mp_physics = 30)
774 !--------------------------------------------------------------------------------------------------
775 # if ( BUILD_SBM_FAST == 1 )
776       IF ( model_config_rec % mp_physics(1) .EQ. FAST_KHAIN_LYNN_SHPUND ) THEN
777          INQUIRE(FILE='./SBM_input_33/BLKD_SDC.dat', EXIST=fsbm_table1_exists)
778          IF (.not.fsbm_table1_exists ) THEN
779             wrf_err_message = "--- ERROR: Input directory SBM_input_33 doesn't exist !!!"
780             CALL wrf_message ( wrf_err_message )
781             wrf_err_message = '--- ERROR: Download this directory of table files from http://www2.mmm.ucar.edu/wrf/src/wrf_files/'
782              CALL wrf_message ( wrf_err_message )
783             count_fatal_error = count_fatal_error + 1
784          END IF
785          INQUIRE(FILE='./scattering_tables_2layer_high_quad_1dT_1%fw_110/GRAUPEL_+00C_000fvw.sct', EXIST=fsbm_table2_exists)
786          IF (.not.fsbm_table2_exists ) THEN
787             wrf_err_message = "--- ERROR: Input directory scattering_tables_2layer_high_quad_1dT_1%fw_110 doesn't exist !!!"
788             CALL wrf_message ( TRIM( wrf_err_message ) )
789             wrf_err_message = '--- ERROR: Download this directory of input table files from http://www2.mmm.ucar.edu/wrf/src/wrf_files/'
790             CALL wrf_message ( wrf_err_message )
791             count_fatal_error = count_fatal_error + 1
792          END IF
793       END IF
794 # endif
795 !-----------------------------------------------------------------------
796 ! There are restrictions on the AFWA diagnostics regarding the choice
797 ! of microphysics scheme. These are hard coded in the AFWA diags driver,
798 ! so while this is inelegant, it is about as good as we can do.
799 !-----------------------------------------------------------------------
800       IF ( model_config_rec%afwa_diag_opt(1) .EQ. 1 ) THEN
801          IF ( ( model_config_rec % mp_physics(1) .EQ. GSFCGCESCHEME   ) .OR. &
802               ( model_config_rec % mp_physics(1) .EQ. ETAMPNEW        ) .OR. &
803               ( model_config_rec % mp_physics(1) .EQ. THOMPSON        ) .OR. &
804               ( model_config_rec % mp_physics(1) .EQ. WSM5SCHEME      ) .OR. &
805               ( model_config_rec % mp_physics(1) .EQ. WSM6SCHEME      ) .OR. &
806               ( model_config_rec % mp_physics(1) .EQ. WDM6SCHEME      ) .OR. &
807               ( model_config_rec % mp_physics(1) .EQ. MORR_TWO_MOMENT ) .OR. &
808               ( model_config_rec % mp_physics(1) .EQ. MORR_TM_AERO    ) ) THEN 
809             !  All is OK
810          ELSE
811             wrf_err_message = '--- WARNING: the AFWA diagnostics option knows only about the following MP schemes:'
812             CALL wrf_message ( wrf_err_message )
813             wrf_err_message = '--- GSFCGCESCHEME, ETAMPNEW, THOMPSON, WSM5SCHEME, WSM6SCHEME, MORR_TWO_MOMENT, MORR_TM_AERO, WDM6SCHEME'
814             CALL wrf_message ( wrf_err_message )
815          END IF
816       END IF
817 #endif
820 !-----------------------------------------------------------------------
821 ! Check that all values of ra_physics are the same for all domains
822 !-----------------------------------------------------------------------
824       DO i = 2, model_config_rec % max_dom
825          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
826          IF ( model_config_rec % ra_lw_physics(i)     .NE. &
827               model_config_rec % ra_lw_physics(1) ) THEN
828             wrf_err_message = '--- ERROR: ra_lw_physics must be equal for all domains '
829             CALL wrf_message ( wrf_err_message )
830             wrf_err_message = '--- Fix ra_lw_physics in namelist.input '
831          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
832          count_fatal_error = count_fatal_error + 1
833          END IF
834       ENDDO
836       DO i = 2, model_config_rec % max_dom
837          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
838          IF ( model_config_rec % ra_sw_physics(i)     .NE. &
839               model_config_rec % ra_sw_physics(1) ) THEN
840             wrf_err_message = '--- ERROR: ra_sw_physics must be equal for all domains '
841             CALL wrf_message ( wrf_err_message )
842             wrf_err_message = '--- Fix ra_sw_physics in namelist.input '
843          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
844          count_fatal_error = count_fatal_error + 1
845          END IF
846       ENDDO
849 !------------------------------------------------------------------------------
850 ! Check that a value for time_step is given, and is not just set to default (-1)
851 !------------------------------------------------------------------------------
853          IF ( ( model_config_rec % use_wps_input == 0 ) .AND. &
854               ( model_config_rec % time_step .EQ. -1 ) ) THEN
856             wrf_err_message = '--- ERROR: Known problem.  time_step must be set to a positive integer'
857          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
858          count_fatal_error = count_fatal_error + 1
860          END IF
862 !-----------------------------------------------------------------------
863 ! Check that all values of bl_pbl_physics are the same for all domains
864 !-----------------------------------------------------------------------
866       DO i = 2, model_config_rec % max_dom
867          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
868          IF ( ( model_config_rec % bl_pbl_physics(i) .NE. model_config_rec % bl_pbl_physics(1) ) .AND. &
869               ( model_config_rec % bl_pbl_physics(i) .NE. 0                                    ) ) THEN
870             wrf_err_message = '--- ERROR: bl_pbl_physics must be equal for all domains (or = zero)'
871             CALL wrf_message ( wrf_err_message )
872             wrf_err_message = '--- Fix bl_pbl_physics in namelist.input '
873          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
874          count_fatal_error = count_fatal_error + 1
875          END IF
876       ENDDO
878 !-----------------------------------------------------------------------
879 ! Check that all values of gwd_opt are the same for all domains
880 !-----------------------------------------------------------------------
882       DO i = 2, model_config_rec % max_dom
883          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
884          IF ( ( model_config_rec % gwd_opt(i) .NE. model_config_rec % gwd_opt(1) ) .AND. &
885               ( model_config_rec % gwd_opt(i) .NE. 0                             ) ) THEN 
886             wrf_err_message = '--- ERROR: gwd_opt must be equal for all domains (or = zero)'
887             CALL wrf_message ( wrf_err_message )
888             wrf_err_message = '--- Fix gwd_opt in namelist.input '
889          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
890          count_fatal_error = count_fatal_error + 1
891          END IF
892       ENDDO
894 !-----------------------------------------------------------------------
895 ! Check that all values of cu_physics are the same for all domains
896 ! Note that a zero option is OK.
897 !-----------------------------------------------------------------------
899       DO i = 2, model_config_rec % max_dom
900          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
901          IF ( ( model_config_rec % cu_physics(i) .NE. model_config_rec % cu_physics(1) ) .AND. &
902               ( model_config_rec % cu_physics(i) .NE. 0                                ) ) THEN
903             wrf_err_message = '--- ERROR: cu_physics must be equal for all domains (or = zero)'
904             CALL wrf_message ( wrf_err_message )
905             wrf_err_message = '--- Fix cu_physics in namelist.input '
906          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
907          count_fatal_error = count_fatal_error + 1
908          END IF
909       ENDDO
912 #if ( defined NO_GAMMA_SUPPORT )
913 !-----------------------------------------------------------------------
914 ! GF CU scheme requires an intrinsic gamma function. This is a 2008
915 ! feature that not all compilers yet support.
916 !-----------------------------------------------------------------------
918       GF_test : DO i = 1, model_config_rec % max_dom
919          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
920          IF ( model_config_rec % cu_physics(i) .EQ. GFSCHEME ) THEN
921             wrf_err_message = '--- ERROR: cu_physics GF uses an intrinsic gamma function that is not available with this compiler'
922             CALL wrf_message ( TRIM( wrf_err_message ) )
923             wrf_err_message = '--- Change compilers, or change cu_physics option in the namelist.input file.'
924             CALL wrf_message ( TRIM( wrf_err_message ) )
925             count_fatal_error = count_fatal_error + 1
926             EXIT GF_test
927          END IF
928       ENDDO GF_test
929 #endif
931 !-----------------------------------------------------------------------
932 ! Climate GHG from an input file requires coordinated pairing of
933 ! LW and SW schemes, and restricts which schemes are eligible.
934 ! Only radiation schemes CAM, RRTM, RRTMG, RRTMG_fast may be used.
935 ! CAM LW and CAM SW must be used together.
936 ! RRTM, RRTMG, RRTMG_fast LW and SW may be wildly mixed and matched 
937 ! together.
938 !-----------------------------------------------------------------------
940       IF ( model_config_rec % ghg_input .EQ. 1 ) THEN
941          oops = 0
942          DO i = 1, model_config_rec % max_dom
943             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
944             IF ( ( ( model_config_rec % ra_lw_physics(i) .EQ. CAMLWSCHEME          )   .AND. &
945                    ( model_config_rec % ra_sw_physics(i) .EQ. CAMSWSCHEME          ) ) .OR.  &
946                ( ( ( model_config_rec % ra_lw_physics(i) .EQ. RRTMSCHEME           )   .OR.  &
947                    ( model_config_rec % ra_lw_physics(i) .EQ. RRTMG_LWSCHEME       )   .OR.  &
948                    ( model_config_rec % ra_lw_physics(i) .EQ. RRTMG_LWSCHEME_FAST  ) ) .AND. &
949                  ( ( model_config_rec % ra_sw_physics(i) .EQ. SWRADSCHEME          )   .OR.  &
950                    ( model_config_rec % ra_sw_physics(i) .EQ. RRTMG_SWSCHEME       )   .OR.  &
951                    ( model_config_rec % ra_sw_physics(i) .EQ. RRTMG_SWSCHEME_FAST  ) ) ) ) THEN
952                ! This is OK, no way would a negation have been understandable!
953             ELSE
954                oops = oops + 1
955             END IF
956          ENDDO
958          IF ( oops .GT. 0 ) THEN
959             wrf_err_message = '--- ERROR: ghg_input available only for these radiation schemes: CAM, RRTM, RRTMG, RRTMG_fast'
960             CALL wrf_message ( TRIM( wrf_err_message ) )
961             wrf_err_message = '           And the LW and SW schemes must be reasonably paired together:'  
962             CALL wrf_message ( TRIM( wrf_err_message ) )
963             wrf_err_message = '           OK = CAM LW with CAM SW'
964             CALL wrf_message ( TRIM( wrf_err_message ) )
965             wrf_err_message = '           OK = RRTM, RRTMG LW or SW, RRTMG_fast LW or SW may be mixed'
966             CALL wrf_message ( TRIM( wrf_err_message ) )
967          END IF
968       END IF
970 !-----------------------------------------------------------------------
971 ! If fractional_seaice = 0, and tice2tsk_if2cold = .true, nothing will happen
972 !-----------------------------------------------------------------------
974       IF ( ( model_config_rec%fractional_seaice .EQ. 0 ).AND. &
975               ( model_config_rec%tice2tsk_if2cold ) ) THEN
976             wrf_err_message = '--- WARNING: You set tice2tsk_if2cold = .true.,  but fractional_seaice = 0'
977             CALL wrf_debug ( 1, wrf_err_message )
978             wrf_err_message = '--- WARNING: tice2tsk_if2cold will have no effect on results.'
979             CALL wrf_debug ( 1, wrf_err_message )
980       END IF
982 !-----------------------------------------------------------------------
983 ! If fractional_seaice == 1, cannot have the simple land model slab 
984 ! scheme activated.
985 !-----------------------------------------------------------------------
987       IF ( ( model_config_rec%fractional_seaice     .EQ. 1          ) .AND. &
988            ( model_config_rec%sf_surface_physics(1) .EQ. SLABSCHEME ) ) THEN
989          wrf_err_message = '--- ERROR: fractional seaice does not work with simple slab thermal diffusion land model'
990          CALL wrf_message ( TRIM( wrf_err_message ) )
991          wrf_err_message = '--- ERROR: Change either fractional_seaice=1 OR sf_surface_physics=1'
992          CALL wrf_message ( TRIM( wrf_err_message ) )
993          count_fatal_error = count_fatal_error + 1
994       END IF
996 !-----------------------------------------------------------------------
997 ! Check that if fine_input_stream /= 0, io_form_auxinput2 must also be in use
998 !-----------------------------------------------------------------------
1000       DO i = 1, model_config_rec % max_dom
1001          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1002          IF ( ( model_config_rec%fine_input_stream(i) .NE. 0 ).AND. &
1003               ( model_config_rec%io_form_auxinput2 .EQ. 0 ) ) THEN
1004             wrf_err_message = '--- ERROR: If fine_input_stream /= 0, io_form_auxinput2 must be /= 0'
1005             CALL wrf_message ( wrf_err_message )
1006             wrf_err_message = '--- Set io_form_auxinput2 in the time_control namelist (probably to 2).'
1007          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1008          count_fatal_error = count_fatal_error + 1
1009          END IF
1010       ENDDO
1012 #if (EM_CORE == 1)
1014 !-----------------------------------------------------------------------
1015 ! Check that if num_metgrid_levels < 20, lagrange_order should be 1
1016 !-----------------------------------------------------------------------
1017             IF  ( model_config_rec%num_metgrid_levels .LE. 20 ) THEN
1018             wrf_err_message = 'Linear vertical interpolation is recommended with input vertical resolution this coarse, changing lagrange_order to 1' 
1019             CALL wrf_debug ( 1, wrf_err_message )
1020             model_config_rec%lagrange_order = 1
1021             END IF
1023 !-----------------------------------------------------------------------
1024 ! Check for domain consistency for urban options.
1025 !-----------------------------------------------------------------------
1027       d1_value = model_config_rec%sf_urban_physics(1)
1028       DO i = 2, model_config_rec % max_dom
1029          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1030          IF ( model_config_rec%sf_urban_physics(i) /= d1_value ) THEN
1031             wrf_err_message = '--- NOTE:   sf_urban_physics option must be identical in each domain'
1032             CALL wrf_debug ( 1, wrf_err_message )
1033             wrf_err_message = '--- NOTE:   ----> Resetting namelist values to that defined on the inner most domain'
1034             CALL wrf_debug ( 1, wrf_err_message )
1035          ENDIF
1036       END DO
1037       d1_value = model_config_rec%sf_urban_physics(model_config_rec % max_dom)
1038       DO i = 1, model_config_rec % max_dom-1
1039          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1040          model_config_rec%sf_urban_physics(i) = d1_value
1041       END DO
1043 !------------------------------------------------------------------------
1044 ! Mills (2011) sea-ice albedo treatment only for Noah LSM and Noah-MP LSM
1045 !------------------------------------------------------------------------
1046       IF ( model_config_rec%seaice_albedo_opt == 1 ) THEN
1047          DO i = 1, model_config_rec % max_dom
1048             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1049             IF ( ( model_config_rec%sf_surface_physics(i) /= LSMSCHEME ) .AND. &
1050                  ( model_config_rec%sf_surface_physics(i) /= NOAHMPSCHEME ) ) THEN
1052                write (wrf_err_message, '(" --- ERROR:   seaice_albedo_opt == 1 works only with ")')
1053                CALL wrf_message ( TRIM ( wrf_err_message ) )
1054                write (wrf_err_message, '("              sf_surface_physics == ", I2, " (Noah) or ", I2, " (Noah-MP).")') &
1055                LSMSCHEME, NOAHMPSCHEME
1056          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1057          count_fatal_error = count_fatal_error + 1
1059             END IF
1060             
1061          END DO
1063       END IF
1066 #endif
1068 !-----------------------------------------------------------------------
1069 !           Check that NSAS shallow convection is not allowed to turn on simultaneously with NSAS
1070 !-----------------------------------------------------------------------
1071       DO i = 1, model_config_rec % max_dom
1072          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1073          IF ( model_config_rec%shcu_physics(i) == nscvshcuscheme .AND. model_config_rec%cu_physics(i) == nsasscheme) THEN
1074             WRITE(wrf_err_message, '(" --- ERROR: NSCV shallow convection scheme is already included in NSAS ")')
1075             CALL wrf_message ( TRIM ( wrf_err_message ) )
1076          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1077          count_fatal_error = count_fatal_error + 1
1078          END IF
1079       END DO
1081 #if (EM_CORE == 1)
1083 !-----------------------------------------------------------------------
1084 ! Check if the bucket size for rain is > 0. If so, then we need to activate
1085 ! a derived namelist variable: bucketr_opt.
1086 !-----------------------------------------------------------------------
1088    IF ( model_config_rec%bucket_mm .GT. 0. ) THEN
1089       model_config_rec%bucketr_opt = 1
1090    END IF
1092 !-----------------------------------------------------------------------
1093 ! Check if the bucket size for radiation is > 0. If so, then we need to activate
1094 ! a derived namelist variable: bucketf_opt.
1095 !-----------------------------------------------------------------------
1097    IF ( model_config_rec%bucket_J .GT. 0. ) THEN
1098       model_config_rec%bucketf_opt = 1
1099    END IF
1101 !-----------------------------------------------------------------------
1102 ! Check if the precip bucket reset time interval > 0. If so, then we need to 
1103 ! activate a derived namelist variable: prec_acc_opt
1104 !-----------------------------------------------------------------------
1106    DO i = 1, model_config_rec % max_dom
1107       IF ( model_config_rec%prec_acc_dt(i) .GT. 0. ) THEN
1108          model_config_rec%prec_acc_opt = 1
1109       END IF
1110    END DO
1112 !-----------------------------------------------------------------------
1113 ! Check if any stochastic perturbation scheme is turned on in any domain,
1114 ! if so, set derived variable sppt_on=1 and/or rand_perturb_on and/or skebs_on=1
1115 !-----------------------------------------------------------------------
1117    DO i = 1, model_config_rec % max_dom
1118          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1119          IF ( model_config_rec % sppt(i) .ne. 0)  then
1120            model_config_rec % sppt_on=1
1121            IF (( model_config_rec%KMINFORCT .ne. 1) .or. (model_config_rec%KMAXFORCT .ne. 1000000) .or.   &
1122                ( model_config_rec%LMINFORCT .ne. 1) .or. (model_config_rec%LMAXFORCT .ne. 1000000)) then    
1123                wrf_err_message = '--- Warning: the namelist parameter "kminforct" etc. are for SKEBS only'
1124                CALL wrf_message ( wrf_err_message )
1125                wrf_err_message = '             and should not be changed from their default value for SPPT'
1126                CALL wrf_message ( wrf_err_message )
1127                wrf_err_message = '--- ERROR: If you really want to modify "kminforct" etc.,  edit module_check a_mundo.'
1128                CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1129                count_fatal_error = count_fatal_error + 1
1130            endif
1131          endif
1132    ENDDO
1133    DO i = 1, model_config_rec % max_dom
1134          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1135          IF ( model_config_rec % rand_perturb(i) .ne. 0)  then
1136            model_config_rec % rand_perturb_on=1
1137            IF (( model_config_rec%KMINFORCT .ne. 1) .or. (model_config_rec%KMAXFORCT .ne. 1000000) .or.   &
1138                ( model_config_rec%LMINFORCT .ne. 1) .or. (model_config_rec%LMAXFORCT .ne. 1000000)) then    
1139                wrf_err_message = '--- Warning: the namelist parameter "kminforct" etc are for SKEBS only'
1140                CALL wrf_message ( wrf_err_message )
1141                wrf_err_message = '             and should not be changed from their default value for RAND_PERTURB'
1142                CALL wrf_message ( wrf_err_message )
1143                wrf_err_message = '--- ERROR: If you really want to modify "kminforct" etc.,  edit module_check a_mundo.'
1144                CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1145                count_fatal_error = count_fatal_error + 1
1146            endif
1147          endif
1148    ENDDO
1149    DO i = 1, model_config_rec % max_dom
1150          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1151          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)  &
1152            .or. ( model_config_rec % spp(i) .ne. 0))  then
1153            model_config_rec % spp_on=1
1154            IF (( model_config_rec%KMINFORCT .ne. 1) .or. (model_config_rec%KMAXFORCT .ne. 1000000) .or.   &
1155                ( model_config_rec%LMINFORCT .ne. 1) .or. (model_config_rec%LMAXFORCT .ne. 1000000)) then    
1156                wrf_err_message = '--- Warning: the namelist parameter "kminforct" etc are for SKEBS only'
1157                CALL wrf_message ( wrf_err_message )
1158                wrf_err_message = '             and should not be changed from their default value for RAND_PERTURB'
1159                CALL wrf_message ( wrf_err_message )
1160                wrf_err_message = '--- ERROR: If you really want to modify "kminforct" etc.,  edit module_check a_mundo.'
1161                CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1162                count_fatal_error = count_fatal_error + 1
1163            endif
1164          endif
1165          IF ( model_config_rec % spp(i) .ne. 0)  then
1166            model_config_rec % spp_conv=1
1167            model_config_rec % spp_pbl=1
1168            model_config_rec % spp_lsm=1
1169          endif
1170    ENDDO
1171    DO i = 1, model_config_rec % max_dom
1172          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1173          IF ( model_config_rec % stoch_vertstruc_opt(i) ==1 )  then
1174            model_config_rec % skebs_vertstruc=1       ! parameter stoch_vertstruc_opt is being replaced with skebs_vertstruc
1175                                                       ! stoch_vertstruc_opt is obsolete starting with V3.7
1176            wrf_err_message = '--- WARNING: the namelist parameter "stoch_vertstruc_opt" is obsolete.'
1177                CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1178            wrf_err_message = '             Please replace with namelist parameter "skebs_vertstruc" in V3.7 and later versions.'
1179                CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1180          endif
1181    ENDDO
1183    DO i = 1, model_config_rec % max_dom
1184          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1185          IF ( model_config_rec % stoch_force_opt(i) ==1 )  THEN
1186            model_config_rec % skebs(i)=1    ! parameter stoch_forc_opt is being replaced with skebs;
1187                                             ! stoch_vertstruc_opt is obsolete starting with V3.7
1188            wrf_err_message = '--- WARNING: the namelist parameter "stoch_force_opt" is obsolete.'
1189                CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1190            wrf_err_message = '             Please replace with namelist parameter "skebs" in V3.7 and later versions.'
1191                CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1192          ENDIF
1193    ENDDO
1194    DO i = 1, model_config_rec % max_dom
1195          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1196          IF ( model_config_rec % skebs(i) .ne. 0)  then
1197            model_config_rec % skebs_on=1
1198          endif
1199    ENDDO
1201 !-----------------------------------------------------------------------
1202 ! Random fields are by default thin 3D arrays (:,1,:).
1203 ! If random fields have vertical structures (stoch_vertstruc_opt .ne. 0)
1204 ! make them full 3D array arrays
1205 !-----------------------------------------------------------------------
1206    IF ( model_config_rec % skebs_vertstruc     .ne. 99 )  then
1207       model_config_rec % num_stoch_levels = model_config_rec %e_vert(1)
1208    ENDIF
1209    IF ( model_config_rec % sppt_vertstruc      .ne. 99 )  then
1210       model_config_rec % num_stoch_levels = model_config_rec %e_vert(1)
1211    ENDIF
1212    IF ( model_config_rec % rand_pert_vertstruc .ne. 99 )  then
1213       model_config_rec % num_stoch_levels = model_config_rec %e_vert(1)
1214    ENDIF
1216 !--------------------------------------------------------------------------------
1217 ! Check if boundary perturbations is turned on and set to '1' (perturb_bdy=1).
1218 ! If so, make sure skebs_on is also turned on.
1219 !--------------------------------------------------------------------------------
1220    IF ( model_config_rec % perturb_bdy .EQ. 1 ) then
1221         model_config_rec % skebs_on=1
1222          wrf_err_message = '--- WARNING: perturb_bdy=1 option uses SKEBS pattern and may'
1223          CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1224          wrf_err_message = '             increase computation time.'
1225          CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1226    ENDIF
1228 !--------------------------------------------------------------------------------
1229 ! Check if chemistry boundary perturbations is turned on and set to '1' (perturb_chem_bdy=1).
1230 ! If so, make sure rand_perturb_on is also turned on.
1231 ! perturb_chem_bdy can be turned on only if WRF_CHEM is also compiled.
1232 ! If perturb_chem_bdy=1, then have_bcs_chem should be turned on as well.
1233 !--------------------------------------------------------------------------------
1235    IF ( model_config_rec % perturb_chem_bdy .EQ. 1 ) then
1237 #if (WRF_CHEM != 1)
1238       wrf_err_message = '--- ERROR: This option is only for WRF_CHEM.'
1239          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1240          count_fatal_error = count_fatal_error + 1
1241 #endif
1243 !NOTE      model_config_rec % rand_perturb_on=1
1244          wrf_err_message = '--- WARNING: perturb_chem_bdy=1 option uses RAND pattern and may'
1245          CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1246          wrf_err_message = '             increase computation time.'
1247          CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1249 #if (WRF_CHEM == 1)
1250       IF ( .NOT. model_config_rec % have_bcs_chem(1) ) THEN
1251             wrf_err_message = '--- ERROR: This perturb_chem_bdy option needs '// &
1252                               'have_bcs_chem = .true. in chem.'
1253          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1254          count_fatal_error = count_fatal_error + 1
1255       ENDIF
1256 #endif
1258    ENDIF
1260 !----------------------------------------------------------------------------
1261 ! If trajectory option is turned off, make sure the number of trajectories is
1262 ! zero.
1263 !----------------------------------------------------------------------------
1264    IF ( ( model_config_rec%traj_opt .EQ. 0 ) .AND. &
1265         ( model_config_rec%num_traj .NE. 0 ) ) THEN
1266          wrf_err_message = '--- WARNING: traj_opt is zero, but num_traj is not zero; setting num_traj to zero.'
1267          CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1268          model_config_rec%num_traj = 0
1269    END IF
1271 !-----------------------------------------------------------------------
1272 ! Catch old method for using multi-file LBCs. Let folks know the 
1273 ! new way to get the same functionality with run-time options.
1274 !-----------------------------------------------------------------------
1275 #if _MULTI_BDY_FILES_
1276    wrf_err_message = '--- ERROR: Do not use the compile-time -D_MULTI_BDY_FILES_ option for multi-file LBCs.'
1277    CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1278    wrf_err_message = '--- ERROR: Use the run-time namelist option multi_bdy_files in nml record bdy_control.'
1279    CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1280    count_fatal_error = count_fatal_error + 1
1281 #endif
1283 !----------------------------------------------------------------------------
1284 ! If using multi_bdy_files option or not, make the lateral bdy file root name
1285 ! correct. For example, we want "wrfbdy_d01" for NON multi_bdy_files and we
1286 ! want "wrfbdy_d01_SOME_DATE" when using the multi_bdy_files option.
1287 !----------------------------------------------------------------------------
1288    IF      ( model_config_rec%multi_bdy_files ) THEN
1289       IF ( INDEX ( TRIM(model_config_rec%bdy_inname) , "_<date>" ) .GT. 0 ) THEN
1290          ! No op, all OK
1291       ELSE
1292          wrf_err_message = '--- ERROR: Need bdy_inname = "wrfbdy_d<domain>_<date>"'
1293          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1294          count_fatal_error = count_fatal_error + 1
1295 !        len1 = LEN_TRIM(model_config_rec%bdy_inname)
1296 !        len2 = "_<date>"
1297 !        model_config_rec%bdy_inname(1:len1+len2) = TRIM(model_config_rec%bdy_inname) // "_<date>"
1298       END IF
1299    ELSE IF ( .NOT. model_config_rec%multi_bdy_files ) THEN
1300       IF ( INDEX ( TRIM(model_config_rec%bdy_inname) , "_<date>" ) .EQ. 0 ) THEN
1301          ! No op, all OK
1302       ELSE
1303          wrf_err_message = '--- ERROR: Remove bdy_inname = "wrfbdy_d<domain>_<date>"'
1304          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1305          count_fatal_error = count_fatal_error + 1
1306 !        len1 = LEN_TRIM(model_config_rec%bdy_inname)
1307 !        len2 = "_<date>"
1308 !        DO len_loop len1-len2+1 , len1
1309 !           model_config_rec%bdy_inname(len_loop:len_loop) = " "
1310 !        END DO 
1311       END IF
1312    END IF
1314 #endif
1316 #if (EM_CORE == 1)
1317 !-----------------------------------------------------------------------
1318 ! In program real, if hypsometric_opt = 2, adjust_heights cannot be set to .true.
1319 !-----------------------------------------------------------------------
1320       IF ( model_config_rec%hypsometric_opt .EQ. 2 &
1321            .AND. model_config_rec%adjust_heights ) THEN
1322          wrf_err_message = '--- NOTE: hypsometric_opt is 2, setting adjust_heights = F'
1323          CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1324             model_config_rec%adjust_heights = .false.
1325       ENDIF
1326 #endif
1328 #if (EM_CORE == 1)
1329 !-----------------------------------------------------------------------
1330 ! scale-aware KF cannot work with 3DTKE (km_opt=5)
1331 !-----------------------------------------------------------------------
1333       oops = 0
1334       DO i = 1, model_config_rec % max_dom
1335          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1336          IF ( ( model_config_rec%km_opt(i) .EQ. SMS_3DTKE ) .AND. &
1337               ( model_config_rec%cu_physics(i) .EQ. MSKFSCHEME ) ) THEN
1338             oops = oops + 1
1339          END IF
1340       ENDDO      ! Loop over domains
1341       IF ( oops .GT. 0 ) THEN
1342          wrf_err_message = '--- ERROR: cu_physics = 11 cannot work with 3DTKE scheme '
1343          CALL wrf_message ( wrf_err_message )
1344          wrf_err_message = '--- Choose another bl_pbl_physics OR use another cu_physics option '
1345          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1346          count_fatal_error = count_fatal_error + 1
1347       END IF
1348       
1349 !-----------------------------------------------------------------------
1350 ! IF cu_physics = 11 (scale-aware KF), THEN set other required flags. This 
1351 ! is not an error, just a convenience for the user.
1352 !-----------------------------------------------------------------------
1354       DO i = 1, model_config_rec % max_dom
1355          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1356          IF ( model_config_rec%cu_physics(i) .EQ. MSKFSCHEME ) THEN
1357             wrf_err_message = '--- NOTE: cu_physics is 11, setting icloud = 1 and cu_rad_feedback = T'
1358             CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1359             model_config_rec%cu_rad_feedback(i) = .true.
1360             model_config_rec%icloud = 1
1361          END IF
1362       ENDDO
1363       
1364 !-----------------------------------------------------------------------
1365 ! aercu_opt = 1 (CESM-aerosal) only works with MSKF, special Morrison
1366 !-----------------------------------------------------------------------
1368       oops = 0
1369       DO i = 1, model_config_rec % max_dom
1370          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1371          IF ( model_config_rec%aercu_opt .GT. 0 .AND.       &
1372               ( model_config_rec%cu_physics(i) .NE. MSKFSCHEME .OR. &
1373               model_config_rec%mp_physics(i) .NE. MORR_TM_AERO ) ) THEN
1374               oops = oops + 1
1375          END IF
1376       ENDDO
1378       IF ( oops .GT. 0 ) THEN
1379          wrf_err_message = '--- ERROR: aercu_opt requires cu_physics = 11, and mp_physics = 40 '
1380          CALL wrf_message ( wrf_err_message )
1381          wrf_err_message = '--- Fix these options in namelist.input if you would like to use aercu_opt'
1382          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1383          count_fatal_error = count_fatal_error + 1
1384       END IF
1386 !-----------------------------------------------------------------------
1387 ! Set the namelist parameters for the aercu_opt > 0
1388 !-----------------------------------------------------------------------
1390       IF ( model_config_rec % aercu_opt .GT. 0 ) THEN
1391          model_config_rec % alevsiz_cu = 30
1392          model_config_rec % no_src_types_cu = 10
1393          DO i = 1, model_config_rec % max_dom
1394             model_config_rec % scalar_pblmix(i) = 1
1395          END DO
1397          wrf_err_message = '--- NOTE: aercu_opt is in use, setting:  ' // &
1398                            'alevsiz_cu=30, no_src_types_cu=10, scalar_pblmix = 1'
1399          CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1401       END IF
1403 #endif
1405 !-----------------------------------------------------------------------
1406 ! If sst_update = 0, set io_form_auxinput4 to 0 so WRF will not try to
1407 ! input the data; auxinput_interval must also be 0
1408 !-----------------------------------------------------------------------
1410       IF ( model_config_rec%sst_update .EQ. 0 ) THEN
1411          model_config_rec%io_form_auxinput4 = 0
1412          DO i = 1, model_config_rec % max_dom
1413             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1414             wrf_err_message = '--- NOTE: sst_update is 0, ' // &
1415                   'setting io_form_auxinput4 = 0 and auxinput4_interval = 0 for all domains'
1416             CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1417             model_config_rec%auxinput4_interval(i)   = 0
1418             model_config_rec%auxinput4_interval_y(i) = 0
1419             model_config_rec%auxinput4_interval_d(i) = 0
1420             model_config_rec%auxinput4_interval_h(i) = 0
1421             model_config_rec%auxinput4_interval_m(i) = 0
1422             model_config_rec%auxinput4_interval_s(i) = 0
1423          ENDDO
1424       ELSE
1425          IF ( model_config_rec%io_form_auxinput4 .EQ. 0 ) THEN
1426             wrf_err_message = '--- ERROR: If sst_update /= 0, io_form_auxinput4 must be /= 0'
1427             CALL wrf_message ( wrf_err_message )
1428             wrf_err_message = '--- Set io_form_auxinput4 in the time_control namelist (probably to 2).'
1429          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1430          count_fatal_error = count_fatal_error + 1
1431          END IF
1432       END IF
1434 !-----------------------------------------------------------------------
1435 ! If sst_update = 1, we need to make sure that two nml items are set:
1436 !   1. io_form_auxinput4 = 2 (only for one domain)
1437 !   2. auxinput4_interval = NON-ZERO (just check most coarse domain)
1438 !-----------------------------------------------------------------------
1440       IF ( model_config_rec%sst_update .EQ. 1 ) THEN
1441          IF ( model_config_rec%io_form_auxinput4 .EQ. 0 ) THEN
1442             wrf_err_message = '--- ERROR: If sst_update /= 0, io_form_auxinput4 must be /= 0'
1443             CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1444             wrf_err_message = '--- Set io_form_auxinput4 in the time_control namelist (probably to 2).'
1445             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1446             count_fatal_error = count_fatal_error + 1
1447          END IF
1449          IF ( ( model_config_rec%auxinput4_interval(1)   .EQ. 0 ) .AND. &
1450               ( model_config_rec%auxinput4_interval_y(1) .EQ. 0 ) .AND. &
1451               ( model_config_rec%auxinput4_interval_d(1) .EQ. 0 ) .AND. &
1452               ( model_config_rec%auxinput4_interval_h(1) .EQ. 0 ) .AND. &
1453               ( model_config_rec%auxinput4_interval_m(1) .EQ. 0 ) .AND. &
1454               ( model_config_rec%auxinput4_interval_s(1) .EQ. 0 ) ) THEN
1455             wrf_err_message = '--- ERROR: If sst_update /= 0, one of the auxinput4_interval settings must be /= 0'
1456             CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1457             wrf_err_message = '--- Set auxinput4_interval_s to the same value as interval_seconds (usually a pretty good guess).'
1458             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1459             count_fatal_error = count_fatal_error + 1
1460          END IF
1461       END IF
1463 !-----------------------------------------------------------------------
1464 ! If qna_update = 0, set io_form_auxinput17 to 0 so WRF will not try to
1465 ! input the data; auxinput_interval must also be 0
1466 !-----------------------------------------------------------------------
1468       IF ( model_config_rec%qna_update .EQ. 0 ) THEN
1469          model_config_rec%io_form_auxinput17 = 0
1470          DO i = 1, model_config_rec % max_dom
1471             wrf_err_message = '--- NOTE: qna_update is 0, ' // &
1472                   'setting io_form_auxinput17 = 0 and auxinput17_interval = 0 for all domains'
1473             CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1474             model_config_rec%auxinput17_interval(i)   = 0
1475             model_config_rec%auxinput17_interval_y(i) = 0
1476             model_config_rec%auxinput17_interval_d(i) = 0
1477             model_config_rec%auxinput17_interval_h(i) = 0
1478             model_config_rec%auxinput17_interval_m(i) = 0
1479             model_config_rec%auxinput17_interval_s(i) = 0
1480          ENDDO
1481       ELSE
1482          IF ( model_config_rec%io_form_auxinput17 .EQ. 0 ) THEN
1483             wrf_err_message = '--- ERROR: If qna_update /= 0, io_form_auxinput17 must be /= 0'
1484             CALL wrf_message ( wrf_err_message )
1485             wrf_err_message = '--- Set io_form_auxinput17 in the time_control namelist (probably to 2).'
1486          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1487          count_fatal_error = count_fatal_error + 1
1488          END IF
1489       END IF
1491 !-----------------------------------------------------------------------
1492 ! If qna_update = 1, we need to make sure that two nml items are set:
1493 !   1. io_form_auxinput17 = 2 (only for one domain)
1494 !   2. auxinput17_interval = NON-ZERO (just check most coarse domain)
1495 !-----------------------------------------------------------------------
1497       IF ( model_config_rec%qna_update .EQ. 1 ) THEN
1498          IF ( model_config_rec%io_form_auxinput17 .EQ. 0 ) THEN
1499             wrf_err_message = '--- ERROR: If qna_update /= 0, io_form_auxinput17 must be /= 0'
1500             CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1501             wrf_err_message = '--- Set io_form_auxinput17 in the time_control namelist (probably to 2).'
1502             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1503             count_fatal_error = count_fatal_error + 1
1504          END IF
1506          IF ( ( model_config_rec%auxinput17_interval(1)   .EQ. 0 ) .AND. &
1507               ( model_config_rec%auxinput17_interval_y(1) .EQ. 0 ) .AND. &
1508               ( model_config_rec%auxinput17_interval_d(1) .EQ. 0 ) .AND. &
1509               ( model_config_rec%auxinput17_interval_h(1) .EQ. 0 ) .AND. &
1510               ( model_config_rec%auxinput17_interval_m(1) .EQ. 0 ) .AND. &
1511               ( model_config_rec%auxinput17_interval_s(1) .EQ. 0 ) ) THEN
1512             wrf_err_message = '--- ERROR: If qna_update /= 0, one of the auxinput17_interval settings must be /= 0'
1513             CALL wrf_debug ( 0, TRIM(wrf_err_message) )
1514             wrf_err_message = '--- Set auxinput17_interval_s to the same value as interval_seconds (usually a pretty good guess).'
1515             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1516             count_fatal_error = count_fatal_error + 1
1517          END IF
1518       END IF
1520 !-----------------------------------------------------------------------
1521 ! The qndropsource relies on the flag PROGN (when not running chemistry)
1522 ! and is always allocated when running WRF Chem.
1523 !-----------------------------------------------------------------------
1525 #if ( (EM_CORE == 1) && (WRF_CHEM != 1) )
1526       model_config_rec%alloc_qndropsource = 0
1527       DO i = 1, model_config_rec % max_dom
1528          IF ( model_config_rec%progn(i) .EQ. 1 ) THEN
1529             model_config_rec%alloc_qndropsource = 1
1530          END IF
1531       END DO
1533 #elif (WRF_CHEM == 1)
1534       model_config_rec%alloc_qndropsource = 1
1535 #endif
1537 #if ((EM_CORE == 1) && (DA_CORE != 1))
1538 !-----------------------------------------------------------------------
1539 ! Check that if grid_sfdda is one, grid_fdda is also 1
1540 !-----------------------------------------------------------------------
1542       DO i = 1, model_config_rec % max_dom
1543          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1544          IF ( ( model_config_rec%grid_sfdda(i) .GT. 0 ).AND. &
1545               ( model_config_rec%grid_fdda (i) .NE. 1 ) ) THEN
1546             wrf_err_message = '--- ERROR: If grid_sfdda >= 1, then grid_fdda must also = 1 for that domain '
1547             CALL wrf_message ( wrf_err_message )
1548             wrf_err_message = '--- Change grid_fdda or grid_sfdda in namelist.input '
1549          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1550          count_fatal_error = count_fatal_error + 1
1551          END IF
1552       ENDDO
1554 !-----------------------------------------------------------------------
1555 ! If grid_fdda or grid_sfdda is 0 for any domain, all interval and
1556 ! ending time information that domain must be set to zero.  For
1557 ! surface fdda, we also need to make sure that the PXLSM soil nudging
1558 ! switch is also zero.  Either surface fdda or soil nudging with the
1559 ! PX scheme are enough to allow the surface fdda file to be read.
1560 !-----------------------------------------------------------------------
1562       DO i = 1, model_config_rec % max_dom
1563          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1565          IF ( model_config_rec%grid_fdda(i) .EQ. 0 ) THEN
1566             WRITE (wrf_err_message, FMT='(A,I6,A)') '--- NOTE: grid_fdda is 0 for domain ', &
1567                          i, ', setting gfdda interval and ending time to 0 for that domain.'
1568             CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1570             model_config_rec%gfdda_end_y(i) = 0
1571             model_config_rec%gfdda_end_d(i) = 0
1572             model_config_rec%gfdda_end_h(i) = 0
1573             model_config_rec%gfdda_end_m(i) = 0
1574             model_config_rec%gfdda_end_s(i) = 0
1575             model_config_rec%gfdda_interval(i)   = 0
1576             model_config_rec%gfdda_interval_y(i) = 0
1577             model_config_rec%gfdda_interval_d(i) = 0
1578             model_config_rec%gfdda_interval_h(i) = 0
1579             model_config_rec%gfdda_interval_m(i) = 0
1580             model_config_rec%gfdda_interval_s(i) = 0
1581          END IF
1583          IF ( ( model_config_rec%grid_sfdda(i) .EQ. 0 ) .AND. &
1584               ( model_config_rec%pxlsm_soil_nudge(i) .EQ. 0 ) ) THEN
1585             WRITE (wrf_err_message, FMT='(A,I6,A)') &
1586                          '--- NOTE: both grid_sfdda and pxlsm_soil_nudge are 0 for domain ', &
1587                          i, ', setting sgfdda interval and ending time to 0 for that domain.'
1588             CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1590             model_config_rec%sgfdda_end_y(i) = 0
1591             model_config_rec%sgfdda_end_d(i) = 0
1592             model_config_rec%sgfdda_end_h(i) = 0
1593             model_config_rec%sgfdda_end_m(i) = 0
1594             model_config_rec%sgfdda_end_s(i) = 0
1595             model_config_rec%sgfdda_interval(i)   = 0
1596             model_config_rec%sgfdda_interval_y(i) = 0
1597             model_config_rec%sgfdda_interval_d(i) = 0
1598             model_config_rec%sgfdda_interval_h(i) = 0
1599             model_config_rec%sgfdda_interval_m(i) = 0
1600             model_config_rec%sgfdda_interval_s(i) = 0
1601          END IF
1603          IF ( model_config_rec%obs_nudge_opt(i) .EQ. 0 ) THEN
1604             WRITE (wrf_err_message, FMT='(A,I6,A)') '--- NOTE: obs_nudge_opt is 0 for domain ', &
1605                          i, ', setting obs nudging interval and ending time to 0 for that domain.'
1606             CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1608             model_config_rec%fdda_end(i) = 0
1609             model_config_rec%auxinput11_interval(i)   = 0
1610             model_config_rec%auxinput11_interval_y(i) = 0
1611             model_config_rec%auxinput11_interval_d(i) = 0
1612             model_config_rec%auxinput11_interval_h(i) = 0
1613             model_config_rec%auxinput11_interval_m(i) = 0
1614             model_config_rec%auxinput11_interval_s(i) = 0
1615             model_config_rec%auxinput11_end(i)   = 0
1616             model_config_rec%auxinput11_end_y(i) = 0
1617             model_config_rec%auxinput11_end_d(i) = 0
1618             model_config_rec%auxinput11_end_h(i) = 0
1619             model_config_rec%auxinput11_end_m(i) = 0
1620             model_config_rec%auxinput11_end_s(i) = 0
1621          END IF
1623       ENDDO      ! Loop over domains
1625 !-----------------------------------------------------------------------
1626 ! If grid_sfdda = 2, we turn it into derived namelist fasdas
1627 !-----------------------------------------------------------------------
1629       DO i = 1, model_config_rec % max_dom
1630          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1631          model_config_rec%fasdas(i) = 0
1632          IF ( model_config_rec%grid_sfdda(i) .EQ. 2 ) THEN
1633             model_config_rec%fasdas(i) = 1
1634          END IF
1635       ENDDO
1637 !-----------------------------------------------------------------------
1638 ! FASDAS:  Check that rinblw is set for max_domains in the namelist if sffdda is active
1639 !-----------------------------------------------------------------------
1640     rinblw_already_done = .FALSE.
1641     DO j = 1, model_config_rec%max_dom
1642     IF ( .NOT. model_config_rec % grid_allowed(j) ) CYCLE
1643     IF (model_config_rec%grid_sfdda(j) .EQ. 1 ) THEN
1644       DO i = 2, model_config_rec%max_dom
1645          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1646          IF ( model_config_rec%rinblw(i) .EQ. -1 ) THEN
1647             model_config_rec%rinblw(i) = model_config_rec % rinblw(1)
1648             IF ( .NOT. rinblw_already_done ) THEN
1649                wrf_err_message = 'Setting blank rinblw entries to domain #1 values.'
1650                CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1651                wrf_err_message = ' --> The rinblw entry in the namelist.input is now max_domains.'
1652                CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1653             END IF
1654             rinblw_already_done = .TRUE.
1655          END IF
1656        ENDDO
1658 !------------------------------------------------------------------------
1659 ! Check that rinblw is not -1 if sfdda is active
1660 !------------------------------------------------------------------------
1661        IF ( model_config_rec%rinblw(1) .EQ. -1 ) THEN
1662             wrf_err_message = '--- ERROR: rinblw needs to be set in the namelist.input file.'
1663          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1664          count_fatal_error = count_fatal_error + 1
1665        END IF
1666     END IF
1667     END DO
1669 !------------------------------------------------------------------------
1670 ! Check to see if FASDAS is active
1671 !------------------------------------------------------------------------
1672     DO i = 1, model_config_rec%max_dom
1673      IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1674      IF (model_config_rec%fasdas(i) .EQ. 1 ) THEN
1675         wrf_err_message = 'FASDAS is active. Mixed Layer fdda is inactive'
1676         CALL wrf_debug ( 1, TRIM( wrf_err_message ) )
1677      END IF
1679 !------------------------------------------------------------------------
1680 ! Check to make sure sfdda is active if FASDAS is in namelist
1681 !------------------------------------------------------------------------
1682 !     IF (model_config_rec%fasdas(i) .EQ. 1 ) THEN
1683 !       IF (model_config_rec%grid_sfdda(i) .EQ. 0) THEN
1684 !        wrf_err_message = '--- ERROR: sfdda needs to be set in the namelist.input file to run FASDAS.'
1685 !        CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1686 !        count_fatal_error = count_fatal_error + 1
1687 !       END IF
1688 !     END IF
1689      END DO
1691 !END FASDAS
1693 !-----------------------------------------------------------------------
1694 !  Only implement the mfshconv option if the QNSE PBL is activated.
1695 !-----------------------------------------------------------------------
1697       oops = 0
1698       DO i = 1, model_config_rec % max_dom
1699          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1700          IF ( ( model_config_rec%bl_pbl_physics(i) .NE. QNSEPBLSCHEME ) .AND. &
1701               ( model_config_rec%mfshconv(i) .NE. 0 ) ) THEN
1702             model_config_rec%mfshconv(i) = 0
1703             oops = oops + 1
1704          END IF
1705       ENDDO      ! Loop over domains
1706       IF ( oops .GT. 0 ) THEN
1707          wrf_err_message = '--- NOTE: bl_pbl_physics /= 4, implies mfshconv must be 0, resetting'
1708          CALL wrf_debug ( 1, wrf_err_message )
1709       END IF
1711 !-----------------------------------------------------------------------
1712 !  shcu_physics = 3 (grimsshcuscheme) only works with YSU & MYNN PBL.
1713 !-----------------------------------------------------------------------
1715       oops = 0
1716       DO i = 1, model_config_rec % max_dom
1717          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1718          IF ( model_config_rec%shcu_physics(i) .EQ. GRIMSSHCUSCHEME ) THEN
1719             IF ( (model_config_rec%bl_pbl_physics(i) .EQ. YSUSCHEME) .OR. &
1720                  (model_config_rec%bl_pbl_physics(i) .EQ. SHINHONGSCHEME) .OR. &
1721                  (model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME2) .OR. &
1722                  (model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME3) ) THEN
1723                !NO PROBLEM
1724             ELSE
1725                model_config_rec%shcu_physics(i) = 0
1726                oops = oops + 1
1727             END IF
1728          END IF
1729       ENDDO      ! Loop over domains
1730       IF ( oops .GT. 0 ) THEN
1731          wrf_err_message = '--- NOTE: bl_pbl_physics /= 1,5,6,11 implies shcu_physics cannot be 3, resetting'
1732          CALL wrf_debug ( 1, wrf_err_message )
1733       END IF
1735 !-----------------------------------------------------------------------
1736 ! If MYNN PBL is not used, set bl_mynn_edmf = 0 so that shallow convection
1737 ! options can be set and we don't get additional output
1738 !-----------------------------------------------------------------------
1740       DO i = 1, model_config_rec % max_dom
1741          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1742          IF ( ( model_config_rec % bl_pbl_physics(i) .NE. MYNNPBLSCHEME2 ) .AND. &
1743               ( model_config_rec % bl_pbl_physics(i) .NE. MYNNPBLSCHEME3 ) ) THEN
1744               model_config_rec % bl_mynn_edmf(i) = 0
1745               model_config_rec % bl_mynn_output(i) = 0
1746          END IF
1747       ENDDO
1749 !-----------------------------------------------------------------------
1750 !  bl_mynn_edmf > 0 over-rules both shcu_physics & ishallow
1751 !-----------------------------------------------------------------------
1753       oops = 0
1754       EDMFMAX = MAXVAL(model_config_rec%bl_mynn_edmf(1:model_config_rec%max_dom))
1755       SCHUMAX = MAXVAL(model_config_rec%shcu_physics(1:model_config_rec%max_dom))
1756          IF ( ( ( EDMFMAX .GT. 0 ) .AND. ( SCHUMAX .GT. 0 ) ) .OR. &
1757               ( ( EDMFMAX .GT. 0 ) .AND. ( model_config_rec%ishallow .GT. 0 ) ) ) THEN
1758             wrf_err_message = '--- ERROR: bl_mynn_edmf > 0 requires both shcu_physics=0 & ishallow=0' 
1759             CALL wrf_message(wrf_err_message)
1760             wrf_err_message = 'when using MYNN PBL, by default bl_mynn_edmf is turned on'
1761             CALL wrf_message(wrf_err_message)
1762             wrf_err_message = 'Modify namelist.input so that shcu_physics nor ishallow is used when bl_mynn_edmf is turned on'
1763             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1764             count_fatal_error = count_fatal_error + 1
1765          END IF
1767 !-----------------------------------------------------------------------
1768 ! Make sure icloud_bl is only used when MYNN is chosen.
1769 !-----------------------------------------------------------------------
1771       oops = 0
1772       DO i = 1, model_config_rec % max_dom
1773          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1774          IF ( model_config_rec%icloud_bl .eq. 1) THEN
1775            IF ( model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME2 .OR. &
1776                 model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME3 ) THEN
1777               !CORRECTLY CONFIGURED
1778            ELSE
1779               model_config_rec%icloud_bl = 0
1780               oops = oops + 1
1781            END IF
1782          END IF
1783       ENDDO      ! Loop over domains
1784       IF ( oops .GT. 0 ) THEN
1785          wrf_err_message = 'Need MYNN PBL for icloud_bl = 1, resetting to 0'
1786          CALL wrf_debug ( 1, wrf_err_message )
1787       END IF
1789 #if (WRF_CHEM == 1)
1790 !-----------------------------------------------------------------------
1791 ! Make sure phot_blcld is only used when icloud_bl==1 and MYNN is chosen.
1792 !-----------------------------------------------------------------------
1794       oops = 0
1795       DO i = 1, model_config_rec % max_dom
1796          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1797          IF ( model_config_rec%phot_blcld(i) ) THEN
1798            IF ( ( model_config_rec%icloud_bl .eq. 1 ) .AND.  &
1799                 ( ( model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME2 ) .OR. &
1800                   ( model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME3 ) ) ) THEN
1801                 !CORRECTLY CONFIGURED
1802            ELSE
1803               oops = oops + 1
1804            END IF
1805          END IF
1806       ENDDO      ! Loop over domains
1807       IF ( oops .GT. 0 ) THEN
1808          wrf_err_message = '--- ERROR: Need MYNN PBL and icloud_bl = 1 for phot_blcld = .true.'
1809          CALL wrf_message(wrf_err_message)
1810          count_fatal_error = count_fatal_error + 1
1811       END IF
1812 #endif
1814 !-----------------------------------------------------------------------
1815 !  We need to know if any of the cumulus schemes are active. This
1816 !  allows the model to allocate space.
1817 !-----------------------------------------------------------------------
1819       model_config_rec%cu_used = 0
1820       DO i = 1, model_config_rec % max_dom
1821          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1822          IF ( model_config_rec%cu_physics(i) .NE. NOCUSCHEME ) THEN
1823             model_config_rec%cu_used = 1
1824          END IF
1825       ENDDO
1827 !-----------------------------------------------------------------------
1828 !  We need to know if any of the shallow cumulus schemes are active. This
1829 !  allows the model to allocate space.
1830 !-----------------------------------------------------------------------
1832       model_config_rec%shcu_used = 0
1833       DO i = 1, model_config_rec % max_dom
1834          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1835          IF ( model_config_rec%shcu_physics(i) .NE. NOSHCUSCHEME ) THEN
1836             model_config_rec%shcu_used = 1
1837          END IF
1838       ENDDO
1840 !-----------------------------------------------------------------------
1841 !  We need to know if the any of the orographic gravity wave drag schemes
1842 !  are active on any domains. This allows the model to allocate space.
1843 !-----------------------------------------------------------------------
1845       model_config_rec%gwd_used = 0
1846       DO i = 1, model_config_rec % max_dom
1847          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1848          IF ( model_config_rec%gwd_opt(i) .EQ. 1 ) THEN
1849             model_config_rec%gwd_used = 1
1850          END IF
1851       ENDDO
1852       DO i = 1, model_config_rec % max_dom
1853          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1854          IF ( model_config_rec%gwd_opt(i) .EQ. 3 ) THEN
1855             model_config_rec%gwd_used = 3
1856          END IF
1857       ENDDO
1858       ! Check if user is requesting extra gravity-wave-drag diagnostics
1859       ! for a given GWD scheme
1860       ! Only assigned to gwd_opts that have diagnostics available
1861       model_config_rec%gwd_diags_used = 0
1862       IF ( model_config_rec%gwd_used .EQ. 3 .AND.     &
1863            model_config_rec%gwd_diags .EQ. 1 ) THEN
1864          model_config_rec%gwd_diags_used = 3
1865       END IF
1867 !-----------------------------------------------------------------------
1868 ! Make sure microphysics option without QICE array cannot be used with icloud=3
1869 !-----------------------------------------------------------------------
1871       oops = 0
1872       DO i = 1, model_config_rec % max_dom
1873          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1874          IF ( model_config_rec%icloud .eq. 3) THEN
1875            IF ( model_config_rec%mp_physics(i) .EQ. WSM3SCHEME .OR. &
1876                 model_config_rec%mp_physics(i) .EQ. KESSLERSCHEME ) THEN
1877                 oops = oops + 1
1878            END IF
1879          END IF
1880       ENDDO      ! Loop over domains
1881       IF ( oops .GT. 0 ) THEN
1882          wrf_err_message = '--- ERROR: Need microphysics schemes with QICE array for icloud = 3'
1883          CALL wrf_message ( wrf_err_message )
1884          wrf_err_message = '--- Choose a microphysics scheme other than WSM3 and Kessler'
1885          CALL wrf_message ( wrf_err_message )
1886          count_fatal_error = count_fatal_error + 1
1887       END IF
1889 !-----------------------------------------------------------------------
1890 !  If analysis FDDA is turned off, reset the io_forms to zero so that
1891 !  there is no chance that WRF tries to input the data.
1892 !-----------------------------------------------------------------------
1894       IF ( MAXVAL( model_config_rec%grid_fdda ) .EQ. 0 ) THEN
1895          model_config_rec%io_form_gfdda = 0
1896       ELSE
1897          IF ( model_config_rec%io_form_gfdda .EQ. 0 ) THEN
1898             wrf_err_message = '--- ERROR: If grid_fdda /= 0, io_form_gfdda must be /= 0'
1899             CALL wrf_message ( wrf_err_message )
1900             wrf_err_message = '--- Set io_form_gfdda in the time_control namelist (probably to 2).'
1901          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1902          count_fatal_error = count_fatal_error + 1
1903          END IF
1904       END IF
1905       IF ( MAXVAL( model_config_rec%grid_sfdda ) .EQ. 0 ) THEN
1906          model_config_rec%io_form_sgfdda = 0
1907       ELSE
1908          IF ( model_config_rec%io_form_sgfdda .EQ. 0 ) THEN
1909             wrf_err_message = '--- ERROR: If grid_sfdda /= 0, io_form_sgfdda must be /= 0'
1910             CALL wrf_message ( wrf_err_message )
1911             wrf_err_message = '--- Set io_form_sgfdda in the time_control namelist (probably to 2).'
1912          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1913          count_fatal_error = count_fatal_error + 1
1914          END IF
1915       END IF
1917 !-----------------------------------------------------------------------
1918 ! If we have asked for the pressure-level diagnostics, make sure we can output them
1919 !-----------------------------------------------------------------------
1921       IF ( model_config_rec%p_lev_diags .EQ. 1 ) THEN
1922          DO i = 1, model_config_rec % max_dom
1923             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1924             IF ( ( MAX ( model_config_rec%auxhist23_interval  (i) , &
1925                          model_config_rec%auxhist23_interval_d(i) , &
1926                          model_config_rec%auxhist23_interval_h(i) , &
1927                          model_config_rec%auxhist23_interval_m(i) , &
1928                          model_config_rec%auxhist23_interval_s(i) ) == 0 ) .OR. &
1929                  (  model_config_rec%io_form_auxhist23 == 0 ) ) THEN
1930                wrf_err_message = '--- ERROR: p_lev_diags requires auxhist23 file information'
1931                CALL wrf_message ( wrf_err_message )
1932                wrf_err_message = '--- ERROR: provide: auxhist23_interval (max_dom) and io_form_auxhist23'
1933                CALL wrf_message ( wrf_err_message )
1934                wrf_err_message = '--- Add supporting IO for stream 23 for pressure-level diags'
1935                CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1936                count_fatal_error = count_fatal_error + 1
1937             END IF
1938          END DO
1939          DO i = 1, model_config_rec % max_dom
1940             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1941             model_config_rec%p_lev_interval(i) = model_config_rec%auxhist23_interval  (i)*   60 + &
1942                                                  model_config_rec%auxhist23_interval_d(i)*86400 + &
1943                                                  model_config_rec%auxhist23_interval_h(i)* 3600 + &
1944                                                  model_config_rec%auxhist23_interval_m(i)*   60 + &
1945                                                  model_config_rec%auxhist23_interval_s(i)
1946          END DO
1947       END IF
1950 !-----------------------------------------------------------------------
1951 ! If we have asked for the height-level diagnostics, make sure we can output them
1952 !-----------------------------------------------------------------------
1954       IF ( model_config_rec%z_lev_diags .EQ. 1 ) THEN
1955          DO i = 1, model_config_rec % max_dom
1956             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1957             IF ( ( MAX ( model_config_rec%auxhist22_interval  (i) , &
1958                          model_config_rec%auxhist22_interval_d(i) , &
1959                          model_config_rec%auxhist22_interval_h(i) , &
1960                          model_config_rec%auxhist22_interval_m(i) , &
1961                          model_config_rec%auxhist22_interval_s(i) ) == 0 ) .OR. &
1962                  (  model_config_rec%io_form_auxhist22 == 0 ) ) THEN
1963                wrf_err_message = '--- ERROR: z_lev_diags requires auxhist22 file information'
1964                CALL wrf_message ( wrf_err_message )
1965                wrf_err_message = '--- ERROR: provide: auxhist22_interval (max_dom) and io_form_auxhist22'
1966                CALL wrf_message ( wrf_err_message )
1967                wrf_err_message = '--- Add supporting IO for stream 22 for height-level diags'
1968                CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
1969                count_fatal_error = count_fatal_error + 1
1970             END IF
1971          END DO
1972          DO i = 1, model_config_rec % max_dom
1973             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1974             model_config_rec%z_lev_interval(i) = model_config_rec%auxhist22_interval  (i)*   60 + &
1975                                                  model_config_rec%auxhist22_interval_d(i)*86400 + &
1976                                                  model_config_rec%auxhist22_interval_h(i)* 3600 + &
1977                                                  model_config_rec%auxhist22_interval_m(i)*   60 + &
1978                                                  model_config_rec%auxhist22_interval_s(i)
1979          END DO
1980       END IF
1982 !-----------------------------------------------------------------------
1983 ! For RASM Diagnostics
1984 ! -verify that only one time interval is specified
1985 ! -change the intervals to values used in RASM Diagnotics
1986 ! -verify that a time interval has been set
1987 !-----------------------------------------------------------------------
1989 ! 1. Only one time interval type specified
1991       DO i = 1, model_config_rec % max_dom
1992          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
1993          count_opt = 0
1994          IF ( model_config_rec%mean_diag_interval_s (i) .GT. 0 ) THEN
1995             count_opt = count_opt + 1
1996          END IF
1997          IF ( model_config_rec%mean_diag_interval_m (i) .GT. 0 ) THEN
1998             count_opt = count_opt + 1
1999          END IF
2000          IF ( model_config_rec%mean_diag_interval_h (i) .GT. 0 ) THEN
2001             count_opt = count_opt + 1
2002          END IF
2003          IF ( model_config_rec%mean_diag_interval_d (i) .GT. 0 ) THEN
2004             count_opt = count_opt + 1
2005          END IF
2006          IF ( model_config_rec%mean_diag_interval_mo(i) .GT. 0 ) THEN
2007             count_opt = count_opt + 1
2008          END IF
2009          IF ( model_config_rec%mean_diag_interval   (i) .GT. 0 ) THEN
2010             count_opt = count_opt + 1
2011          END IF
2012          IF ( count_opt .GT. 1 ) THEN
2013             wrf_err_message = '--- ERROR:  Only use one of: mean_diag_interval, _s, _m, _h, _d, _mo '
2014             CALL wrf_message ( wrf_err_message )
2015             count_fatal_error = count_fatal_error + 1
2016          END IF
2017       END DO
2019 ! 2. Put canonical intervals into RASM expected form
2021       DO i = 1, model_config_rec % max_dom
2022          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2023          IF ( model_config_rec%mean_diag_interval_s (i) .GT. 0 ) THEN
2024             model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_s (i)
2025             model_config_rec%mean_freq = 1
2026          END IF
2027          IF ( model_config_rec%mean_diag_interval_m (i) .GT. 0 ) THEN
2028             model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_m (i)
2029             model_config_rec%mean_freq = 2
2030          END IF
2031          IF ( model_config_rec%mean_diag_interval_h (i) .GT. 0 ) THEN
2032             model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_h (i)
2033             model_config_rec%mean_freq = 3
2034          END IF
2035          IF ( model_config_rec%mean_diag_interval_d (i) .GT. 0 ) THEN
2036             model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_d (i)
2037             model_config_rec%mean_freq = 4
2038          END IF
2039          IF ( model_config_rec%mean_diag_interval_mo(i) .GT. 0 ) THEN
2040             model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval_mo(i)
2041             model_config_rec%mean_freq = 5
2042          END IF
2043          IF ( model_config_rec%mean_diag_interval   (i) .GT. 0 ) THEN
2044             model_config_rec%mean_interval(i) = model_config_rec%mean_diag_interval   (i)
2045             model_config_rec%mean_freq = 2
2046          END IF
2047       END DO
2049 ! 3. If requested, need an interval.
2051       IF ( model_config_rec%mean_diag .EQ. 1 ) THEN
2052          count_opt = 0
2053          DO i = 1, model_config_rec % max_dom
2054             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2055             IF ( model_config_rec%mean_interval   (i) .GT. 0 ) THEN
2056                count_opt = count_opt + 1
2057             END IF
2058          END DO
2059          IF ( count_opt .LT. 1 ) THEN
2060             wrf_err_message = '--- ERROR:  mean_diag = 1, but no computation interval given'
2061             CALL wrf_message ( wrf_err_message )
2062             wrf_err_message = '            Use one of: mean_diag_interval, _s, _m, _h, _d, _mo '
2063             CALL wrf_message ( wrf_err_message )
2064             count_fatal_error = count_fatal_error + 1
2065          END IF
2066       END IF
2068 !-----------------------------------------------------------------------
2069 ! For nwp_diagnostics = 1, history_interval must be used.           
2070 !-----------------------------------------------------------------------
2072       IF ( ( model_config_rec%nwp_diagnostics .NE. 0 ) .AND. &
2073            ( model_config_rec%history_interval(1) .EQ. 0 ) ) THEN
2074          wrf_err_message = '--- ERROR:  nwp_diagnostics requires the use of "history_interval" namelist.'
2075          CALL wrf_message ( wrf_err_message )
2076          wrf_err_message = '---         Replace interval variable with "history_interval".'
2077          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2078          count_fatal_error = count_fatal_error + 1
2079       END IF
2081 !-----------------------------------------------------------------------
2082 ! If a user sets nwp_diagnostics = 1, then radar reflectivity computation
2083 ! needs to happen
2084 !-----------------------------------------------------------------------
2086       IF ( model_config_rec % nwp_diagnostics == 1 ) model_config_rec % do_radar_ref = 1
2088 !-----------------------------------------------------------------------
2089 ! If hailcast_opt = 1 for any domain, convective parameterization must be off for that domain.           
2090 !-----------------------------------------------------------------------
2092       DO i = 1, model_config_rec % max_dom
2093          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2094          IF ( ( model_config_rec%hailcast_opt(i) .NE. 0 ) .AND. &
2095               (model_config_rec%cu_physics(i) .NE. 0) ) THEN
2096               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).'
2097               CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2098               count_fatal_error = count_fatal_error + 1
2099          ENDIF
2100       ENDDO
2102 !-----------------------------------------------------------------------
2103 ! Name change in the namelist.input file.  We used to only have the
2104 ! ocean mixed layer option (omlcall=1).  With the addition of a 3D ocean,
2105 ! now let's change the name of the option.  If the old name is present,
2106 ! tell the user to swap their namelist, and then stop.
2107 !-----------------------------------------------------------------------
2109       IF ( model_config_rec%omlcall .NE. 0 ) THEN
2110          wrf_err_message = '--- ERROR:  The namelist.input variable "omlcall" has been renamed.'
2111          CALL wrf_message ( wrf_err_message )
2112          wrf_err_message = '---         Replace "omlcall" with the new name "sf_ocean_physics".'
2113          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2114          count_fatal_error = count_fatal_error + 1
2115       END IF
2117 !-----------------------------------------------------------------------
2118 ! For adaptive time stepping, certain physics schemes are not allowed
2119 ! to have intermittent frequencies.  So, for those schemes below, we just
2120 ! turn the frequencies so that the schemes are called for each time step.
2121 !-----------------------------------------------------------------------
2123       IF ( model_config_rec%use_adaptive_time_step ) THEN
2124          IF ( ( model_config_rec%cu_physics(1) .EQ. BMJSCHEME     ) .OR. &
2125               ( model_config_rec%cu_physics(1) .EQ. SCALESASSCHEME) .OR. &
2126               ( model_config_rec%cu_physics(1) .EQ. SASSCHEME     ) .OR. &
2127               ( model_config_rec%cu_physics(1) .EQ. OSASSCHEME    ) .OR. &
2128               ( model_config_rec%cu_physics(1) .EQ. KSASSCHEME    ) .OR. &
2129               ( model_config_rec%cu_physics(1) .EQ. NSASSCHEME    ) .OR. &
2130               ( model_config_rec%cu_physics(1) .EQ. TIEDTKESCHEME ) ) THEN
2131             wrf_err_message = '--- WARNING: If use_adaptive_time_step, must use cudt=0 for the following CU schemes:'
2132             CALL wrf_debug ( 1, wrf_err_message )
2133             wrf_err_message = '---          BMJ, all SAS, Tiedtke'
2134             CALL wrf_debug ( 1, wrf_err_message )
2135             wrf_err_message = '---          CUDT=0 has been done for you.'
2136             CALL wrf_debug ( 1, wrf_err_message )
2137             DO i = 1, model_config_rec % max_dom
2138                model_config_rec%cudt(i) = 0
2139             END DO
2140          END IF
2141       END IF
2143 !-----------------------------------------------------------------------
2144 ! When digital filtering is turned on, if no specific time step is given to be
2145 ! used during the digitial filtering period, then the standard WRF time
2146 ! step is used.  If neither time steps are specified, then fatal error.
2147 !-----------------------------------------------------------------------
2149       IF ( .NOT. model_config_rec%dfi_opt .EQ. DFI_NODFI ) THEN
2150          IF ( model_config_rec%time_step_dfi .EQ. -1 ) THEN
2151             model_config_rec%time_step_dfi = model_config_rec%time_step
2152             IF ( model_config_rec%time_step_dfi .EQ. -1 ) THEN
2153                wrf_err_message = '--- ERROR: DFI Timestep or standard WRF time step must be specified.'
2154                CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2155                count_fatal_error = count_fatal_error + 1
2156             END IF
2157          END IF
2158       END IF
2160 !-----------------------------------------------------------------------
2161 ! The cu_rad_feedback namelist flag with the two Grell cumulus parameterization
2162 ! schemes needs to have the namelist flag cu_diag=1
2163 !-----------------------------------------------------------------------
2165       DO i = 1, model_config_rec % max_dom
2166          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2167          IF ( ( model_config_rec%cu_rad_feedback(i) .EQV. .TRUE. )  .OR. &
2168               ( model_config_rec%cu_rad_feedback(i) .EQV. .true. ) ) THEN
2169             IF ( ( model_config_rec%cu_physics(1) .EQ. GFSCHEME     ) .OR. &
2170                  ( model_config_rec%cu_physics(1) .EQ. G3SCHEME     ) .OR. &
2171                  ( model_config_rec%cu_physics(1) .EQ. GDSCHEME     ) ) THEN
2172                wrf_err_message = '--- WARNING: Turning on cu_rad_feedback also requires setting cu_diag== 1'
2173                CALL wrf_debug ( 1, wrf_err_message )
2174                model_config_rec%cu_diag(i) = 1
2175             ELSE
2176                model_config_rec%cu_diag(i) = 0
2177             END IF
2178          END IF
2179       END DO
2181 !-----------------------------------------------------------------------
2182 ! The namelist flag cu_diag=1 must have one of the two Grell cumulus parameterizations
2183 ! turned on.  All other cumulus parameterizations need to have cu_diag=0
2184 !-----------------------------------------------------------------------
2186        DO i = 1, model_config_rec % max_dom
2187          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2188          IF ( model_config_rec%cu_diag(i) .EQ. G3TAVE ) THEN
2189           IF ( ( model_config_rec%cu_physics(i) .NE. GDSCHEME ) .AND. &
2190                ( model_config_rec%cu_physics(i) .NE. GFSCHEME ) .AND. &
2191                ( model_config_rec%cu_physics(i) .NE. KFCUPSCHEME ) .AND. &
2192                ( model_config_rec%cu_physics(i) .NE. G3SCHEME ) ) THEN
2193                 wrf_err_message = '--- ERROR: Using cu_diag=1 requires use of one of the following CU schemes:'
2194                 CALL wrf_message ( wrf_err_message )
2195                 wrf_err_message = '---          Grell-Freitas (GF) CU scheme'
2196                 CALL wrf_message ( wrf_err_message )
2197                 wrf_err_message = '---          Grell 3D (G3) CU scheme'
2198                 CALL wrf_message ( wrf_err_message )
2199                 wrf_err_message = '---          Kain-Fritsch Cumulus Potential (KF-CuP) CU scheme'
2200                 CALL wrf_message ( wrf_err_message )
2201                 wrf_err_message = '---          Grell-Devenyi (GD) CU scheme'
2202             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2203             count_fatal_error = count_fatal_error + 1
2204           END IF
2205          END IF
2206        END DO
2208 !-----------------------------------------------------------------------
2209 ! The namelist flag kf_edrates=1 must have one of the three KF cumulus parameterizations
2210 ! turned on.  All other cumulus parameterizations need to have kf_edrates=0
2211 !-----------------------------------------------------------------------
2213        DO i = 1, model_config_rec % max_dom
2214          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2215          IF ( model_config_rec%kf_edrates(i) .EQ. KFEDRATES ) THEN
2216           IF ( ( model_config_rec%cu_physics(i) .NE. KFETASCHEME ) .AND. &
2217                ( model_config_rec%cu_physics(i) .NE. MSKFSCHEME ) .AND. &
2218                ( model_config_rec%cu_physics(i) .NE. KFSCHEME ) ) THEN
2219                 wrf_err_message = '--- ERROR: Using kf_edrates=1 requires use of one of the following KF schemes:'
2220                 CALL wrf_message ( wrf_err_message )
2221                 wrf_err_message = '---          Kain-Fritsch (cu_physics=1)'
2222                 CALL wrf_message ( wrf_err_message )
2223                 wrf_err_message = '---          Multi-scale Kain-Fritsch (cu_physics=11)'
2224                 CALL wrf_message ( wrf_err_message )
2225                 wrf_err_message = '---          old Kain-Fritsch (cu_physics=99)'
2226             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2227             count_fatal_error = count_fatal_error + 1
2228           END IF
2229          END IF
2230        END DO
2232 !-----------------------------------------------------------------------
2233 ! Test to see if we allocate space for the time series.
2234 !-----------------------------------------------------------------------
2236       IF ( wrf_dm_on_monitor() ) THEN
2237          CALL wrf_tsin_exist ( exists )
2238          IF ( exists ) THEN
2239             IF ( model_config_rec%solar_diagnostics == 1 ) THEN
2240                model_config_rec%process_time_series = 2
2241             ELSE
2242                model_config_rec%process_time_series = 1
2243             END IF
2244          ELSE
2245             model_config_rec%process_time_series = 0
2246          END IF
2247       END IF
2248 #ifdef DM_PARALLEL
2249       CALL wrf_dm_bcast_integer(model_config_rec%process_time_series, 1)
2250 #endif
2251 !-----------------------------------------------------------------------
2252 ! The three Grell cumulus parameterization schemes need to have the
2253 ! namelist flag cu_diag=1, and all other cumulus schemes must have
2254 ! cu_diag=0.
2255 !-----------------------------------------------------------------------
2257       DO i = 1, model_config_rec % max_dom
2258          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2259          IF ( ( model_config_rec%cu_physics(i) .EQ. GDSCHEME ) .OR. &
2260               ( model_config_rec%cu_physics(i) .EQ. GFSCHEME ) .OR. &
2261               ( model_config_rec%cu_physics(i) .EQ. KFCUPSCHEME ) .OR. &
2262               ( model_config_rec%cu_physics(i) .EQ. G3SCHEME ) ) THEN
2263             model_config_rec%cu_diag(i) = 1
2264          ELSE
2265             model_config_rec%cu_diag(i) = 0
2266          END IF
2267       END DO
2269 !-----------------------------------------------------------------------
2270 !  Only implement the TEMF PBL scheme with the TEMP SFCLAY scheme.  
2271 !-----------------------------------------------------------------------
2273       DO i = 1, model_config_rec % max_dom
2274          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2275          IF ( ( model_config_rec%bl_pbl_physics(i) .EQ. TEMFPBLSCHEME ) .AND. &
2276               ( model_config_rec%sf_sfclay_physics(i) .NE. TEMFSFCSCHEME ) )  THEN
2277             wrf_err_message = '--- ERROR: Using bl_pbl_physics=10 requires sf_sfclay_physics=10 '
2278             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2279             count_fatal_error = count_fatal_error + 1
2280          ELSEIF ( ( model_config_rec%bl_pbl_physics(i) .NE. TEMFPBLSCHEME ) .AND. &
2281                   ( model_config_rec%sf_sfclay_physics(i) .EQ. TEMFSFCSCHEME ) ) THEN
2282             wrf_err_message = '--- ERROR: Using sf_sfclay_physics=10 requires bl_pbl_physics=10 '
2283             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2284             count_fatal_error = count_fatal_error + 1
2285          END IF
2286       ENDDO      ! Loop over domains
2288 !-----------------------------------------------------------------------
2289 !  Need to set lagday to 150 if tmn_update is 1
2290 !-----------------------------------------------------------------------
2292       IF ( model_config_rec%tmn_update .EQ. 1 .AND. &
2293            model_config_rec%lagday .EQ. 1 ) THEN
2294            wrf_err_message = '--- ERROR: Using tmn_update=1 requires lagday=150 '
2295          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2296          count_fatal_error = count_fatal_error + 1
2297       END IF
2299 !-----------------------------------------------------------------------
2300 !  Do not allow digital filtering to be run with TEMF.
2301 !-----------------------------------------------------------------------
2303       DO i = 1, model_config_rec % max_dom
2304          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2305          IF ( ( model_config_rec%bl_pbl_physics(i) .EQ. TEMFPBLSCHEME ) .AND. &
2306               (model_config_rec%dfi_opt .NE. DFI_NODFI) )  THEN
2307             wrf_err_message = '--- ERROR: DFI not available for bl_pbl_physics=10 '
2308             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2309             count_fatal_error = count_fatal_error + 1
2310          END IF
2311       ENDDO      ! Loop over domains
2313 !-----------------------------------------------------------------------
2314 !  If this is a restart, shut off the DFI.
2315 !-----------------------------------------------------------------------
2317       IF ( model_config_rec%restart ) THEN
2318          model_config_rec%dfi_opt = DFI_NODFI
2319       END IF
2321 !-----------------------------------------------------------------------
2322 !  The CLM scheme may not even be compiled, so make sure it is not allowed
2323 !  to be run if the code is not available.
2324 !-----------------------------------------------------------------------
2326 !#if !defined ( WRF_USE_CLM )
2327 !      oops = 0
2328 !      DO i = 1, model_config_rec % max_dom
2329 !         IF ( model_config_rec%sf_surface_physics(i) .EQ. CLMSCHEME ) THEN
2330 !            oops = oops + 1 
2331 !         END IF
2332 !      ENDDO      ! Loop over domains
2333 !      IF ( oops .GT. 0 ) THEN
2334 !         wrf_err_message = '--- ERROR: The CLM surface scheme was requested in the namelist.input file.'
2335 !         CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2336 !         wrf_err_message = '--- ERROR: However, the WRF CLM scheme was not compiled in WRF.'
2337 !         CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2338 !         wrf_err_message = '--- ERROR: Please place the -DWRF_USE_CLM option in configure.wrf file, and recompile.'
2339 !         ! CALL wrf_error_fatal ( wrf_err_message )
2340 !         CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2341 !         fatal_error = .true.
2342 !         count_fatal_error = count_fatal_error + 1
2343 !      END IF
2344 !#endif
2345 #if (WRF_USE_CLM != 1)
2346       oops = 0
2347       DO i = 1, model_config_rec % max_dom
2348          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2349          IF ( model_config_rec%sf_surface_physics(i) .EQ. CLMSCHEME ) THEN
2350             oops = oops + 1
2351          END IF
2352       ENDDO      ! Loop over domains
2353       IF ( oops .GT. 0 ) THEN
2354          wrf_err_message = '--- ERROR: The CLM surface scheme was requested in the namelist.input file.'
2355          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2356          wrf_err_message = '--- ERROR: However, the WRF CLM scheme was not compiled in WRF.'
2357          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2358          wrf_err_message = '--- ERROR: Please place the -DWRF_USE_CLM option in configure.wrf file, and recompile.'
2359          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2360          count_fatal_error = count_fatal_error + 1
2361       END IF
2362 #if ( WRF_CHEM == 1)
2363       DO i = 1, model_config_rec % max_dom
2364          IF ( model_config_rec%bio_emiss_opt(i) == MEGAN2_CLM ) THEN
2365             oops = oops + 1 
2366          END IF
2367       ENDDO
2369       IF ( oops .GT. 0 ) THEN
2370          wrf_err_message = '--- ERROR: The CLM Megan2.1 bio emission scheme was requested in the namelist.input file.'
2371          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2372          wrf_err_message = '--- ERROR: However, the WRF CLM scheme was not compiled in WRF.'
2373          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2374          wrf_err_message = '--- ERROR: Please place the -DWRF_USE_CLM option in configure.wrf file, and recompile.'
2375          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2376          count_fatal_error = count_fatal_error + 1
2377       END IF
2378 #endif
2379 #else
2380 !-----------------------------------------------------------------------
2381 !  The CLM scheme has been compiled.
2382 !  Check for possible logic errors with namelist settings.
2383 !-----------------------------------------------------------------------
2384 #if ( WRF_CHEM == 1 )
2385       oops = 0
2386       DO i = 1, model_config_rec % max_dom
2387         IF ( model_config_rec%bio_emiss_opt(i) == MEGAN2_CLM .and. &
2388              model_config_rec%sf_surface_physics(i) /= CLMSCHEME ) THEN
2389             oops = oops + 1 
2390         END IF
2391       ENDDO
2392       IF ( oops .GT. 0 ) THEN
2393         wrf_err_message = '--- ERROR: The CLM Megan2.1 bio emission scheme was requested in the namelist.input file.'
2394         CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2395         wrf_err_message = '--- ERROR: However, the CLM surface physics scheme was not requested in the namelist.input file.'
2396         CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2397         wrf_err_message = '--- ERROR: Please set the physics namelist variable sf_surface_physics to 5 in the namelist.input file.'
2398         CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2399         count_fatal_error = count_fatal_error + 1
2400       END IF
2401 #endif
2402       oops = 0
2403       DO i = 1, model_config_rec % max_dom
2404         IF ( model_config_rec%SF_SURFACE_PHYSICS(i) == CLMSCHEME .and. &
2405              model_config_rec%SF_URBAN_PHYSICS(i) >= 1 .and. &
2406              model_config_rec%SF_URBAN_PHYSICS(i) <= 3 ) THEN
2407              oops = oops + 1 
2408         ENDIF
2409       ENDDO
2410       IF ( oops .GT. 0 ) THEN
2411         wrf_err_message = '--- ERROR: CLM does not work with any URBAN PHYSICS SCHEME'
2412         CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2413         count_fatal_error = count_fatal_error + 1
2414       END IF
2415 #endif
2417 !-----------------------------------------------------------------------
2418 !  The CTSM scheme may not even be compiled, so make sure it is not allowed
2419 !  to be run if the code is not available.
2420 !-----------------------------------------------------------------------
2422 #if !defined ( WRF_USE_CTSM ) 
2423       oops = 0
2424       DO i = 1, model_config_rec % max_dom
2425          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2426          IF ( model_config_rec%sf_surface_physics(i) .EQ. CTSMSCHEME ) THEN
2427             oops = oops + 1
2428          END IF
2429       ENDDO      ! Loop over domains
2430       IF ( oops .GT. 0 ) THEN
2431          wrf_err_message = '--- ERROR: The CTSM surface scheme was requested in the namelist.input file.'
2432          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2433          wrf_err_message = '--- ERROR: However, the WRF CTSM scheme was not compiled in WRF.'
2434          CALL wrf_debug ( 0, TRIM(wrf_err_message) )
2435          wrf_err_message = '--- ERROR: Please read doc/README.CTSM for how to compile WRF with CTSM.'
2436          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2437          count_fatal_error = count_fatal_error + 1
2438       END IF
2439 #endif
2441 !-----------------------------------------------------------------------
2442 !  grav_settling = 1 must be turned off for mp_physics=28.
2443 !-----------------------------------------------------------------------
2444       oops = 0
2445       DO i = 1, model_config_rec % max_dom
2446          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2447          IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2448             IF ( model_config_rec%grav_settling(i) .NE. FOGSETTLING0 ) THEN
2449                 model_config_rec%grav_settling(i) = 0
2450                 oops = oops + 1
2451             END IF
2452          END IF
2453       ENDDO      ! Loop over domains
2454       IF ( oops .GT. 0 ) THEN
2455          wrf_err_message = '--- NOTE: mp_physics == 28, already has gravitational fog settling; resetting grav_settling to 0'
2456          CALL wrf_debug ( 1, wrf_err_message )
2457       END IF
2459 !-----------------------------------------------------------------------
2460 !  scalar_pblmix = 1 should be turned on for mp_physics=28. But can be off for MYNN (when bl_mynn_mixscalars = 1)
2461 !-----------------------------------------------------------------------
2462       oops = 0
2463       DO i = 1, model_config_rec % max_dom
2464          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2465          IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2466             IF ( (model_config_rec%use_aero_icbc .OR. model_config_rec%use_rap_aero_icbc) &
2467                                       .AND. model_config_rec%scalar_pblmix(i) .NE. 1 ) THEN
2468                 model_config_rec%scalar_pblmix(i) = 1
2469                 oops = oops + 1
2470             END IF
2471          END IF
2472       ENDDO      ! Loop over domains
2473       IF ( oops .GT. 0 ) THEN
2474          wrf_err_message = '--- WARNING: For mp_physics == 28 and use_aero_icbc is true, recommend to turn on scalar_pblmix'
2475          CALL wrf_debug ( 1, wrf_err_message )
2476          wrf_err_message = 'resetting scalar_pblmix = 1'
2477          CALL wrf_debug ( 1, wrf_err_message )
2478       END IF
2480       !NOW CHECK FOR MYNN
2481       oops = 0
2482       DO i = 1, model_config_rec % max_dom
2483          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2484          IF ((model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME2) .OR. &
2485              (model_config_rec%bl_pbl_physics(i) .EQ. MYNNPBLSCHEME3) ) THEN
2486             IF ( model_config_rec%bl_mynn_mixscalars(i) .EQ. 1 ) THEN
2487                 model_config_rec%scalar_pblmix(i) = 0
2488                 oops = oops + 1
2489             END IF
2490          END IF
2491       ENDDO      ! Loop over domains
2492       IF ( oops .GT. 0 ) THEN
2493          wrf_err_message = '--- WARNING: MYNN is set to mix scalars, turning off scalar_pblmix'
2494          CALL wrf_message ( wrf_err_message )
2495       END IF
2497 !-----------------------------------------------------------------------
2498 !  Set aer_init_opt for Thompson-MP-Aero (mp_physics=28)
2499 !-----------------------------------------------------------------------
2500      DO i = 1, model_config_rec % max_dom
2501        IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2502          IF ( model_config_rec%use_aero_icbc ) THEN
2503            model_config_rec%aer_init_opt = 1
2504          ELSE IF ( model_config_rec%use_rap_aero_icbc ) THEN
2505            model_config_rec%aer_init_opt = 2
2506          END IF
2507        END IF
2508      END DO
2510 !-----------------------------------------------------------------------
2511 !  Check if qna_update=0 when aer_init_opt>1 for Thompson-MP-Aero (mp_physics=28)
2512 !-----------------------------------------------------------------------
2513      DO i = 1, model_config_rec % max_dom
2514        IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO ) THEN
2515          IF ( model_config_rec%aer_init_opt .GT. 1 .and. model_config_rec%qna_update .EQ. 0 ) THEN
2516            wrf_err_message = '--- ERROR: Time-varying sfc aerosol emissions not set for mp_physics=28 '
2517            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2518            wrf_err_message = '--- ERROR: Please set qna_update=1 and control through auxinput17 options '
2519            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2520            count_fatal_error = count_fatal_error + 1
2521          END IF
2522        END IF
2523      END DO
2525 !-----------------------------------------------------------------------
2526 !  Set aer_fire_emit_opt for Thompson-MP-Aero (mp_physics=28)
2527 !-----------------------------------------------------------------------
2528      DO i = 1, model_config_rec % max_dom
2529        IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO .AND. model_config_rec%wif_fire_emit) THEN
2530          IF ( model_config_rec%aer_init_opt .EQ. 2) THEN
2531            IF ( model_config_rec%wif_input_opt .EQ. 1 ) THEN
2532              model_config_rec%aer_fire_emit_opt = 1
2533            ELSE IF ( model_config_rec%wif_input_opt .EQ. 2 ) THEN
2534              model_config_rec%aer_fire_emit_opt = 2
2535            END IF
2536          ELSE IF ( model_config_rec%aer_init_opt .EQ. 0 .OR. model_config_rec%aer_init_opt .EQ. 1) THEN
2537            wrf_err_message = '--- ERROR: wif_fire_emit=.true. but selected aerosol source does not contain fire emissions '
2538            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2539            wrf_err_message = '--- ERROR: Please use first guess aerosol source with fire emissions and set use_rap_aero_icbc=.true. '
2540            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2541            count_fatal_error = count_fatal_error + 1
2542          END IF
2543        END IF
2544      END DO
2546 !-----------------------------------------------------------------------
2547 !  Set warning message if wif_fire_inj for Thompson-MP-Aero (mp_physics=28)
2548 !  is turned on when no PBL scheme is active
2549 !-----------------------------------------------------------------------
2550      DO i = 1, model_config_rec % max_dom
2551        IF ( model_config_rec%mp_physics(i) .EQ. THOMPSONAERO .AND. model_config_rec%wif_fire_emit) THEN
2552          IF ( model_config_rec%bl_pbl_physics(i) .EQ. 0  ) THEN
2553            wrf_err_message = '--- WARNING: PBL scheme not active but wif_fire_inj=1 for mp_physics=28 '
2554            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2555          END IF
2556        END IF
2557      END DO
2559 !-----------------------------------------------------------------------
2560 ! Stop the model if full_khain_lynn or mp_physics = 32 is selected
2561 !-----------------------------------------------------------------------
2562       DO i = 1, model_config_rec % max_dom
2563          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2564          IF ( model_config_rec%mp_physics(i) .eq. full_khain_lynn) THEN
2565               oops = oops + 1
2566          wrf_err_message = '--- ERROR: full bin spectral microphysics should not be used '
2567          CALL wrf_message ( wrf_err_message )
2568          wrf_err_message = '--- ERROR: use fast version instead (mp_physics=30)'
2569          CALL wrf_message ( wrf_err_message )
2570          count_fatal_error = count_fatal_error + 1
2571          END IF
2572       ENDDO      ! Loop over domains
2574 !-----------------------------------------------------------------------
2575 !  DJW Check that we're not using ndown and vertical nesting.
2576 !-----------------------------------------------------------------------
2577      DO i=1,model_config_rec%max_dom
2578        IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2579        IF ((model_config_rec%vert_refine_method(i) .NE. 0) .AND. (model_config_rec%vert_refine_fact .NE. 1)) THEN
2580          wrf_err_message = '--- ERROR: vert_refine_fact is ndown specific and cannot be used with vert_refine_method, and vice versa.'
2581          CALL wrf_debug ( 1, wrf_err_message )
2582        ENDIF
2583      ENDDO
2585 !-----------------------------------------------------------------------
2586 !  DJW Check that only one type of vertical nesting is enabled.
2587 !-----------------------------------------------------------------------
2588      DO i=1,model_config_rec%max_dom
2589        IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2590        IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2591          DO j=1,model_config_rec%max_dom
2592            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
2593              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.'
2594               CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2595               count_fatal_error = count_fatal_error + 1
2596            ENDIF
2597          ENDDO
2598        ENDIF
2599      ENDDO
2601 !-----------------------------------------------------------------------
2602 !  DJW Check that e_vert is the same for nested domains not using
2603 !  vertical nesting. Don't do this check if we're using ndown.
2604 !-----------------------------------------------------------------------
2605       IF ((model_config_rec%max_dom .GT. 1) .AND. (model_config_rec%vert_refine_fact .EQ. 1)) THEN
2606         DO i=1,model_config_rec%max_dom
2607           IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2608           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
2609             DO j=1,model_config_rec%max_dom
2610               IF ((i .NE. j) .AND. (model_config_rec%parent_id(i) .EQ. model_config_rec%grid_id(j))) THEN
2611                 IF (model_config_rec%e_vert(i) .NE. model_config_rec%e_vert(j)) THEN
2612                   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.'
2613                   CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2614                   count_fatal_error = count_fatal_error + 1
2615                 ENDIF
2616               ENDIF
2617             ENDDO
2618           ENDIF
2619         ENDDO
2620       ENDIF
2622 !-----------------------------------------------------------------------
2623 !  Check that vertical levels are defined in a logical way.
2624 !  DJW Check that domains without a parent do not have vertical
2625 !  nesting enabled.
2626 !-----------------------------------------------------------------------
2627       DO i=1,model_config_rec%max_dom
2628         IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2629         IF ((model_config_rec%parent_id(i) .EQ. 0) .OR. (model_config_rec%parent_id(i) .EQ. model_config_rec%grid_id(i))) THEN
2630           IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2631             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.'
2632             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2633             count_fatal_error = count_fatal_error + 1
2634           ENDIF
2635         ENDIF
2636       ENDDO
2638 !-----------------------------------------------------------------------
2639 !  DJW Check that we've got appropriate e_vert for integer refinement.
2640 !-----------------------------------------------------------------------
2641       DO i = 1, model_config_rec % max_dom
2642         IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2643         IF (model_config_rec%vert_refine_method(i) .EQ. 1) THEN
2644           j = model_config_rec%parent_id(i)
2645           IF (MOD(model_config_rec%e_vert(i)-1, model_config_rec%e_vert(j)-1) .NE. 0) THEN
2646             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."
2647             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2648             count_fatal_error = count_fatal_error + 1
2649           ENDIF
2650         ENDIF
2651       ENDDO
2653 !-----------------------------------------------------------------------
2654 !   Check that max_ts_level is smaller than the number of half levels
2655 !-----------------------------------------------------------------------
2656       IF ( model_config_rec % max_ts_level .gt. model_config_rec %e_vert(1)-1 )  then
2657         wrf_err_message = ' max_ts_level must be <= number of znu half layers '
2658         CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2659         wrf_err_message = ' max_ts_level is reset to the number of znu half layers '
2660         CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2661         model_config_rec % max_ts_level = model_config_rec %e_vert(1)-1
2662       ENDIF
2664 !-----------------------------------------------------------------------
2665 !  Consistency checks between vertical refinement and radiation
2666 !  scheme selection.  For "choose any vertical levels" for the nest,
2667 !  only option 1 (RRTM/Dudhia) or option 4 (RRTMG) are eligible.
2668 !-----------------------------------------------------------------------
2669       DO i = 2, model_config_rec % max_dom
2670         IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2671         IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2672           IF ( ( ( model_config_rec%ra_lw_physics(i) .EQ. 0                   ) .OR. &
2673                  ( model_config_rec%ra_lw_physics(i) .EQ. RRTMSCHEME          ) .OR. &
2674                  ( model_config_rec%ra_lw_physics(i) .EQ. RRTMG_LWSCHEME      ) ) .AND. &
2675                ( ( model_config_rec%ra_sw_physics(i) .EQ. 0                   ) .OR. &
2676                  ( model_config_rec%ra_sw_physics(i) .EQ. SWRADSCHEME         ) .OR. &
2677                  ( model_config_rec%ra_sw_physics(i) .EQ. RRTMG_SWSCHEME      ) ) ) THEN
2678              !  We are OK, I just hate writing backwards / negative / convoluted if tests
2679              !  that are not easily comprehensible.
2680           ELSE
2681             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)'
2682             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2683             count_fatal_error = count_fatal_error + 1
2684           END IF
2685         END IF
2686       END DO
2688 !-----------------------------------------------------------------------
2689 !  Consistency checks for vertical refinement:
2690 !  feedback has to be turned off
2691 !-----------------------------------------------------------------------
2692       oops = 0 
2693       DO i = 2, model_config_rec % max_dom
2694         IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2695         IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2696           IF ( model_config_rec%feedback .NE. 0 ) THEN
2697             oops = oops + 1
2698           END IF
2699         END IF
2700       END DO
2702       IF ( oops .GT. 0 ) THEN
2703         wrf_err_message = '--- ERROR: vert_refine_method=2 only works with feedback = 0 '
2704         CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2705         count_fatal_error = count_fatal_error + 1
2706       END IF
2708 !-----------------------------------------------------------------------
2709 !  Consistency checks for vertical refinement:
2710 !  rebalance must be set to 1 
2711 !-----------------------------------------------------------------------
2712       oops = 0 
2713       DO i = 2, model_config_rec % max_dom
2714         IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2715         IF (model_config_rec%vert_refine_method(i) .NE. 0) THEN
2716           IF ( model_config_rec%rebalance .NE. 1 ) THEN
2717             oops = oops + 1
2718           END IF
2719         END IF
2720       END DO
2722       IF ( oops .GT. 0 ) THEN
2723         wrf_err_message = '--- ERROR: vert_refine_method=2 only works with rebalance=1 '
2724         CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2725         count_fatal_error = count_fatal_error + 1
2726       END IF
2728 !-----------------------------------------------------------------------
2729 ! This WRF version does not support trajectories on a global domain
2730 !-----------------------------------------------------------------------
2731       IF (  model_config_rec % polar(1) .AND. &
2732             model_config_rec % fft_filter_lat .LT. 90. .AND. &
2733             model_config_rec % traj_opt .NE. 0 ) THEN
2734          CALL wrf_debug ( 0, '--- ERROR: Trajectories not supported on global domain' )
2735          count_fatal_error = count_fatal_error + 1
2736       END IF
2738 !-----------------------------------------------------------------------
2739 ! If the user did not specify a global setting in the lateral BC
2740 ! portion of the namelist file (polar), but the distance around the
2741 ! equator is approximately equal to the entire globe, then it is likely
2742 ! that the user probably forgot to flip that polar switch on.
2743 !-----------------------------------------------------------------------
2744       lon_extent_is_global = .FALSE.
2745       IF ( ABS ( model_config_rec % e_we(1) * model_config_rec % dx(1) - 2. * piconst / reradius ) .LT. model_config_rec % dx(1) ) THEN
2746          lon_extent_is_global = .TRUE.
2747       END IF
2749       lat_extent_is_global = .FALSE.
2750       IF ( ABS ( model_config_rec % e_sn(1) * model_config_rec % dy(1) -      piconst / reradius ) .LT. model_config_rec % dy(1) ) THEN
2751          lat_extent_is_global = .TRUE.
2752       END IF
2754       IF ( ( .NOT. model_config_rec % polar(1) ) .AND. &
2755            ( lon_extent_is_global .AND. lat_extent_is_global ) ) THEN
2756          CALL wrf_debug ( 0, '--- ERROR: Domain size is global, set &bdy_control polar=.TRUE.' )
2757          count_fatal_error = count_fatal_error + 1
2758       END IF
2760 !-----------------------------------------------------------------------
2761 !  Remapping namelist variables for gridded and surface fdda to aux streams 9 and 10.
2762 !  Relocated here so that the remappings are after checking the namelist for inconsistencies.
2763 !-----------------------------------------------------------------------
2765 # include "../dyn_em/namelist_remappings_em.h"
2767 #endif
2769 #if (EM_CORE == 1)
2770 !-----------------------------------------------------------------------
2771 !  For the real program (ARW only), check that the vertical interpolation options
2772 !  selected by the user are consistent.
2773 !  1. If the user has turned-off using the surface level, do not allow the force
2774 !     option to select how many layers the surface is to be used through.
2775 !  2. If the user has turned-off using the surface level, do not allow the
2776 !     lowest level from surface option to be activated.
2777 !-----------------------------------------------------------------------
2779       IF ( model_config_rec % use_wps_input .EQ. 1 ) THEN
2780          IF ( ( .NOT. model_config_rec % use_surface )  .AND. &
2781               ( model_config_rec % force_sfc_in_vinterp .GT. 0 ) ) THEN
2782             wrf_err_message = '--- NOTE: Inconsistent vertical interpolation settings in program real.'
2783             CALL wrf_debug ( 1, wrf_err_message )
2784             wrf_err_message = '--- NOTE: With use_surface=F, automatically setting force_sfc_in_vinterp=0.'
2785             CALL wrf_debug ( 1, wrf_err_message )
2786             model_config_rec % force_sfc_in_vinterp = 0
2787          END IF
2788          IF ( ( .NOT. model_config_rec % use_surface )  .AND. &
2789               ( model_config_rec % lowest_lev_from_sfc ) ) THEN
2790             wrf_err_message = '--- NOTE: Inconsistent vertical interpolation settings in program real.'
2791             CALL wrf_debug ( 1, wrf_err_message )
2792             wrf_err_message = '--- NOTE: With use_surface=F, automatically setting lowest_lev_from_sfc=F.'
2793             CALL wrf_debug ( 1, wrf_err_message )
2794             model_config_rec % lowest_lev_from_sfc = .FALSE.
2795          END IF
2796       END IF
2797 #endif
2799 #if (EM_CORE == 1 && WRFPLUS == 1 )
2800       IF ( ( model_config_rec%jcdfi_use ).AND. &
2801            ( model_config_rec%jcdfi_diag .NE. 1 ) ) THEN
2802          wrf_err_message = '--- ERROR: If jcdfi_use = 1, then jcdfi_diag must also = 1 '
2803          CALL wrf_message ( wrf_err_message )
2804          wrf_err_message = '--- Change jcdfi_diag in namelist.input '
2805          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2806          count_fatal_error = count_fatal_error + 1
2807       END IF
2808       ! derived namelist for packaged a_/g_ variables
2809       model_config_rec%mp_physics_plus = 0
2810       DO i = 1, model_config_rec % max_dom
2811          model_config_rec%mp_physics_plus(i) = model_config_rec%mp_physics(i)
2812       ENDDO
2813       model_config_rec%cu_used_plus = 0
2814       DO i = 1, model_config_rec % max_dom
2815          IF ( model_config_rec%cu_physics(i) .NE. NOCUSCHEME ) THEN
2816             model_config_rec%cu_used_plus = 1
2817          END IF
2818       ENDDO
2819       model_config_rec%shcu_used_plus = 0
2820       DO i = 1, model_config_rec % max_dom
2821          IF ( model_config_rec%shcu_physics(i) .NE. NOSHCUSCHEME ) THEN
2822             model_config_rec%shcu_used_plus = 1
2823          END IF
2824       ENDDO
2825 #endif
2827 #if (EM_CORE == 1)
2828 # if( BUILD_SBM_FAST != 1)
2829 !-----------------------------------------------------------------------
2830 !  If the FAST SBM scheme is requested and it is not compiled, let the
2831 !  user know.
2832 !-----------------------------------------------------------------------
2834       IF ( model_config_rec % mp_physics(1) .EQ. FAST_KHAIN_LYNN_SHPUND ) THEN
2835          wrf_err_message = '--- ERROR: FAST SBM scheme must be built with a default compile-time flag'
2836          CALL wrf_message ( wrf_err_message )
2837          wrf_err_message = '--- ERROR: Run ./clean -a, ./configure, ./compile scripts again'
2838          CALL wrf_message ( wrf_err_message )
2839          count_fatal_error = count_fatal_error + 1
2840       END IF
2841 # endif
2842 #endif
2844 !-----------------------------------------------------------------------
2845 !  If the RRTMG FAST schemes are requested, check that the code with
2846 !  built to use them.
2847 !-----------------------------------------------------------------------
2849 #if( BUILD_RRTMG_FAST != 1)
2850       IF ( ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME_FAST )  .OR. &
2851            ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME_FAST )  ) THEN
2852          wrf_err_message = '--- ERROR: RRTMG FAST schemes must be built with a default compile-time flag'
2853          CALL wrf_message ( wrf_err_message )
2854          wrf_err_message = '--- ERROR: Run ./clean -a, ./configure, ./compile scripts again'
2855          CALL wrf_message ( wrf_err_message )
2856          count_fatal_error = count_fatal_error + 1
2857       END IF
2858 #endif
2860 !-----------------------------------------------------------------------
2861 !  If the RRTMG KIAPS schemes are requested, check that the code with
2862 !  built to use them.
2863 !-----------------------------------------------------------------------
2865 #if( BUILD_RRTMK != 1)
2866       IF ( ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_LWSCHEME )  .OR. &
2867            ( model_config_rec % ra_sw_physics(1) .EQ. RRTMK_SWSCHEME )  ) THEN
2868          wrf_err_message = '--- ERROR: RRTMG-based KIAPS 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
2873       END IF
2874 #endif
2876 !-----------------------------------------------------------------------
2877 !  Set the namelist parameter o3input to 0 for the radiation schemes other
2878 !  than RRTMG_LWSCHEME and RRTMG_SWSCHEME.
2879 !-----------------------------------------------------------------------
2881       IF ( ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME )  .OR. &
2882            ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME )  .OR. &
2883            ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_LWSCHEME )  .OR. &
2884            ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_SWSCHEME )  .OR. &
2885            ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME_FAST )  .OR. &
2886            ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME_FAST )  ) THEN
2887          wrf_err_message = '--- NOTE: RRTMG radiation is used, namelist ' // &
2888                            'value for o3input (ozone input) is used '
2889          CALL wrf_debug ( 1, wrf_err_message )
2890       ELSE
2891          model_config_rec % o3input = 0
2892          wrf_err_message = '--- NOTE: RRTMG radiation is not used, setting:  ' // &
2893                            'o3input=0 to avoid data pre-processing'
2894          CALL wrf_debug ( 1, wrf_err_message )
2895       END IF
2897 !-----------------------------------------------------------------------
2898 !  Consistency checks between eclipse option and shortwave radiation
2899 !  scheme selection. Eclipse option only applies to
2900 !  RRTMG_SWSCHEME, SWRADSCHEME, GSFCSWSCHEME and GODDARDSWSCHEME
2901 !-----------------------------------------------------------------------
2902       DO i = 1, model_config_rec % max_dom
2903         IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2904          IF ( model_config_rec%ra_sw_eclipse == 1 ) THEN
2905           IF ( ( model_config_rec%ra_sw_physics(i) .EQ. RRTMG_SWSCHEME      ) .OR. &
2906                ( model_config_rec%ra_sw_physics(i) .EQ. SWRADSCHEME         ) .OR. &
2907                ( model_config_rec%ra_sw_physics(i) .EQ. GSFCSWSCHEME        ) .OR. &
2908                ( model_config_rec%ra_sw_physics(i) .EQ. GODDARDSWSCHEME     ) ) THEN
2909              !  We are OK, these sw radiation schemes have eclipse physics
2910           ELSE
2911             wrf_err_message = '--- ERROR: ra_sw_eclipse=1 only works with ra_sw_physics=1 (Dudhia), ' // &
2912                               '=2 (Old Goddard), =4 (RRTMG) and =5 (new Goddard) '
2913             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2914             count_fatal_error = count_fatal_error + 1
2915           END IF
2916          END IF
2917       END DO
2919 #if (WRF_CHEM == 1 && WRF_KPP == 1 )
2920 !-----------------------------------------------------------------------
2921 ! Check for consistent chem_opt and irr_opt
2922 !-----------------------------------------------------------------------
2923       DO i = 1, model_config_rec % max_dom
2924          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2925          IF ( model_config_rec%irr_opt(i) > 0 .and. &
2926               (model_config_rec%chem_opt(i) /= mozcart_kpp .and. &
2927                model_config_rec%chem_opt(i) /= t1_mozcart_kpp .and. &
2928                model_config_rec%chem_opt(i) /= mozart_mosaic_4bin_kpp .and. &
2929                model_config_rec%chem_opt(i) /= mozart_mosaic_4bin_aq_kpp ) ) THEN
2930            wrf_err_message = '--- ERROR: IRR diagnostics can only be used with the following chem_opt settings:'
2931            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2932            wrf_err_message = '    MOZCART_KPP, T1_MOZCART_KPP, MOZART_MOSAIC_4BIN_KPP, MOZART_MOSAIC_4BIN_AQ_KPP'
2933            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2934            write(wrf_err_message,'(''    chem_opt = '',i3,'', '',i3,'', '',i3,'', or '',i3)') &
2935                  MOZCART_KPP, T1_MOZCART_KPP, MOZART_MOSAIC_4BIN_KPP, MOZART_MOSAIC_4BIN_AQ_KPP 
2936            CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2937            count_fatal_error = count_fatal_error + 1
2938          END IF
2939       ENDDO
2940 #endif
2942 #if ( ( EM_CORE == 1) && ( defined(DM_PARALLEL) )&& ( ! defined(STUBMPI) ) )
2943 !-----------------------------------------------------------------------
2944 ! Did the user ask for too many MPI tasks, or are those tasks poorly distributed.
2945 !-----------------------------------------------------------------------
2947       oops = 0
2948       DO i = 1, model_config_rec % max_dom
2949          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
2950          IF ( ( model_config_rec % e_we(i) /  model_config_rec % nproc_x .LT. 10 ) .OR. &
2951               ( model_config_rec % e_sn(i) /  model_config_rec % nproc_y .LT. 10 ) ) THEN
2952             WRITE ( wrf_err_message , * ) 'For domain ',i,', the domain size is too small for this many processors, ', & 
2953                                           'or the decomposition aspect ratio is poor.'
2954             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2955             WRITE ( wrf_err_message , * ) 'Minimum decomposed computational patch size, either x-dir or y-dir, is 10 grid cells.'
2956             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2957             WRITE ( wrf_err_message , fmt='(a,i5,a,i4,a,i4)' ) &
2958                                           'e_we = ', model_config_rec % e_we(i),', nproc_x = ',model_config_rec % nproc_x, &
2959                                           ', with cell width in x-direction = ', &
2960                                           model_config_rec % e_we(i) /  model_config_rec % nproc_x
2961             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2962             WRITE ( wrf_err_message , fmt='(a,i5,a,i4,a,i4)' ) &
2963                                           'e_sn = ', model_config_rec % e_sn(i),', nproc_y = ',model_config_rec % nproc_y, &
2964                                           ', with cell width in y-direction = ', &
2965                                           model_config_rec % e_sn(i) /  model_config_rec % nproc_y
2966             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2967             wrf_err_message = '--- ERROR: Reduce the MPI rank count, or redistribute the tasks.'
2968             CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2969             oops = oops + 1
2970          END IF
2971       ENDDO
2972       IF ( oops .GT. 0 ) THEN
2973          count_fatal_error = count_fatal_error + 1
2974       END IF
2975 #endif
2980 !---------------------------------------------------------------------
2981 !  The "clean" atmosphere radiative flux diagnostics can only be used 
2982 !     with WRF-Chem.
2983 !---------------------------------------------------------------------
2985       IF ( model_config_rec%clean_atm_diag > 0 ) THEN
2987 #if (WRF_CHEM != 1)
2988          wrf_err_message = '--- NOTE: "Clean" atmosphere diagnostics can only be used in WRF-Chem' 
2989          CALL wrf_debug ( 0, TRIM( wrf_err_message ) )
2990          model_config_rec%calc_clean_atm_diag = 0
2991 #else
2992          model_config_rec%calc_clean_atm_diag = 1
2993 #endif
2995       ENDIF
2997 !-----------------------------------------------------------------------
2998 !  MUST BE AFTER ALL OF THE PHYSICS CHECKS.
2999 !-----------------------------------------------------------------------
3001       IF ( count_fatal_error .GT. 0 ) THEN
3002          WRITE (wrf_err_message, FMT='(A,I6, A)') 'NOTE:  ', count_fatal_error, &
3003                                             ' namelist settings are wrong. Please check and reset these options'
3004          CALL wrf_error_fatal (  wrf_err_message  )
3005       END IF
3007    END SUBROUTINE check_nml_consistency
3009 !=======================================================================
3011    SUBROUTINE setup_physics_suite
3013 !<DESCRIPTION>
3015 ! Based on the selection of physics suite provided in the namelist, sets the
3016 ! values of other namelist options (mp_physics, cu_physics, ra_lw_physics,
3017 ! ra_sw_physics, bl_pbl_physics, sf_sfclay_physics, and sf_surface_physics)
3018 ! to reflect that suite.
3020 !</DESCRIPTION>
3022       USE module_domain, ONLY : change_to_lower_case
3024       IMPLICIT NONE
3025 #if ( EM_CORE == 1 )
3027       INTEGER :: i
3028       INTEGER :: max_dom
3029       LOGICAL :: have_mods
3030       INTEGER, DIMENSION( max_domains ) :: orig_mp_physics, orig_cu_physics, orig_ra_lw_physics, orig_ra_sw_physics, &
3031                                            orig_bl_pbl_physics, orig_sf_sfclay_physics, orig_sf_surface_physics
3032       CHARACTER, DIMENSION( max_domains ) :: modified_mp_option, modified_cu_option, modified_ra_lw_option, modified_ra_sw_option, &
3033                                              modified_bl_pbl_option, modified_sf_sfclay_option, modified_sf_surface_option
3034       CHARACTER (LEN=256) :: physics_suite_lowercase
3035       CHARACTER (LEN=32) :: formatstring
3037       !
3038       ! Initialize the debug level so that it can be used in the namelist testing.
3039       ! wrf_debug_level is a global value in module_wrf_error.
3040       !
3042       wrf_debug_level = model_config_rec%debug_level
3044       max_dom = model_config_rec % max_dom
3046       !
3047       ! Save physics selections as given by the user to later determine if the
3048       ! user has overridden any options
3049       !
3050       modified_mp_option(1:max_dom) = ' '
3051       orig_mp_physics(1:max_dom) = model_config_rec % mp_physics(1:max_dom)
3053       modified_cu_option(1:max_dom) = ' '
3054       orig_cu_physics(1:max_dom) = model_config_rec % cu_physics(1:max_dom)
3056       modified_ra_lw_option(1:max_dom) = ' '
3057       orig_ra_lw_physics(1:max_dom) = model_config_rec % ra_lw_physics(1:max_dom)
3059       modified_ra_sw_option(1:max_dom) = ' '
3060       orig_ra_sw_physics(1:max_dom) = model_config_rec % ra_sw_physics(1:max_dom)
3062       modified_bl_pbl_option(1:max_dom) = ' '
3063       orig_bl_pbl_physics(1:max_dom) = model_config_rec % bl_pbl_physics(1:max_dom)
3065       modified_sf_sfclay_option(1:max_dom) = ' '
3066       orig_sf_sfclay_physics(1:max_dom) = model_config_rec % sf_sfclay_physics(1:max_dom)
3068       modified_sf_surface_option(1:max_dom) = ' '
3069       orig_sf_surface_physics(1:max_dom) = model_config_rec % sf_surface_physics(1:max_dom)
3071       CALL change_to_lower_case(trim(model_config_rec % physics_suite), physics_suite_lowercase)
3073       !
3074       ! If physics suite is 'none', we can return early
3075       !
3076       IF ( trim(physics_suite_lowercase) == 'none' ) THEN
3077          wrf_err_message = '*************************************'
3078          call wrf_debug ( 1, wrf_err_message )
3079          wrf_err_message = 'No physics suite selected.'
3080          call wrf_debug ( 1, wrf_err_message )
3081          wrf_err_message = 'Physics options will be used directly from the namelist.'
3082          call wrf_debug ( 1, wrf_err_message )
3083          wrf_err_message = '*************************************'
3084          call wrf_debug ( 1, wrf_err_message )
3085          RETURN
3086       END IF
3088       CALL wrf_message ('*************************************')
3089       CALL wrf_message ('Configuring physics suite '''//trim(physics_suite_lowercase)//'''')
3090       CALL wrf_message ('')
3092       !
3093       ! Set options based on the suite selection
3094       !
3095       SELECT CASE ( trim(physics_suite_lowercase) )
3097       !
3098       ! CONUS suite
3099       !
3100       CASE ('conus')
3101          DO i = 1, max_dom
3103             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3104             IF ( model_config_rec % cu_physics(i) == -1 ) model_config_rec % cu_physics(i) = TIEDTKESCHEME               ! Tiedtke
3105             IF ( model_config_rec % mp_physics(i) == -1 ) model_config_rec % mp_physics(i) = THOMPSON                    ! Thompson
3106             IF ( model_config_rec % ra_lw_physics(i) == -1 ) model_config_rec % ra_lw_physics(i) = RRTMG_LWSCHEME        ! RRTMG LW
3107             IF ( model_config_rec % ra_sw_physics(i) == -1 ) model_config_rec % ra_sw_physics(i) = RRTMG_SWSCHEME        ! RRTMG SW
3108             IF ( model_config_rec % bl_pbl_physics(i) == -1 ) model_config_rec % bl_pbl_physics(i) = MYJPBLSCHEME        ! MYJ
3109             IF ( model_config_rec % sf_sfclay_physics(i) == -1 ) model_config_rec % sf_sfclay_physics(i) = MYJSFCSCHEME  ! MYJ
3110             IF ( model_config_rec % sf_surface_physics(i) == -1 ) model_config_rec % sf_surface_physics(i) = LSMSCHEME   ! Noah
3112          END DO
3114       !
3115       ! Tropical suite
3116       !
3117       CASE ('tropical')
3118          DO i = 1, max_dom
3120             IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3121             IF ( model_config_rec % cu_physics(i) == -1 ) model_config_rec % cu_physics(i) = NTIEDTKESCHEME              ! New Tiedtke
3122             IF ( model_config_rec % mp_physics(i) == -1 ) model_config_rec % mp_physics(i) = WSM6SCHEME                  ! WSM6
3123             IF ( model_config_rec % ra_lw_physics(i) == -1 ) model_config_rec % ra_lw_physics(i) = RRTMG_LWSCHEME        ! RRTMG LW
3124             IF ( model_config_rec % ra_sw_physics(i) == -1 ) model_config_rec % ra_sw_physics(i) = RRTMG_SWSCHEME        ! RRTMG SW
3125             IF ( model_config_rec % bl_pbl_physics(i) == -1 ) model_config_rec % bl_pbl_physics(i) = YSUSCHEME           ! YSU
3126             IF ( model_config_rec % sf_sfclay_physics(i) == -1 ) model_config_rec % sf_sfclay_physics(i) = SFCLAYSCHEME  ! MM5
3127             IF ( model_config_rec % sf_surface_physics(i) == -1 ) model_config_rec % sf_surface_physics(i) = LSMSCHEME   ! Noah
3129          END DO
3131       CASE DEFAULT
3132          CALL wrf_error_fatal ( 'Unrecognized physics suite' )
3134       END SELECT
3136       WRITE (formatstring, '(A,I3,A)') '(A21,', max_dom, '(I6,A1))'
3138       !
3139       ! Print microphysics options
3140       !
3141       WHERE (model_config_rec % mp_physics(1:max_dom) == orig_mp_physics(1:max_dom)) modified_mp_option(1:max_dom) = '*'
3142       WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'mp_physics: ', &
3143                                                     (model_config_rec % mp_physics(i), modified_mp_option(i), i=1,max_dom)
3144       CALL wrf_message (wrf_err_message)
3146       !
3147       ! Print cumulus options
3148       !
3149       WHERE (model_config_rec % cu_physics(1:max_dom) == orig_cu_physics(1:max_dom)) modified_cu_option(1:max_dom) = '*'
3150       WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'cu_physics: ', &
3151                                                     (model_config_rec % cu_physics(i), modified_cu_option(i), i=1,max_dom)
3152       CALL wrf_message (wrf_err_message)
3154       !
3155       ! Print LW radiation options
3156       !
3157       WHERE (model_config_rec % ra_lw_physics(1:max_dom) == orig_ra_lw_physics(1:max_dom)) modified_ra_lw_option(1:max_dom) = '*'
3158       WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'ra_lw_physics: ', &
3159                                                     (model_config_rec % ra_lw_physics(i), modified_ra_lw_option(i), i=1,max_dom)
3160       CALL wrf_message (wrf_err_message)
3162       !
3163       ! Print SW radiation options
3164       !
3165       WHERE (model_config_rec % ra_sw_physics(1:max_dom) == orig_ra_sw_physics(1:max_dom)) modified_ra_sw_option(1:max_dom) = '*'
3166       WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'ra_sw_physics: ', &
3167                                                     (model_config_rec % ra_sw_physics(i), modified_ra_sw_option(i), i=1,max_dom)
3168       CALL wrf_message (wrf_err_message)
3170       !
3171       ! Print boundary layer options
3172       !
3173       WHERE (model_config_rec % bl_pbl_physics(1:max_dom) == orig_bl_pbl_physics(1:max_dom)) modified_bl_pbl_option(1:max_dom) = '*'
3174       WRITE (wrf_err_message, FMT=TRIM(formatstring)) 'bl_pbl_physics: ', &
3175                                                     (model_config_rec % bl_pbl_physics(i), modified_bl_pbl_option(i), i=1,max_dom)
3176       CALL wrf_message (wrf_err_message)
3178       !
3179       ! Print surface layer options
3180       !
3181       WHERE (model_config_rec % sf_sfclay_physics(1:max_dom) == orig_sf_sfclay_physics(1:max_dom)) &
3182             modified_sf_sfclay_option(1:max_dom) = '*'
3183       WRITE (wrf_err_message, FMT=TRIM(formatstring)) &
3184             'sf_sfclay_physics: ', (model_config_rec % sf_sfclay_physics(i), modified_sf_sfclay_option(i), i=1,max_dom)
3185       CALL wrf_message (wrf_err_message)
3187       !
3188       ! Print surface options
3189       !
3190       WHERE (model_config_rec % sf_surface_physics(1:max_dom) == orig_sf_surface_physics(1:max_dom)) &
3191             modified_sf_surface_option(1:max_dom) = '*'
3192       WRITE (wrf_err_message, FMT=TRIM(formatstring)) &
3193             'sf_surface_physics: ', (model_config_rec % sf_surface_physics(i), modified_sf_surface_option(i), i=1,max_dom)
3194       CALL wrf_message (wrf_err_message)
3196       !
3197       ! Print footnote if any physics schemes were overridden by the user
3198       !
3199       have_mods = ANY (modified_mp_option(1:max_dom) == '*') &
3200              .OR. ANY (modified_cu_option(1:max_dom) == '*') &
3201              .OR. ANY (modified_ra_lw_option(1:max_dom) == '*') &
3202              .OR. ANY (modified_ra_sw_option(1:max_dom) == '*') &
3203              .OR. ANY (modified_bl_pbl_option(1:max_dom) == '*') &
3204              .OR. ANY (modified_sf_sfclay_option(1:max_dom) == '*') &
3205              .OR. ANY (modified_sf_surface_option(1:max_dom) == '*')
3207       IF (have_mods) THEN
3208          CALL wrf_message ('')
3209          CALL wrf_message ('(* = option overrides suite setting)')
3210       END IF
3212       CALL wrf_message ('*************************************')
3214 #endif
3216    END SUBROUTINE setup_physics_suite
3218 !=======================================================================
3220    SUBROUTINE set_physics_rconfigs
3222 !<DESCRIPTION>
3224 ! Some derived rconfig entries need to be set based on the value of other,
3225 ! non-derived entries before package-dependent memory allocation takes place.
3226 ! This works around depending on the user to set these specific settings in the
3227 ! namelist.
3229 !</DESCRIPTION>
3231       IMPLICIT NONE
3233       INTEGER :: numsoiltemp , nummosaictemp
3234       INTEGER :: i
3237 !-----------------------------------------------------------------------
3238 ! Set the namelist urban dimensions if sf_urban_physics > 0  
3239 !-----------------------------------------------------------------------
3241       IF ( any(model_config_rec%sf_urban_physics > 0 ) ) THEN
3242       
3243          model_config_rec%urban_map_zrd = model_config_rec%num_urban_ndm * &
3244                                           model_config_rec%num_urban_nwr * &
3245                                           model_config_rec%num_urban_nz
3246          model_config_rec%urban_map_zwd = model_config_rec%num_urban_ndm * &
3247                                           model_config_rec%num_urban_nwr * &
3248                                           model_config_rec%num_urban_nz  * &
3249                                           model_config_rec%num_urban_nbui
3250          model_config_rec%urban_map_gd  = model_config_rec%num_urban_ndm * &
3251                                           model_config_rec%num_urban_ng
3252          model_config_rec%urban_map_zd  = model_config_rec%num_urban_ndm * &
3253                                           model_config_rec%num_urban_nz  * &
3254                                           model_config_rec%num_urban_nbui
3255          model_config_rec%urban_map_zdf = model_config_rec%num_urban_ndm * &
3256                                           model_config_rec%num_urban_nz 
3257          model_config_rec%urban_map_bd  = model_config_rec%num_urban_nz  * &
3258                                           model_config_rec%num_urban_nbui
3259          model_config_rec%urban_map_wd  = model_config_rec%num_urban_ndm * &
3260                                           model_config_rec%num_urban_nz  * &
3261                                           model_config_rec%num_urban_nbui
3262          model_config_rec%urban_map_gbd = model_config_rec%num_urban_ndm * &
3263                                           model_config_rec%num_urban_ngb * &
3264                                           model_config_rec%num_urban_nbui
3265          model_config_rec%urban_map_fbd = model_config_rec%num_urban_ndm       * &
3266                                           (model_config_rec%num_urban_nz - 1)  * &
3267                                           model_config_rec%num_urban_nf        * &
3268                                           model_config_rec%num_urban_nbui
3269         model_config_rec%urban_map_zgrd = model_config_rec%num_urban_ndm * &
3270                                           model_config_rec%num_urban_ngr  * &
3271                                           model_config_rec%num_urban_nz
3273       END IF     
3274       
3275 !-----------------------------------------------------------------------
3276 ! Set the namelist mosaic_cat_soil parameter for the Noah-mosaic  scheme if sf_surface_mosaic == 1.  
3277 !-----------------------------------------------------------------------
3279       IF ( model_config_rec % sf_surface_mosaic .EQ. 1 ) THEN
3280       
3281       numsoiltemp = model_config_rec % num_soil_layers
3282       nummosaictemp = model_config_rec % mosaic_cat
3283       
3284          model_config_rec % mosaic_cat_soil = numsoiltemp * nummosaictemp
3286          wrf_err_message = '--- NOTE: Noah-mosaic is in use, setting:  ' // &
3287                            'mosaic_cat_soil = mosaic_cat * num_soil_layers'
3288          CALL wrf_debug ( 1, wrf_err_message )
3290       END IF     
3291       
3292 #if (DA_CORE != 1)
3293 !-----------------------------------------------------------------------
3294 ! How big to allocate random seed arrays.
3295 !-----------------------------------------------------------------------
3297       CALL RANDOM_SEED ( SIZE = model_config_rec % seed_dim )
3299 !-----------------------------------------------------------------------
3300 ! If this is a WRF run with polar boundary conditions, then this is a
3301 ! global domain. A global domain needs to have the FFT arrays allocated.
3302 !-----------------------------------------------------------------------
3304       model_config_rec % fft_used = 0
3305       IF ( ( model_config_rec % polar(1) ) .AND. &
3306            ( model_config_rec % fft_filter_lat .LT. 90. ) ) THEN
3307          model_config_rec % fft_used = 1
3308       END IF
3310 !-----------------------------------------------------------------------
3311 ! Need to know if this run has aercu_opt set to either 1 or 2,
3312 ! so that we can set a derived namelist for packaging arrays.
3313 !-----------------------------------------------------------------------
3315       model_config_rec % aercu_used = 0
3316       IF ( model_config_rec %aercu_opt .GT. 0 ) THEN
3317          model_config_rec % aercu_used = 1
3318       END IF
3320 !-----------------------------------------------------------------------
3321 ! If any CAM scheme is turned on, then there are a few shared variables.
3322 ! These need to be allocated when any CAM scheme is active.
3323 !-----------------------------------------------------------------------
3325 #if ( (EM_CORE == 1) && (WRF_CHEM != 1) )
3326       model_config_rec % cam_used = 0
3327       DO i = 1, model_config_rec % max_dom
3328          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3329          IF ( ( model_config_rec % mp_physics(i)     .EQ. CAMMGMPSCHEME   ) .OR. &
3330               ( model_config_rec % bl_pbl_physics(i) .EQ. CAMUWPBLSCHEME  ) .OR. &
3331               ( model_config_rec % shcu_physics(i)   .EQ. CAMUWSHCUSCHEME ) ) THEN
3332             model_config_rec % cam_used = 1
3333          END IF
3334       ENDDO
3336 #elif (WRF_CHEM == 1)
3337       model_config_rec % cam_used = 1
3338 #endif
3340 #endif
3342       
3343 !-----------------------------------------------------------------------
3344 ! Set the namelist parameters for the CAM radiation scheme if either
3345 ! ra_lw_physics = CAMLWSCHEME or ra_sw_physics = CAMSWSCHEME.  
3346 !-----------------------------------------------------------------------
3348       IF (( model_config_rec % ra_lw_physics(1) .EQ. CAMLWSCHEME ) .OR. &
3349           ( model_config_rec % ra_sw_physics(1) .EQ. CAMSWSCHEME )) THEN
3350          model_config_rec % paerlev = 29
3351          model_config_rec % levsiz = 59
3352          model_config_rec % cam_abs_dim1 = 4
3353          model_config_rec % cam_abs_dim2 = model_config_rec % e_vert(1)
3355          wrf_err_message = '--- NOTE: CAM radiation is in use, setting:  ' // &
3356                            'paerlev=29, levsiz=59, cam_abs_dim1=4, cam_abs_dim2=e_vert'
3357          CALL wrf_debug ( 1, wrf_err_message )
3359       END IF
3361 !-----------------------------------------------------------------------
3362 ! If a user requested to compute the radar reflectivity .OR. if this is
3363 ! one of the schemes that ALWAYS computes the radar reflectivity, then
3364 ! turn on the switch that says allocate the space for the refl_10cm array.
3365 !-----------------------------------------------------------------------
3367       DO i = 1, model_config_rec % max_dom
3368          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3369          IF ( ( model_config_rec % mp_physics(i) .EQ. MILBRANDT2MOM ) .OR. &
3370 #if (EM_CORE == 1)
3371               ( model_config_rec % mp_physics(i) .EQ. NSSL_2MOM     ) .OR. &
3372               ( model_config_rec % mp_physics(i) .EQ. NSSL_2MOMG    ) .OR. &
3373               ( model_config_rec % mp_physics(i) .EQ. NSSL_2MOMCCN  ) .OR. &
3374               ( model_config_rec % mp_physics(i) .EQ. NSSL_1MOM     ) .OR. &
3375               ( model_config_rec % mp_physics(i) .EQ. NSSL_1MOMLFO  ) .OR. &
3376 #endif
3377               ( model_config_rec % do_radar_ref  .EQ. 1             ) ) THEN
3378             model_config_rec % compute_radar_ref = 1
3379          END IF
3380       ENDDO
3382 !-----------------------------------------------------------------------
3383 ! If a user selected LOGICAL fire-related switches, convert those to
3384 ! INTEGER for the package allocation assignment required in the 
3385 ! registry file.
3386 !-----------------------------------------------------------------------
3388 #if (EM_CORE == 1)
3389       DO i = 1, model_config_rec % max_dom
3390          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3391          IF ( model_config_rec % fmoist_run(i) .EQV. .TRUE.  ) THEN
3392             model_config_rec % fmoisti_run(i) = 1
3393          ELSE 
3394             model_config_rec % fmoisti_run(i) = 0
3395          END IF
3396          IF ( model_config_rec % fmoist_interp(i) .EQV. .TRUE.  ) THEN
3397             model_config_rec % fmoisti_interp(i) = 1
3398          ELSE 
3399             model_config_rec % fmoisti_interp(i) = 0
3400          END IF
3401       ENDDO
3402 #endif
3404 !-----------------------------------------------------------------------
3405 ! If MYNN PBL is not used, set bl_mynn_edmf = 0 so that we don't get 
3406 ! additional output 
3407 !-----------------------------------------------------------------------
3409 #if (EM_CORE == 1)
3410       DO i = 1, model_config_rec % max_dom
3411          IF ( .NOT. model_config_rec % grid_allowed(i) ) CYCLE
3412          IF ( ( model_config_rec % bl_pbl_physics(i) .NE. MYNNPBLSCHEME2 ) .AND. &
3413               ( model_config_rec % bl_pbl_physics(i) .NE. MYNNPBLSCHEME3 ) ) THEN
3414             model_config_rec % bl_mynn_edmf = 0
3415          END IF
3416       ENDDO
3417 #endif
3419 !-----------------------------------------------------------------------
3420 ! Set the namelist parameters for the RRTMG radiation scheme if either
3421 ! ra_lw_physics or ra_sw_physics is set to one of the RRTMG schemes.
3422 !-----------------------------------------------------------------------
3424       IF (( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME      ) .OR. &
3425           ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME      ) .OR. &
3426           ( model_config_rec % ra_lw_physics(1) .EQ. RRTMK_LWSCHEME      ) .OR. &
3427           ( model_config_rec % ra_sw_physics(1) .EQ. RRTMK_SWSCHEME      ) .OR. &
3428           ( model_config_rec % ra_lw_physics(1) .EQ. RRTMG_LWSCHEME_FAST ) .OR. &
3429           ( model_config_rec % ra_sw_physics(1) .EQ. RRTMG_SWSCHEME_FAST )) THEN
3430          model_config_rec % levsiz = 59
3431          model_config_rec % alevsiz = 12
3432          model_config_rec % no_src_types = 6
3434          wrf_err_message = '--- NOTE: One of the RRTMG radiation schemes is in use, setting:  ' // &
3435                            'levsiz=59, alevsiz=12, no_src_types=6'
3436          CALL wrf_debug ( 1, wrf_err_message )
3438       END IF
3440 !-----------------------------------------------------------------------
3441 ! Set namelist parameter num_soil_levels depending on the value of
3442 ! sf_surface_physics
3443 !-----------------------------------------------------------------------
3445 #if (EM_CORE == 1)
3446       IF      (   model_config_rec % sf_surface_physics(1) .EQ. NOLSMSCHEME  ) THEN
3447          model_config_rec % num_soil_layers = 5
3448       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. SLABSCHEME   ) THEN
3449          model_config_rec % num_soil_layers = 5
3450       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. LSMSCHEME    ) THEN
3451          model_config_rec % num_soil_layers = 4
3452       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. NOAHMPSCHEME ) THEN
3453          model_config_rec % num_soil_layers = 4
3454       ELSE IF ( ( model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME ) .AND. &
3455                 ( model_config_rec % num_soil_layers .EQ. 6 ) ) THEN
3456          model_config_rec % num_soil_layers = 6
3457       ELSE IF ( ( model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME ) .AND. &
3458                 ( model_config_rec % num_soil_layers .EQ. 9 ) ) THEN
3459          model_config_rec % num_soil_layers = 9
3460       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME ) THEN
3461          model_config_rec % num_soil_layers = 6
3462       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. PXLSMSCHEME  ) THEN
3463          model_config_rec % num_soil_layers = 2
3464       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. CLMSCHEME    ) THEN
3465          model_config_rec % num_soil_layers = 10
3466       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. CTSMSCHEME    ) THEN
3467          ! Using 4 for the sake of the sea ice scheme
3468          model_config_rec % num_soil_layers = 4
3469       ELSE IF (   model_config_rec % sf_surface_physics(1) .EQ. SSIBSCHEME   ) THEN
3470          model_config_rec % num_soil_layers = 3
3471       ELSE
3472          CALL wrf_debug       ( 0 , '--- ERROR: Unknown sf_surface_physics has no associated number of soil levels' )
3473          WRITE (wrf_err_message, FMT='(A,I6)') '--- ERROR: sf_surface_physics = ' , model_config_rec % sf_surface_physics(1)
3474          CALL wrf_error_fatal ( TRIM(wrf_err_message) )
3475       END IF 
3476 #endif
3478       WRITE (wrf_err_message, FMT='(A,I6)') '--- NOTE: num_soil_layers has been set to ', &
3479                                              model_config_rec % num_soil_layers
3480       CALL wrf_debug ( 1, wrf_err_message )
3482    END SUBROUTINE set_physics_rconfigs
3484 !=======================================================================
3486    RECURSIVE SUBROUTINE get_moad_factor ( id, parent_id, parent_grid_ratio, max_dom, factor )
3487       IMPLICIT NONE
3488       INTEGER                     :: max_dom
3489       INTEGER, DIMENSION(max_dom) :: parent_id, parent_grid_ratio
3490       INTEGER                     :: factor, id
3491    
3492       IF ( id .EQ. 1 ) THEN
3493          RETURN
3494       ELSE
3495          factor = factor * parent_grid_ratio(id)
3496          CALL get_moad_factor ( parent_id(id), parent_id, parent_grid_ratio, max_dom, factor )
3497       END IF
3498    END  SUBROUTINE get_moad_factor
3500 !=======================================================================
3502    END MODULE module_check_a_mundo
3504 !=======================================================================