output_wrf.F

References to this file elsewhere.
1 !WRF:MEDIATION:IO
2 !  ---principal wrf output routine (called from routines in module_io_domain ) 
3   SUBROUTINE output_wrf ( fid , grid , config_flags, switch , ierr )
4     USE module_io
5     USE module_wrf_error
6     USE module_io_wrf
7     USE module_domain
8     USE module_state_description
9     USE module_configure
10 !    USE module_date_time
11     USE module_model_constants
12     USE module_utility
13     IMPLICIT NONE
14 #include <wrf_io_flags.h>
15 #include <wrf_status_codes.h>
16     TYPE(domain) :: grid
17     TYPE(grid_config_rec_type),  INTENT(INOUT)    :: config_flags
18     INTEGER, INTENT(IN) :: fid, switch
19     INTEGER, INTENT(INOUT) :: ierr
20 
21     ! Local data
22     INTEGER ids , ide , jds , jde , kds , kde , &
23             ims , ime , jms , jme , kms , kme , &
24             ips , ipe , jps , jpe , kps , kpe
25       
26     INTEGER , DIMENSION(3) :: domain_start , domain_end
27     INTEGER , DIMENSION(3) :: memory_start , memory_end
28     INTEGER , DIMENSION(3) :: patch_start , patch_end
29     INTEGER i,j
30     INTEGER julyr, julday, idt, iswater , map_proj
31     INTEGER filestate
32     LOGICAL dryrun
33     REAL    gmt, cen_lat, cen_lon, bdyfrq , truelat1 , truelat2 , moad_cen_lat , stand_lon
34     INTEGER dyn_opt, diff_opt, km_opt, damp_opt,  &
35             mp_physics, ra_lw_physics, ra_sw_physics, sf_sfclay_physics, &
36             sf_surface_physics, bl_pbl_physics, cu_physics
37     REAL    khdif, kvdif, swrad_scat
38     INTEGER ucmcall, w_damping, smooth_option, feedback, surface_input_source, sst_update
39 #if (EM_CORE == 1)
40     INTEGER grid_id , parent_id , i_parent_start , j_parent_start , parent_grid_ratio
41     INTEGER diff_6th_opt
42     REAL    diff_6th_factor
43     INTEGER grid_fdda, gfdda_interval_m, gfdda_end_h, if_ramping, &
44             obs_nudge_opt, obs_nudge_wind, obs_nudge_temp, obs_nudge_mois, obs_nudge_pstr, obs_idynin, obs_ionf
45     REAL    fgdt, guv, gt, gq, dtramp_min, &
46             obs_coef_wind, obs_coef_temp, obs_coef_mois, obs_coef_pstr, obs_dtramp, fdda_end
47     LOGICAL pd_moist, pd_scalar, pd_tke
48 #endif
49     CHARACTER (len=19) simulation_start_date
50     CHARACTER (len=len_current_date) current_date_save
51     INTEGER simulation_start_year   , &
52             simulation_start_month  , &
53             simulation_start_day    , &
54             simulation_start_hour   , &
55             simulation_start_minute , &
56             simulation_start_second
57     INTEGER rc
58     INTEGER :: io_form
59     LOGICAL, EXTERNAL :: multi_files
60     INTEGER, EXTERNAL :: use_package
61     INTEGER p_hr, p_min, p_sec, p_ms
62 
63     CHARACTER*256 message
64     CHARACTER*80  fname
65     CHARACTER*80  char_junk
66     INTEGER    ibuf(1)
67     REAL       rbuf(1)
68     TYPE(WRFU_TimeInterval) :: bdy_increment
69     TYPE(WRFU_Time)         :: next_time, currentTime, startTime
70     CHARACTER*40            :: next_datestr
71     INTEGER :: start_year , start_month , start_day , start_hour , start_minute , start_second
72     LOGICAL :: adjust
73 
74     WRITE(wrf_err_message,*)'output_wrf: begin, fid = ',fid
75     CALL wrf_debug( 300 , wrf_err_message )
76 
77     CALL wrf_inquire_filename ( fid , fname , filestate , ierr )
78     IF ( ierr /= 0 ) THEN
79       WRITE(wrf_err_message,*)'module_io_wrf: output_wrf: wrf_inquire_filename Status = ',ierr
80       CALL wrf_error_fatal( wrf_err_message )
81     ENDIF
82 
83     WRITE(wrf_err_message,*)'output_wrf: fid,filestate = ',fid,filestate
84     CALL wrf_debug( 300 , wrf_err_message )
85 
86     ! io_form is used to determine if multi-file I/O is enabled and to 
87     ! control writing of format-specific time-independent metadata
88     IF ( switch .EQ. model_input_only ) THEN
89       CALL nl_get_io_form_input( 1, io_form )
90     ELSE IF ( switch .EQ. aux_model_input1_only ) THEN
91       CALL nl_get_io_form_auxinput1( 1, io_form )
92     ELSE IF ( switch .EQ. aux_model_input2_only ) THEN
93       CALL nl_get_io_form_auxinput2( 1, io_form )
94     ELSE IF ( switch .EQ. aux_model_input3_only ) THEN
95       CALL nl_get_io_form_auxinput3( 1, io_form )
96     ELSE IF ( switch .EQ. aux_model_input4_only ) THEN
97       CALL nl_get_io_form_auxinput4( 1, io_form )
98     ELSE IF ( switch .EQ. aux_model_input5_only ) THEN
99       CALL nl_get_io_form_auxinput5( 1, io_form )
100     ELSE IF ( switch .EQ. aux_model_input6_only ) THEN
101       CALL nl_get_io_form_auxinput6( 1, io_form )
102     ELSE IF ( switch .EQ. aux_model_input7_only ) THEN
103       CALL nl_get_io_form_auxinput7( 1, io_form )
104     ELSE IF ( switch .EQ. aux_model_input8_only ) THEN
105       CALL nl_get_io_form_auxinput8( 1, io_form )
106     ELSE IF ( switch .EQ. aux_model_input9_only ) THEN
107       CALL nl_get_io_form_auxinput9( 1, io_form )
108     ELSE IF ( switch .EQ. aux_model_input10_only ) THEN
109       CALL nl_get_io_form_gfdda( 1, io_form )
110     ELSE IF ( switch .EQ. aux_model_input11_only ) THEN
111       CALL nl_get_io_form_auxinput11( 1, io_form )
112 
113     ELSE IF ( switch .EQ. history_only ) THEN
114       CALL nl_get_io_form_history( 1, io_form )
115     ELSE IF ( switch .EQ. aux_hist1_only ) THEN
116       CALL nl_get_io_form_auxhist1( 1, io_form )
117     ELSE IF ( switch .EQ. aux_hist2_only ) THEN
118       CALL nl_get_io_form_auxhist2( 1, io_form )
119     ELSE IF ( switch .EQ. aux_hist3_only ) THEN
120       CALL nl_get_io_form_auxhist3( 1, io_form )
121     ELSE IF ( switch .EQ. aux_hist4_only ) THEN
122       CALL nl_get_io_form_auxhist4( 1, io_form )
123     ELSE IF ( switch .EQ. aux_hist5_only ) THEN
124       CALL nl_get_io_form_auxhist5( 1, io_form )
125     ELSE IF ( switch .EQ. aux_hist6_only ) THEN
126       CALL nl_get_io_form_auxhist6( 1, io_form )
127     ELSE IF ( switch .EQ. aux_hist7_only ) THEN
128       CALL nl_get_io_form_auxhist7( 1, io_form )
129     ELSE IF ( switch .EQ. aux_hist8_only ) THEN
130       CALL nl_get_io_form_auxhist8( 1, io_form )
131     ELSE IF ( switch .EQ. aux_hist9_only ) THEN
132       CALL nl_get_io_form_auxhist9( 1, io_form )
133     ELSE IF ( switch .EQ. aux_hist10_only ) THEN
134       CALL nl_get_io_form_auxhist10( 1, io_form )
135     ELSE IF ( switch .EQ. aux_hist11_only ) THEN
136       CALL nl_get_io_form_auxhist11( 1, io_form )
137 
138     ELSE IF ( switch .EQ. restart_only ) THEN
139       CALL nl_get_io_form_restart( 1, io_form )
140     ELSE IF ( switch .EQ. boundary_only ) THEN
141       CALL nl_get_io_form_boundary( 1, io_form )
142     ELSE  ! default:  use history
143       CALL nl_get_io_form_history( 1, io_form )
144     ENDIF
145 
146     dryrun       = ( filestate .EQ. WRF_FILE_OPENED_NOT_COMMITTED )
147 
148     WRITE(wrf_err_message,*)'output_wrf: dryrun = ',dryrun
149     CALL wrf_debug( 300 , wrf_err_message )
150 
151     CALL get_ijk_from_grid (  grid ,                        &
152                               ids, ide, jds, jde, kds, kde,    &
153                               ims, ime, jms, jme, kms, kme,    &
154                               ips, ipe, jps, jpe, kps, kpe    )
155 
156     call nl_get_dyn_opt       ( 1, dyn_opt                       )
157     call nl_get_diff_opt      ( 1, diff_opt                      )
158     call nl_get_km_opt        ( 1, km_opt                        )
159     call nl_get_damp_opt      ( 1, damp_opt                      )
160     call nl_get_khdif         ( grid%id,  khdif               )
161     call nl_get_kvdif         ( grid%id,  kvdif               )
162     call nl_get_mp_physics    ( grid%id,  mp_physics          )
163     call nl_get_ra_lw_physics ( grid%id,  ra_lw_physics       )
164     call nl_get_ra_sw_physics ( grid%id,  ra_sw_physics           )
165     call nl_get_sf_sfclay_physics  ( grid%id,  sf_sfclay_physics  )
166     call nl_get_sf_surface_physics ( grid%id,  sf_surface_physics )
167     call nl_get_bl_pbl_physics     ( grid%id,  bl_pbl_physics     )
168     call nl_get_cu_physics         ( grid%id,  cu_physics         )
169 
170 ! add nml variables in 2.2
171     call nl_get_surface_input_source ( 1      ,  surface_input_source )
172     call nl_get_sst_update           ( 1      ,  sst_update           )
173     call nl_get_feedback             ( 1      ,  feedback             )
174     call nl_get_smooth_option        ( 1      ,  smooth_option        )
175     call nl_get_swrad_scat           ( 1      ,  swrad_scat           )
176     call nl_get_ucmcall              ( 1      ,  ucmcall              )
177     call nl_get_w_damping            ( 1      ,  w_damping            )
178 
179 #if (EM_CORE == 1)
180     CALL nl_get_pd_moist  ( grid%id , pd_moist )
181     CALL nl_get_pd_scalar ( grid%id , pd_scalar )
182     CALL nl_get_pd_tke    ( grid%id , pd_tke )
183     CALL nl_get_diff_6th_opt  ( grid%id , diff_6th_opt )
184     CALL nl_get_diff_6th_factor ( grid%id , diff_6th_factor )
185     CALL nl_get_grid_fdda  ( grid%id , grid_fdda )
186     CALL nl_get_gfdda_end_h( grid%id , gfdda_end_h )
187     CALL nl_get_gfdda_interval_m ( grid%id , gfdda_interval_m )
188 
189     IF ( grid_fdda == 1 ) THEN
190     CALL nl_get_fgdt       ( grid%id , fgdt )
191     CALL nl_get_guv        ( grid%id , guv )
192     CALL nl_get_gt         ( grid%id , gt )
193     CALL nl_get_gq         ( grid%id , gq )
194     CALL nl_get_if_ramping ( 1       , if_ramping )
195     CALL nl_get_dtramp_min ( 1       , dtramp_min )
196     ENDIF
197 
198     CALL nl_get_obs_nudge_opt  ( grid%id , obs_nudge_opt )
199     IF ( obs_nudge_opt == 1 ) THEN
200     CALL nl_get_fdda_end       ( grid%id , fdda_end )
201     CALL nl_get_obs_nudge_wind ( grid%id , obs_nudge_wind )
202     CALL nl_get_obs_coef_wind  ( grid%id , obs_coef_wind )
203     CALL nl_get_obs_nudge_temp ( grid%id , obs_nudge_temp )
204     CALL nl_get_obs_coef_temp  ( grid%id , obs_coef_temp )
205     CALL nl_get_obs_nudge_mois ( grid%id , obs_nudge_mois )
206     CALL nl_get_obs_coef_mois  ( grid%id , obs_coef_mois )
207     CALL nl_get_obs_nudge_pstr ( grid%id , obs_nudge_pstr )
208     CALL nl_get_obs_coef_pstr  ( grid%id , obs_coef_pstr )
209     CALL nl_get_obs_ionf       ( 1       , obs_ionf )
210     CALL nl_get_obs_idynin     ( 1       , obs_idynin )
211     CALL nl_get_obs_dtramp     ( 1       , obs_dtramp )
212     ENDIF
213 #endif
214 
215 ! julday and gmt can be set in namelist_03 for ideal.exe run
216     CALL nl_get_gmt (grid%id, gmt)
217     CALL nl_get_julyr (grid%id, julyr)
218     CALL nl_get_julday (grid%id, julday)
219     CALL nl_get_mminlu ( 1, char_junk(1:4) )
220     CALL nl_get_iswater (grid%id, iswater )
221     CALL nl_get_cen_lat ( grid%id , cen_lat )
222     CALL nl_get_cen_lon ( grid%id , cen_lon )
223     CALL nl_get_truelat1 ( grid%id , truelat1 )
224     CALL nl_get_truelat2 ( grid%id , truelat2 )
225     CALL nl_get_moad_cen_lat ( grid%id , moad_cen_lat )
226     CALL nl_get_stand_lon ( grid%id , stand_lon )
227     CALL nl_get_map_proj ( grid%id , map_proj )
228 
229 #if (EM_CORE == 1)
230     CALL nl_get_parent_id ( grid%id , parent_id )
231     CALL nl_get_i_parent_start ( grid%id , i_parent_start )
232     CALL nl_get_j_parent_start ( grid%id , j_parent_start )
233     CALL nl_get_parent_grid_ratio ( grid%id , parent_grid_ratio )
234 #endif
235 
236     CALL domain_clockprint(150, grid, &
237            'DEBUG output_wrf():  before call to domain_clock_get,')
238     CALL domain_clock_get( grid, current_time=currentTime, &
239                                  start_time=startTime,     &
240                                  current_timestr=current_date )
241     WRITE ( wrf_err_message , * ) 'output_wrf: begin, current_date=',current_date
242     CALL wrf_debug ( 300 , wrf_err_message )
243 
244     WRITE( message , * ) "OUTPUT FROM " , TRIM(program_name)
245     CALL wrf_put_dom_ti_char ( fid , 'TITLE' , TRIM(message) , ierr )
246     ! added grib-specific metadata:  Todd Hutchinson 8/21/2005
247     IF ( ( use_package( io_form ) == IO_GRIB1 ) .OR. &
248          ( use_package( io_form ) == IO_GRIB2 ) ) THEN
249       CALL wrf_put_dom_ti_char ( fid, 'PROGRAM_NAME', TRIM(program_name) , ierr )
250     ENDIF
251     CALL nl_get_start_year(grid%id,start_year)
252     CALL nl_get_start_month(grid%id,start_month)
253     CALL nl_get_start_day(grid%id,start_day)
254     CALL nl_get_start_hour(grid%id,start_hour)
255     CALL nl_get_start_minute(grid%id,start_minute)
256     CALL nl_get_start_second(grid%id,start_second)
257 #ifdef PLANET
258     WRITE ( start_date , FMT = '(I4.4,"-",I5.5,"_",I2.2,":",I2.2,":",I2.2)' ) &
259             start_year,start_day,start_hour,start_minute,start_second
260 #else
261     WRITE ( start_date , FMT = '(I4.4,"-",I2.2,"-",I2.2,"_",I2.2,":",I2.2,":",I2.2)' ) &
262             start_year,start_month,start_day,start_hour,start_minute,start_second
263 #endif
264     CALL wrf_put_dom_ti_char ( fid , 'START_DATE', TRIM(start_date) , ierr )
265     IF ( switch .EQ. model_input_only) THEN
266        CALL wrf_put_dom_ti_char ( fid , 'SIMULATION_START_DATE', TRIM(start_date) , ierr )
267     ELSE IF ( ( switch .EQ. restart_only ) .OR. ( switch .EQ. history_only ) ) THEN
268        CALL nl_get_simulation_start_year   ( 1, simulation_start_year   )
269        CALL nl_get_simulation_start_month  ( 1, simulation_start_month  )
270        CALL nl_get_simulation_start_day    ( 1, simulation_start_day    )
271        CALL nl_get_simulation_start_hour   ( 1, simulation_start_hour   )
272        CALL nl_get_simulation_start_minute ( 1, simulation_start_minute )
273        CALL nl_get_simulation_start_second ( 1, simulation_start_second )
274 #ifdef PLANET
275        WRITE ( simulation_start_date , FMT = '(I4.4,"-",I5.5,"_",I2.2,":",I2.2,":",I2.2)' ) &
276                simulation_start_year,simulation_start_day,&
277                simulation_start_hour,simulation_start_minute,simulation_start_second
278 #else
279        WRITE ( simulation_start_date , FMT = '(I4.4,"-",I2.2,"-",I2.2,"_",I2.2,":",I2.2,":",I2.2)' ) &
280                simulation_start_year,simulation_start_month,simulation_start_day,&
281                simulation_start_hour,simulation_start_minute,simulation_start_second
282 #endif
283        CALL wrf_put_dom_ti_char ( fid , 'SIMULATION_START_DATE', TRIM(simulation_start_date) , ierr )
284     END IF
285 
286     ibuf(1) = config_flags%e_we - config_flags%s_we + 1
287     CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_GRID_DIMENSION' ,  ibuf , 1 , ierr )
288 
289     ibuf(1) = config_flags%e_sn - config_flags%s_sn + 1
290     CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_GRID_DIMENSION' , ibuf , 1 , ierr )
291 
292     ibuf(1) = config_flags%e_vert - config_flags%s_vert + 1
293     CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_GRID_DIMENSION' , ibuf , 1 , ierr )
294 
295 #if (EM_CORE == 1)
296     IF (grid%map_proj == 6) THEN
297        ! Global ... dx determined automatically
298        ! Don't use value from namelist ... used derived value instead
299        CALL wrf_put_dom_ti_real ( fid , 'DX' , grid%dx , 1 , ierr )
300        CALL wrf_put_dom_ti_real ( fid , 'DY' , grid%dy , 1 , ierr )
301     ELSE
302        CALL wrf_put_dom_ti_real ( fid , 'DX' , config_flags%dx , 1 , ierr )
303        CALL wrf_put_dom_ti_real ( fid , 'DY' , config_flags%dy , 1 , ierr )
304     END IF
305 #endif
306 
307 ! added this metadatum for H. Chuan, NCEP, 030417, JM
308     SELECT CASE ( dyn_opt )
309 #if (NMM_CORE == 1)
310         CASE ( dyn_nmm )
311           CALL wrf_put_dom_ti_char ( fid , 'GRIDTYPE',  'E' , ierr )
312 #endif
313 #if (EM_CORE == 1)
314         CASE ( dyn_em )
315           CALL wrf_put_dom_ti_char ( fid , 'GRIDTYPE',  'C' , ierr )
316 #endif
317 #if (COAMPS_CORE == 1 )
318         CASE ( dyn_coamps )
319           CALL wrf_put_dom_ti_char ( fid , 'GRIDTYPE',  'B' , ierr )
320 #endif
321         CASE DEFAULT
322           ! we don't know; don't put anything in the file
323     END SELECT
324 
325 ! added these fields for W. Skamarock, 020402, JM
326     ibuf(1) = dyn_opt
327     CALL wrf_put_dom_ti_integer ( fid , 'DYN_OPT' ,  ibuf , 1 , ierr )
328     ibuf(1) = diff_opt
329     CALL wrf_put_dom_ti_integer ( fid , 'DIFF_OPT' ,  ibuf , 1 , ierr )
330     ibuf(1) = km_opt
331     CALL wrf_put_dom_ti_integer ( fid , 'KM_OPT' ,  ibuf , 1 , ierr )
332     ibuf(1) = damp_opt
333     CALL wrf_put_dom_ti_integer ( fid , 'DAMP_OPT' ,  ibuf , 1 , ierr )
334     rbuf(1) = khdif
335     CALL wrf_put_dom_ti_real    ( fid , 'KHDIF' ,  rbuf , 1 , ierr )
336     rbuf(1) = kvdif
337     CALL wrf_put_dom_ti_real    ( fid , 'KVDIF' ,  rbuf , 1 , ierr )
338     ibuf(1) = mp_physics
339     CALL wrf_put_dom_ti_integer ( fid , 'MP_PHYSICS' ,  ibuf , 1 , ierr )
340     ibuf(1) = ra_lw_physics
341     CALL wrf_put_dom_ti_integer ( fid , 'RA_LW_PHYSICS' ,  ibuf , 1 , ierr )
342     ibuf(1) = ra_sw_physics
343     CALL wrf_put_dom_ti_integer ( fid , 'RA_SW_PHYSICS' ,  ibuf , 1 , ierr )
344     ibuf(1) = sf_sfclay_physics
345     CALL wrf_put_dom_ti_integer ( fid , 'SF_SFCLAY_PHYSICS' ,  ibuf , 1 , ierr )
346     ibuf(1) = sf_surface_physics
347     CALL wrf_put_dom_ti_integer ( fid , 'SF_SURFACE_PHYSICS' ,  ibuf , 1 , ierr )
348     ibuf(1) = bl_pbl_physics
349     CALL wrf_put_dom_ti_integer ( fid , 'BL_PBL_PHYSICS' ,  ibuf , 1 , ierr )
350     ibuf(1) = cu_physics
351     CALL wrf_put_dom_ti_integer ( fid , 'CU_PHYSICS' ,  ibuf , 1 , ierr )
352 
353     ! added netcdf-specific metadata:
354     IF ( ( use_package( io_form ) == IO_NETCDF ) .OR. &
355          ( use_package( io_form ) == IO_PHDF5  ) .OR. &
356          ( use_package( io_form ) == IO_PNETCDF ) ) THEN
357       CALL wrf_put_dom_ti_integer ( fid, 'SURFACE_INPUT_SOURCE', surface_input_source , 1 , ierr )
358       CALL wrf_put_dom_ti_integer ( fid, 'SST_UPDATE', sst_update , 1 , ierr )
359 #if (EM_CORE == 1)
360       CALL wrf_put_dom_ti_integer ( fid, 'GRID_FDDA', grid_fdda , 1 , ierr )
361       CALL wrf_put_dom_ti_integer ( fid, 'GFDDA_INTERVAL_M', gfdda_interval_m , 1 , ierr )
362       CALL wrf_put_dom_ti_integer ( fid, 'GFDDA_END_H', gfdda_end_h , 1 , ierr )
363 #endif
364 
365       IF ( switch .EQ. history_only ) THEN
366       CALL wrf_put_dom_ti_integer ( fid, 'UCMCALL', ucmcall , 1 , ierr )
367       CALL wrf_put_dom_ti_integer ( fid, 'FEEDBACK', feedback , 1 , ierr )
368       CALL wrf_put_dom_ti_integer ( fid, 'SMOOTH_OPTION', smooth_option , 1 , ierr )
369       CALL wrf_put_dom_ti_real    ( fid, 'SWRAD_SCAT', swrad_scat , 1 , ierr )
370       CALL wrf_put_dom_ti_integer ( fid, 'W_DAMPING', w_damping , 1 , ierr )
371 
372 #if (EM_CORE == 1)
373       CALL wrf_put_dom_ti_logical ( fid, 'PD_MOIST', pd_moist , 1 , ierr )
374       CALL wrf_put_dom_ti_logical ( fid, 'PD_SCALAR', pd_scalar , 1 , ierr )
375       CALL wrf_put_dom_ti_logical ( fid, 'PD_TKE', pd_tke , 1 , ierr )
376       CALL wrf_put_dom_ti_integer ( fid, 'DIFF_6TH_OPT', diff_6th_opt , 1 , ierr )
377       CALL wrf_put_dom_ti_real    ( fid, 'DIFF_6TH_FACTOR', diff_6th_factor , 1 , ierr )
378 
379       IF ( grid_fdda == 1 ) THEN
380         CALL wrf_put_dom_ti_real    ( fid, 'FGDT', fgdt , 1 , ierr )
381         CALL wrf_put_dom_ti_real    ( fid, 'GUV', guv , 1 , ierr )
382         CALL wrf_put_dom_ti_real    ( fid, 'GT', gt , 1 , ierr )
383         CALL wrf_put_dom_ti_real    ( fid, 'GQ', gq , 1 , ierr )
384         CALL wrf_put_dom_ti_integer ( fid, 'IF_RAMPING', if_ramping , 1 , ierr )
385         CALL wrf_put_dom_ti_real    ( fid, 'DTRAMP_MIN', dtramp_min , 1 , ierr )
386       ENDIF
387 
388       CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_OPT', obs_nudge_opt , 1 , ierr )
389       IF ( obs_nudge_opt == 1 ) THEN
390         CALL wrf_put_dom_ti_real    ( fid, 'FDDA_END', fdda_end , 1 , ierr )
391         CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_WIND', obs_nudge_wind , 1 , ierr )
392         CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_WIND', obs_coef_wind , 1 , ierr )
393         CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_TEMP', obs_nudge_temp , 1 , ierr )
394         CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_TEMP', obs_coef_temp , 1 , ierr )
395         CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_MOIS', obs_nudge_mois , 1 , ierr )
396         CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_MOIS', obs_coef_mois , 1 , ierr )
397         CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_PSTR', obs_nudge_pstr , 1 , ierr )
398         CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_PSTR', obs_coef_pstr , 1 , ierr )
399         CALL wrf_put_dom_ti_integer ( fid, 'OBS_IONF', obs_ionf , 1 , ierr )
400         CALL wrf_put_dom_ti_integer ( fid, 'OBS_IDYNIN', obs_idynin , 1 , ierr )
401         CALL wrf_put_dom_ti_real    ( fid, 'OBS_DTRAMP', obs_dtramp , 1 , ierr )
402       ENDIF
403 #endif
404       ENDIF ! history_only
405     ENDIF
406 
407 ! added these fields for use by reassembly programs , 010831, JM
408 ! modified these fields so "patch" == "domain" when multi-file output 
409 ! formats are not used.  051018, TBH
410 
411     ibuf(1) = MAX(ips,ids)
412     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ids
413     CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_START_UNSTAG' ,  ibuf , 1 , ierr )
414     ibuf(1) = MIN(ipe,ide-1)
415     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ide - 1
416     CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_END_UNSTAG' ,  ibuf , 1 , ierr )
417     ibuf(1) = MAX(ips,ids)
418     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ids
419     CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_START_STAG' ,  ibuf , 1 , ierr )
420     ibuf(1) = MIN(ipe,ide)
421     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ide
422     CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_END_STAG' ,  ibuf , 1 , ierr )
423     ibuf(1) = MAX(jps,jds)
424     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jds
425     CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_START_UNSTAG' ,  ibuf , 1 , ierr )
426     ibuf(1) = MIN(jpe,jde-1)
427     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jde - 1
428     CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_END_UNSTAG' ,  ibuf , 1 , ierr )
429     ibuf(1) = MAX(jps,jds)
430     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jds
431     CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_START_STAG' ,  ibuf , 1 , ierr )
432     ibuf(1) = MIN(jpe,jde)
433     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jde
434     CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_END_STAG' ,  ibuf , 1 , ierr )
435 
436     ibuf(1) = MAX(kps,kds)
437     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kds
438     CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_START_UNSTAG' ,  ibuf , 1 , ierr )
439     ibuf(1) = MIN(kpe,kde-1)
440     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kde - 1
441     CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_END_UNSTAG' ,  ibuf , 1 , ierr )
442     ibuf(1) = MAX(kps,kds)
443     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kds
444     CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_START_STAG' ,  ibuf , 1 , ierr )
445     ibuf(1) = MIN(kpe,kde)
446     IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kde
447     CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_END_STAG' ,  ibuf , 1 , ierr )
448 #if (EM_CORE == 1)
449     ibuf(1) = grid%id
450     CALL wrf_put_dom_ti_integer ( fid , 'GRID_ID' ,  ibuf , 1 , ierr )
451     ibuf(1) = parent_id
452     CALL wrf_put_dom_ti_integer ( fid , 'PARENT_ID' ,  ibuf , 1 , ierr )
453     ibuf(1) = i_parent_start
454     CALL wrf_put_dom_ti_integer ( fid , 'I_PARENT_START' ,  ibuf , 1 , ierr )
455     ibuf(1) = j_parent_start
456     CALL wrf_put_dom_ti_integer ( fid , 'J_PARENT_START' ,  ibuf , 1 , ierr )
457     ibuf(1) = parent_grid_ratio
458     CALL wrf_put_dom_ti_integer ( fid , 'PARENT_GRID_RATIO' ,  ibuf , 1 , ierr )
459 #endif
460 
461 ! end add 010831 JM
462 
463 #if (EM_CORE != 1)
464     CALL wrf_put_dom_ti_real ( fid , 'DX' ,  config_flags%dx , 1 , ierr )
465     CALL wrf_put_dom_ti_real ( fid , 'DY' ,  config_flags%dy , 1 , ierr )
466 #endif
467     CALL wrf_put_dom_ti_real ( fid , 'DT' ,  config_flags%dt , 1 , ierr )
468     CALL wrf_put_dom_ti_real ( fid , 'CEN_LAT' ,  config_flags%cen_lat , 1 , ierr )
469     CALL wrf_put_dom_ti_real ( fid , 'CEN_LON' ,  config_flags%cen_lon , 1 , ierr )
470     CALL wrf_put_dom_ti_real ( fid , 'TRUELAT1',  config_flags%truelat1, 1 , ierr )
471     CALL wrf_put_dom_ti_real ( fid , 'TRUELAT2',  config_flags%truelat2, 1 , ierr )
472     CALL wrf_put_dom_ti_real ( fid , 'MOAD_CEN_LAT',  config_flags%moad_cen_lat, 1 , ierr )
473     CALL wrf_put_dom_ti_real ( fid , 'STAND_LON',  config_flags%stand_lon, 1 , ierr )
474     IF ( switch .NE. boundary_only ) THEN
475 #ifdef PLANET
476       ! When writing to restart files, use the values of the instantaneous
477       ! time for determining the values of JULYR, JULDAY, and GMT.  If the
478       ! original values in config_flags are used, this assumes that the
479       ! restart simulation will start with an itimestep NE 0.  If we use
480       ! the instantaneous time, we can start a restart simulation with a
481       ! different value of delta-t for timestep and still get the clocks
482       ! calendars (and orbital information!) correct.
483       !
484       ! Current time is still defined from above call to WRF_UTIL_ClockGet
485       CALL WRFU_TimeGet( currentTime, YY=julyr, dayOfYear=julday, H=p_hr, M=p_min, S=p_sec, MS=p_ms, rc=rc)
486       WRITE(wrf_err_message,*)'output_wrf: julyr,julday,hr,min,sec,ms = ',julyr,julday,p_hr,p_min,p_sec,p_ms
487       CALL wrf_debug( 100 , wrf_err_message )
488       gmt = REAL(p_hr)+REAL(p_min)/60.+REAL(p_sec)/3600.+REAL(p_ms)/3600000.
489       CALL wrf_put_dom_ti_real ( fid , 'GMT' ,  gmt , 1 , ierr )
490       CALL wrf_put_dom_ti_integer ( fid , 'JULYR' ,  julyr , 1 , ierr )
491       CALL wrf_put_dom_ti_integer ( fid , 'JULDAY' ,  julday , 1 , ierr )
492 #else
493       CALL wrf_put_dom_ti_real ( fid , 'GMT' ,  config_flags%gmt , 1 , ierr )
494       CALL wrf_put_dom_ti_integer ( fid , 'JULYR' ,  config_flags%julyr , 1 , ierr )
495       CALL wrf_put_dom_ti_integer ( fid , 'JULDAY' ,  config_flags%julday , 1 , ierr )
496 #endif
497     ENDIF
498 #if (NMM_CORE == 1)
499         write(0,*) 'MMINLU would be: ', MMINLU(1:4)
500         MMINLU(1:4)='USGS'
501         write(0,*) 'MMINLU now: ', MMINLU(1:4)
502 #endif
503     CALL wrf_put_dom_ti_integer ( fid , 'MAP_PROJ' ,  config_flags%map_proj , 1 , ierr )
504     CALL wrf_put_dom_ti_char ( fid , 'MMINLU',  mminlu(1:4) , ierr )
505     CALL wrf_put_dom_ti_integer ( fid , 'ISWATER' ,  config_flags%iswater , 1 , ierr )
506     CALL wrf_put_dom_ti_integer ( fid , 'ISICE' ,  config_flags%isice , 1 , ierr )
507     CALL wrf_put_dom_ti_integer ( fid , 'ISURBAN' ,  config_flags%isurban , 1 , ierr )
508     CALL wrf_put_dom_ti_integer ( fid , 'ISOILWATER' ,  config_flags%isoilwater , 1 , ierr )
509 ! added these fields for restarting of moving nests, JM
510     CALL wrf_put_dom_ti_integer ( fid , 'I_PARENT_START' ,  config_flags%i_parent_start  , 1 , ierr )
511     CALL wrf_put_dom_ti_integer ( fid , 'J_PARENT_START' ,  config_flags%j_parent_start  , 1 , ierr )
512 
513 
514     IF ( switch .EQ. boundary_only ) THEN
515         CALL WRFU_TimeIntervalSet( bdy_increment, S=NINT(config_flags%bdyfrq),rc=rc)
516         next_time = currentTime + bdy_increment
517         CALL wrf_timetoa ( next_time, next_datestr )
518         CALL wrf_put_dom_td_char ( fid , 'THISBDYTIME' ,  current_date(1:19), current_date(1:19), ierr )
519         CALL wrf_put_dom_td_char ( fid , 'NEXTBDYTIME' ,  current_date(1:19), next_datestr(1:19), ierr )
520     ENDIF
521 
522     ! added grib2-specific metadata:  Todd Hutchinson 8/21/2005
523     IF ( use_package( io_form ) == IO_GRIB2 ) THEN
524       CALL wrf_put_dom_ti_integer ( fid , 'BACKGROUND_PROC_ID' , config_flags%background_proc_id , 1 , ierr )
525       CALL wrf_put_dom_ti_integer ( fid , 'FORECAST_PROC_ID' , config_flags%forecast_proc_id , 1 , ierr )
526       CALL wrf_put_dom_ti_integer ( fid , 'PRODUCTION_STATUS' , config_flags%production_status , 1 , ierr )
527       CALL wrf_put_dom_ti_integer ( fid , 'COMPRESSION' , config_flags%compression , 1 , ierr )
528     ENDIF
529 
530     CALL nl_get_adjust_output_times( grid%id, adjust ) 
531     current_date_save = current_date
532 #if 1
533     IF ( switch .EQ. model_input_only ) THEN
534       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_inputout.inc' )
535       CALL wrf_inputout( fid , grid , config_flags, switch, dryrun,  ierr )
536     ELSE IF ( switch .EQ. aux_model_input1_only ) THEN
537       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput1out.inc' )
538       CALL wrf_auxinput1out( fid , grid , config_flags, switch, dryrun,  ierr )
539     ELSE IF ( switch .EQ. aux_model_input2_only ) THEN
540       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput2out.inc' )
541       CALL wrf_auxinput2out( fid , grid , config_flags, switch, dryrun,  ierr )
542     ELSE IF ( switch .EQ. aux_model_input3_only ) THEN
543       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput3out.inc' )
544       CALL wrf_auxinput3out( fid , grid , config_flags, switch, dryrun,  ierr )
545     ELSE IF ( switch .EQ. aux_model_input4_only ) THEN
546       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput4out.inc' )
547       CALL wrf_auxinput4out( fid , grid , config_flags, switch, dryrun,  ierr )
548     ELSE IF ( switch .EQ. aux_model_input5_only ) THEN
549       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput5out.inc' )
550       CALL wrf_auxinput5out( fid , grid , config_flags, switch, dryrun,  ierr )
551     ELSE IF ( switch .EQ. aux_model_input6_only ) THEN
552       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput6out.inc' )
553       CALL wrf_auxinput6out( fid , grid , config_flags, switch, dryrun,  ierr )
554     ELSE IF ( switch .EQ. aux_model_input7_only ) THEN
555       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput7out.inc' )
556       CALL wrf_auxinput7out( fid , grid , config_flags, switch, dryrun,  ierr )
557     ELSE IF ( switch .EQ. aux_model_input8_only ) THEN
558       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput8out.inc' )
559       CALL wrf_auxinput8out( fid , grid , config_flags, switch, dryrun,  ierr )
560     ELSE IF ( switch .EQ. aux_model_input9_only ) THEN
561       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput9out.inc' )
562       CALL wrf_auxinput9out( fid , grid , config_flags, switch, dryrun,  ierr )
563     ELSE IF ( switch .EQ. aux_model_input10_only ) THEN
564       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput10out.inc' )
565       CALL wrf_auxinput10out( fid , grid , config_flags, switch, dryrun,  ierr )
566     ELSE IF ( switch .EQ. aux_model_input11_only ) THEN
567       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput11out.inc' )
568       CALL wrf_auxinput11out( fid , grid , config_flags, switch, dryrun,  ierr )
569     ELSE IF ( switch .EQ. history_only ) THEN
570       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_histout.inc' )
571       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( HISTORY_ALARM ), currentTime, startTime, current_date )
572       CALL wrf_histout( fid , grid , config_flags, switch, dryrun,  ierr )
573     ELSE IF ( switch .EQ. aux_hist1_only ) THEN
574       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist1out' )
575       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST1_ALARM ), currentTime, startTime, current_date )
576       CALL wrf_auxhist1out( fid , grid , config_flags, switch, dryrun,  ierr )
577     ELSE IF ( switch .EQ. aux_hist2_only ) THEN
578       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist2out.inc' )
579       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST2_ALARM ), currentTime, startTime, current_date )
580       CALL wrf_auxhist2out( fid , grid , config_flags, switch, dryrun,  ierr )
581     ELSE IF ( switch .EQ. aux_hist3_only ) THEN
582       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist3out.inc' )
583       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST3_ALARM ), currentTime, startTime, current_date )
584       CALL wrf_auxhist3out( fid , grid , config_flags, switch, dryrun,  ierr )
585     ELSE IF ( switch .EQ. aux_hist4_only ) THEN
586       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist4out.inc' )
587       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST4_ALARM ), currentTime, startTime, current_date )
588       CALL wrf_auxhist4out( fid , grid , config_flags, switch, dryrun,  ierr )
589     ELSE IF ( switch .EQ. aux_hist5_only ) THEN
590       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist5out.inc' )
591       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST5_ALARM ), currentTime, startTime, current_date )
592       CALL wrf_auxhist5out( fid , grid , config_flags, switch, dryrun,  ierr )
593     ELSE IF ( switch .EQ. aux_hist6_only ) THEN
594       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist6out.inc' )
595       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST6_ALARM ), currentTime, startTime, current_date )
596       CALL wrf_auxhist6out( fid , grid , config_flags, switch, dryrun,  ierr )
597     ELSE IF ( switch .EQ. aux_hist7_only ) THEN
598       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist7out.inc' )
599       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST7_ALARM ), currentTime, startTime, current_date )
600       CALL wrf_auxhist7out( fid , grid , config_flags, switch, dryrun,  ierr )
601     ELSE IF ( switch .EQ. aux_hist8_only ) THEN
602       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist8out.inc' )
603       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST8_ALARM ), currentTime, startTime, current_date )
604       CALL wrf_auxhist8out( fid , grid , config_flags, switch, dryrun,  ierr )
605     ELSE IF ( switch .EQ. aux_hist9_only ) THEN
606       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist9out.inc' )
607       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST9_ALARM ), currentTime, startTime, current_date )
608       CALL wrf_auxhist9out( fid , grid , config_flags, switch, dryrun,  ierr )
609     ELSE IF ( switch .EQ. aux_hist10_only ) THEN
610       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist10out.inc' )
611       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST10_ALARM ), currentTime, startTime, current_date )
612       CALL wrf_auxhist10out( fid , grid , config_flags, switch, dryrun,  ierr )
613     ELSE IF ( switch .EQ. aux_hist11_only ) THEN
614       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist11out.inc' )
615       IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST11_ALARM ), currentTime, startTime, current_date )
616       CALL wrf_auxhist11out( fid , grid , config_flags, switch, dryrun,  ierr )
617     ELSE IF ( switch .EQ. restart_only ) THEN
618       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_restartout.inc' )
619       CALL wrf_restartout( fid , grid , config_flags, switch, dryrun,  ierr )
620     ELSE IF ( switch .EQ. boundary_only ) THEN
621       CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_bdyout.inc' )
622       CALL wrf_bdyout( fid , grid , config_flags, switch, dryrun,  ierr )
623     ENDIF
624 #else
625     CALL wrf_message ( "ALL I/O DISABLED IN share/module_io_wrf.F")
626 #endif
627     current_date = current_date_save
628 
629     IF ( .NOT. dryrun ) THEN
630        CALL wrf_debug ( 300 , 'output_wrf: calling wrf_iosync ' )
631        CALL wrf_iosync ( fid , ierr )
632        CALL wrf_debug ( 300 , 'output_wrf: back from wrf_iosync ' )
633     ENDIF
634 
635     WRITE(wrf_err_message,*)'output_wrf: end, fid = ',fid
636     CALL wrf_debug( 300 , wrf_err_message )
637 
638     RETURN
639   END SUBROUTINE output_wrf