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