MODULE module_check_a_mundo USE module_state_description USE module_wrf_error USE module_configure IMPLICIT NONE CONTAINS SUBROUTINE check_nml_consistency IMPLICIT NONE INTEGER :: i, oops DO i = 2, model_config_rec % max_dom IF ( model_config_rec % sf_surface_physics(i) .NE. & model_config_rec % sf_surface_physics(i-1) ) THEN wrf_err_message = '--- ERROR: sf_surface_physics must be equal for all domains ' CALL wrf_message ( wrf_err_message ) wrf_err_message = '--- Fix sf_surface_physics in namelist.input ' CALL wrf_error_fatal3("<stdin>",67,& TRIM( wrf_err_message ) ) END IF ENDDO IF ( ( model_config_rec%fractional_seaice .EQ. 0 ).AND. & ( model_config_rec%tice2tsk_if2cold ) ) THEN wrf_err_message = '--- WARNING: You set tice2tsk_if2cold = .true., but fractional_seaice = 0' CALL wrf_message ( wrf_err_message ) wrf_err_message = '--- WARNING: tice2tsk_if2cold will have no effect on results.' CALL wrf_message ( wrf_err_message ) END IF DO i = 1, model_config_rec % max_dom IF ( ( model_config_rec%fine_input_stream(i) .NE. 0 ).AND. & ( model_config_rec%io_form_auxinput2 .EQ. 0 ) ) THEN wrf_err_message = '--- ERROR: If fine_input_stream /= 0, io_form_auxinput2 must be /= 0' CALL wrf_message ( wrf_err_message ) wrf_err_message = '--- Set io_form_auxinput2 in the time_control namelist (probably to 2).' CALL wrf_error_fatal3("<stdin>",94,& TRIM( wrf_err_message ) ) END IF ENDDO IF ( model_config_rec%sst_update .EQ. 0 ) THEN model_config_rec%io_form_auxinput4 = 0 DO i = 1, model_config_rec % max_dom WRITE (wrf_err_message, FMT='(A,A)') '--- NOTE: sst_update is 0, ', & 'setting io_form_auxinput4 = 0 and auxinput4_interval = 0 for all domains' CALL wrf_message ( wrf_err_message ) model_config_rec%auxinput4_interval(i) = 0 model_config_rec%auxinput4_interval_y(i) = 0 model_config_rec%auxinput4_interval_d(i) = 0 model_config_rec%auxinput4_interval_h(i) = 0 model_config_rec%auxinput4_interval_m(i) = 0 model_config_rec%auxinput4_interval_s(i) = 0 ENDDO ELSE IF ( model_config_rec%io_form_auxinput4 .EQ. 0 ) THEN wrf_err_message = '--- ERROR: If sst_update /= 0, io_form_auxinput4 must be /= 0' CALL wrf_message ( wrf_err_message ) wrf_err_message = '--- Set io_form_auxinput4 in the time_control namelist (probably to 2).' CALL wrf_error_fatal3("<stdin>",124,& TRIM( wrf_err_message ) ) END IF END IF END SUBROUTINE SUBROUTINE set_physics_rconfigs IMPLICIT NONE IF (( model_config_rec % ra_lw_physics(1) .EQ. CAMLWSCHEME ) .OR. & ( model_config_rec % ra_sw_physics(1) .EQ. CAMSWSCHEME )) THEN model_config_rec % paerlev = 29 model_config_rec % levsiz = 59 model_config_rec % cam_abs_dim1 = 4 model_config_rec % cam_abs_dim2 = model_config_rec % e_vert(1) wrf_err_message = '--- NOTE: CAM radiation is in use, setting: ' // & 'paerlev=29, levsiz=59, cam_abs_dim1=4, cam_abs_dim2=e_vert' CALL wrf_message ( wrf_err_message ) END IF IF ( model_config_rec % sf_surface_physics(1) .EQ. 0 ) & model_config_rec % num_soil_layers = 5 IF ( model_config_rec % sf_surface_physics(1) .EQ. SLABSCHEME ) & model_config_rec % num_soil_layers = 5 IF ( model_config_rec % sf_surface_physics(1) .EQ. LSMSCHEME ) & model_config_rec % num_soil_layers = 4 IF ( model_config_rec % sf_surface_physics(1) .EQ. NOAHMPSCHEME ) & model_config_rec % num_soil_layers = 4 IF ( model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME) & model_config_rec % num_soil_layers = 6 IF ( model_config_rec % sf_surface_physics(1) .EQ. PXLSMSCHEME ) & model_config_rec % num_soil_layers = 2 IF ( model_config_rec % sf_surface_physics(1) .EQ. 88 ) & model_config_rec % num_soil_layers = 4 WRITE (wrf_err_message, FMT='(A,I6)') '--- NOTE: num_soil_layers has been set to ', & model_config_rec % num_soil_layers CALL wrf_message ( wrf_err_message ) END SUBROUTINE set_physics_rconfigs END MODULE module_check_a_mundo