source: lmdz_wrf/WRFV3/share/module_check_a_mundo.F @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 12.8 KB
Line 
1!=======================================================================
2!
3   MODULE module_check_a_mundo
4
5!<DESCRIPTION>
6!
7! Contains subroutines that check the consistency of some namelist
8! settings. Some namelist settings depend on other values in the
9! namelist. These subroutines reset the dependent values and write
10! a message to stdout instead of detecting a fatal error and abort-
11! ing on a parameter mis-match.  This works around depending on the
12! user to set these specific settings in the namelist.
13!
14!   SUBROUTINE check_nml_consistency  :
15!      Check namelist settings for consistency
16!
17!   SUBROUTINE set_physics_rconfigs:
18!      Check namelist settings that determine memory allocations.
19!
20!</DESCRIPTION>
21
22      USE module_state_description
23      USE module_wrf_error
24      USE module_configure
25
26      IMPLICIT NONE
27
28!=======================================================================
29
30   CONTAINS
31
32!=======================================================================
33
34   SUBROUTINE  check_nml_consistency
35 
36!<DESCRIPTION>
37!
38! Check consistency of namelist settings
39!
40!</DESCRIPTION>
41
42      IMPLICIT NONE
43
44      INTEGER :: i
45
46!-----------------------------------------------------------------------
47! Check that all values of sf_surface_physics are the same for all domains
48!-----------------------------------------------------------------------
49
50      DO i = 2, model_config_rec % max_dom
51         IF ( model_config_rec % sf_surface_physics(i)     .NE. &
52              model_config_rec % sf_surface_physics(i-1) ) THEN
53            wrf_err_message = '--- ERROR: sf_surface_physics must be equal for all domains '
54            CALL wrf_message ( wrf_err_message )
55            wrf_err_message = '--- Fix sf_surface_physics in namelist.input '
56            CALL wrf_error_fatal ( TRIM( wrf_err_message ) )
57         END IF
58      ENDDO
59
60!-----------------------------------------------------------------------
61! If fractional_seaice = 0, and tice2tsk_if2cold = .true, nothing will happen
62!-----------------------------------------------------------------------
63
64      IF ( ( model_config_rec%fractional_seaice .EQ. 0 ).AND. &
65              ( model_config_rec%tice2tsk_if2cold ) ) THEN
66            wrf_err_message = '--- WARNING: You set tice2tsk_if2cold = .true.,  but fractional_seaice = 0'
67            CALL wrf_message ( wrf_err_message )
68            wrf_err_message = '--- WARNING: tice2tsk_if2cold will have no effect on results.'
69            CALL wrf_message ( wrf_err_message )
70      END IF
71
72!-----------------------------------------------------------------------
73! Check that if fine_input_stream /= 0, io_form_auxinput2 must also be in use
74!-----------------------------------------------------------------------
75
76      DO i = 1, model_config_rec % max_dom
77         IF ( ( model_config_rec%fine_input_stream(i) .NE. 0 ).AND. &
78              ( model_config_rec%io_form_auxinput2 .EQ. 0 ) ) THEN
79            wrf_err_message = '--- ERROR: If fine_input_stream /= 0, io_form_auxinput2 must be /= 0'
80            CALL wrf_message ( wrf_err_message )
81            wrf_err_message = '--- Set io_form_auxinput2 in the time_control namelist (probably to 2).'
82            CALL wrf_error_fatal ( TRIM( wrf_err_message ) )
83         END IF
84      ENDDO
85
86!-----------------------------------------------------------------------
87! If sst_update = 0, set io_form_auxinput4 to 0 so WRF will not try to
88! input the data; auxinput_interval must also be 0
89!-----------------------------------------------------------------------
90
91      IF ( model_config_rec%sst_update .EQ. 0 ) THEN
92         model_config_rec%io_form_auxinput4 = 0
93         DO i = 1, model_config_rec % max_dom
94            WRITE (wrf_err_message, FMT='(A,A)') '--- NOTE: sst_update is 0, ', &
95                  'setting io_form_auxinput4 = 0 and auxinput4_interval = 0 for all domains'
96            CALL wrf_message ( wrf_err_message )
97            model_config_rec%auxinput4_interval(i)   = 0
98            model_config_rec%auxinput4_interval_y(i) = 0
99            model_config_rec%auxinput4_interval_d(i) = 0
100            model_config_rec%auxinput4_interval_h(i) = 0
101            model_config_rec%auxinput4_interval_m(i) = 0
102            model_config_rec%auxinput4_interval_s(i) = 0
103         ENDDO
104      ELSE
105         IF ( model_config_rec%io_form_auxinput4 .EQ. 0 ) THEN
106            wrf_err_message = '--- ERROR: If sst_update /= 0, io_form_auxinput4 must be /= 0'
107            CALL wrf_message ( wrf_err_message )
108            wrf_err_message = '--- Set io_form_auxinput4 in the time_control namelist (probably to 2).'
109            CALL wrf_error_fatal ( TRIM( wrf_err_message ) )
110         END IF
111      END IF
112
113#if ((EM_CORE == 1) && (DA_CORE != 1))
114!-----------------------------------------------------------------------
115! Check that if grid_sfdda is one, grid_fdda is also 1
116!-----------------------------------------------------------------------
117
118      DO i = 1, model_config_rec % max_dom
119         IF ( ( model_config_rec%grid_sfdda(i) .EQ. 1 ).AND. &
120              ( model_config_rec%grid_fdda (i) .NE. 1 ) ) THEN
121            wrf_err_message = '--- ERROR: If grid_sfdda = 1, then grid_fdda must also = 1 for that domain '
122            CALL wrf_message ( wrf_err_message )
123            wrf_err_message = '--- Change grid_fdda or grid_sfdda in namelist.input '
124            CALL wrf_error_fatal ( TRIM( wrf_err_message ) )
125         END IF
126      ENDDO
127
128!-----------------------------------------------------------------------
129! If grid_fdda or grid_sfdda is 0 for any domain, all interval and
130! ending time information that domain must be set to zero.  For
131! surface fdda, we also need to make sure that the PXLSM soil nudging
132! switch is also zero.  Either surface fdda or soil nudging with the
133! PX scheme are enough to allow the surface fdda file to be read.
134!-----------------------------------------------------------------------
135
136      DO i = 1, model_config_rec % max_dom
137
138         IF ( model_config_rec%grid_fdda(i) .EQ. 0 ) THEN
139            WRITE (wrf_err_message, FMT='(A,I6,A)') '--- NOTE: grid_fdda is 0 for domain ', &
140                         i, ', setting gfdda interval and ending time to 0 for that domain.'
141            CALL wrf_message ( wrf_err_message )
142
143            model_config_rec%gfdda_end_y(i) = 0
144            model_config_rec%gfdda_end_d(i) = 0
145            model_config_rec%gfdda_end_h(i) = 0
146            model_config_rec%gfdda_end_m(i) = 0
147            model_config_rec%gfdda_end_s(i) = 0
148            model_config_rec%gfdda_interval(i)   = 0
149            model_config_rec%gfdda_interval_y(i) = 0
150            model_config_rec%gfdda_interval_d(i) = 0
151            model_config_rec%gfdda_interval_h(i) = 0
152            model_config_rec%gfdda_interval_m(i) = 0
153            model_config_rec%gfdda_interval_s(i) = 0
154         END IF
155
156         IF ( ( model_config_rec%grid_sfdda(i) .EQ. 0 ) .AND. &
157              ( model_config_rec%pxlsm_soil_nudge(i) .EQ. 0 ) ) THEN
158            WRITE (wrf_err_message, FMT='(A,I6,A)') &
159                         '--- NOTE: both grid_sfdda and pxlsm_soil_nudge are 0 for domain ', &
160                         i, ', setting sgfdda interval and ending time to 0 for that domain.'
161            CALL wrf_message ( wrf_err_message )
162
163            model_config_rec%sgfdda_end_y(i) = 0
164            model_config_rec%sgfdda_end_d(i) = 0
165            model_config_rec%sgfdda_end_h(i) = 0
166            model_config_rec%sgfdda_end_m(i) = 0
167            model_config_rec%sgfdda_end_s(i) = 0
168            model_config_rec%sgfdda_interval(i)   = 0
169            model_config_rec%sgfdda_interval_y(i) = 0
170            model_config_rec%sgfdda_interval_d(i) = 0
171            model_config_rec%sgfdda_interval_h(i) = 0
172            model_config_rec%sgfdda_interval_m(i) = 0
173            model_config_rec%sgfdda_interval_s(i) = 0
174         END IF
175
176         IF ( model_config_rec%obs_nudge_opt(i) .EQ. 0 ) THEN
177            WRITE (wrf_err_message, FMT='(A,I6,A)') '--- NOTE: obs_nudge_opt is 0 for domain ', &
178                         i, ', setting obs nudging interval and ending time to 0 for that domain.'
179            CALL wrf_message ( wrf_err_message )
180
181            model_config_rec%fdda_end(i) = 0
182            model_config_rec%auxinput11_interval(i)   = 0
183            model_config_rec%auxinput11_interval_y(i) = 0
184            model_config_rec%auxinput11_interval_d(i) = 0
185            model_config_rec%auxinput11_interval_h(i) = 0
186            model_config_rec%auxinput11_interval_m(i) = 0
187            model_config_rec%auxinput11_interval_s(i) = 0
188            model_config_rec%auxinput11_end(i)   = 0
189            model_config_rec%auxinput11_end_y(i) = 0
190            model_config_rec%auxinput11_end_d(i) = 0
191            model_config_rec%auxinput11_end_h(i) = 0
192            model_config_rec%auxinput11_end_m(i) = 0
193            model_config_rec%auxinput11_end_s(i) = 0
194         END IF
195
196      ENDDO      ! Loop over domains
197
198!-----------------------------------------------------------------------
199!  If analysis FDDA is turned off, reset the io_forms to zero so that
200!  there is no chance that WRF tries to input the data.
201!-----------------------------------------------------------------------
202
203      IF ( MAXVAL( model_config_rec%grid_fdda ) .EQ. 0 ) THEN
204         model_config_rec%io_form_gfdda = 0
205      ELSE
206         IF ( model_config_rec%io_form_gfdda .EQ. 0 ) THEN
207            wrf_err_message = '--- ERROR: If grid_fdda /= 0, io_form_gfdda must be /= 0'
208            CALL wrf_message ( wrf_err_message )
209            wrf_err_message = '--- Set io_form_gfdda in the time_control namelist (probably to 2).'
210            CALL wrf_error_fatal ( TRIM( wrf_err_message ) )
211         END IF
212      END IF
213      IF ( MAXVAL( model_config_rec%grid_sfdda ) .EQ. 0 ) THEN
214         model_config_rec%io_form_sgfdda = 0
215      ELSE
216         IF ( model_config_rec%io_form_sgfdda .EQ. 0 ) THEN
217            wrf_err_message = '--- ERROR: If grid_sfdda /= 0, io_form_sgfdda must be /= 0'
218            CALL wrf_message ( wrf_err_message )
219            wrf_err_message = '--- Set io_form_sgfdda in the time_control namelist (probably to 2).'
220            CALL wrf_error_fatal ( TRIM( wrf_err_message ) )
221         END IF
222      END IF
223
224!  Remapping namelist variables for gridded and surface fdda to aux streams 9 and 10.
225!  Relocated here so that the remappings are after checking the namelist for inconsistencies.
226
227#     include "../dyn_em/namelist_remappings_em.h"
228
229#endif
230
231   END SUBROUTINE
232
233!=======================================================================
234
235   SUBROUTINE set_physics_rconfigs
236
237!<DESCRIPTION>
238!
239! Some derived rconfig entries need to be set based on the value of other,
240! non-derived entries before package-dependent memory allocation takes place.
241! This works around depending on the user to set these specific settings in the
242! namelist.
243!
244!</DESCRIPTION>
245
246      IMPLICIT NONE
247
248!-----------------------------------------------------------------------
249! Set the namelist parameters for the CAM radiation scheme if either
250! ra_lw_physics = CAMLWSCHEME or ra_sw_physics = CAMSWSCHEME. 
251!-----------------------------------------------------------------------
252
253      IF (( model_config_rec % ra_lw_physics(1) .EQ. CAMLWSCHEME ) .OR. &
254          ( model_config_rec % ra_sw_physics(1) .EQ. CAMSWSCHEME )) THEN
255         model_config_rec % paerlev = 29
256         model_config_rec % levsiz = 59
257         model_config_rec % cam_abs_dim1 = 4
258         model_config_rec % cam_abs_dim2 = model_config_rec % e_vert(1)
259
260         wrf_err_message = '--- NOTE: CAM radiation is in use, setting:  ' // &
261                           'paerlev=29, levsiz=59, cam_abs_dim1=4, cam_abs_dim2=e_vert'
262         CALL wrf_message ( wrf_err_message )
263
264      END IF
265
266!-----------------------------------------------------------------------
267! Set namelist parameter num_soil_levels depending on the value of
268! sf_surface_physics
269!-----------------------------------------------------------------------
270
271      IF ( model_config_rec % sf_surface_physics(1) .EQ. 0           ) &
272           model_config_rec % num_soil_layers = 5
273      IF ( model_config_rec % sf_surface_physics(1) .EQ. SLABSCHEME  ) &
274           model_config_rec % num_soil_layers = 5
275      IF ( model_config_rec % sf_surface_physics(1) .EQ. LSMSCHEME   ) &
276           model_config_rec % num_soil_layers = 4
277      IF ( model_config_rec % sf_surface_physics(1) .EQ. RUCLSMSCHEME) &
278           model_config_rec % num_soil_layers = 6
279      IF ( model_config_rec % sf_surface_physics(1) .EQ. PXLSMSCHEME ) &
280           model_config_rec % num_soil_layers = 2
281      IF ( model_config_rec % sf_surface_physics(1) .EQ. 88          ) &
282           model_config_rec % num_soil_layers = 4
283
284      WRITE (wrf_err_message, FMT='(A,I6)') '--- NOTE: num_soil_layers has been set to ', &
285                                             model_config_rec % num_soil_layers
286      CALL wrf_message ( wrf_err_message )
287
288   END SUBROUTINE set_physics_rconfigs
289
290!=======================================================================
291
292   END MODULE module_check_a_mundo
293
294!=======================================================================
Note: See TracBrowser for help on using the repository browser.