source: trunk/WRF.COMMON/WRFV3/share/output_wrf.F @ 3567

Last change on this file since 3567 was 2759, checked in by aslmd, 2 years ago

adding unmodified code from WRFV3.0.1.1, expurged from useless data +1M size

File size: 32.8 KB
Line 
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 km_opt, diff_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_diff_opt      ( 1, diff_opt                      )
157    call nl_get_km_opt        ( 1, km_opt                        )
158    call nl_get_damp_opt      ( 1, damp_opt                      )
159    call nl_get_khdif         ( grid%id,  khdif               )
160    call nl_get_kvdif         ( grid%id,  kvdif               )
161    call nl_get_mp_physics    ( grid%id,  mp_physics          )
162    call nl_get_ra_lw_physics ( grid%id,  ra_lw_physics       )
163    call nl_get_ra_sw_physics ( grid%id,  ra_sw_physics           )
164    call nl_get_sf_sfclay_physics  ( grid%id,  sf_sfclay_physics  )
165    call nl_get_sf_surface_physics ( grid%id,  sf_surface_physics )
166    call nl_get_bl_pbl_physics     ( grid%id,  bl_pbl_physics     )
167    call nl_get_cu_physics         ( grid%id,  cu_physics         )
168
169! add nml variables in 2.2
170    call nl_get_surface_input_source ( 1      ,  surface_input_source )
171    call nl_get_sst_update           ( 1      ,  sst_update           )
172    call nl_get_feedback             ( 1      ,  feedback             )
173    call nl_get_smooth_option        ( 1      ,  smooth_option        )
174    call nl_get_swrad_scat           ( 1      ,  swrad_scat           )
175    call nl_get_ucmcall              ( 1      ,  ucmcall              )
176    call nl_get_w_damping            ( 1      ,  w_damping            )
177
178#if (EM_CORE == 1)
179    CALL nl_get_pd_moist  ( grid%id , pd_moist )
180    CALL nl_get_pd_scalar ( grid%id , pd_scalar )
181    CALL nl_get_pd_tke    ( grid%id , pd_tke )
182    CALL nl_get_diff_6th_opt  ( grid%id , diff_6th_opt )
183    CALL nl_get_diff_6th_factor ( grid%id , diff_6th_factor )
184    CALL nl_get_grid_fdda  ( grid%id , grid_fdda )
185    CALL nl_get_gfdda_end_h( grid%id , gfdda_end_h )
186    CALL nl_get_gfdda_interval_m ( grid%id , gfdda_interval_m )
187
188    IF ( grid_fdda == 1 ) THEN
189    CALL nl_get_fgdt       ( grid%id , fgdt )
190    CALL nl_get_guv        ( grid%id , guv )
191    CALL nl_get_gt         ( grid%id , gt )
192    CALL nl_get_gq         ( grid%id , gq )
193    CALL nl_get_if_ramping ( 1       , if_ramping )
194    CALL nl_get_dtramp_min ( 1       , dtramp_min )
195    ENDIF
196
197    CALL nl_get_obs_nudge_opt  ( grid%id , obs_nudge_opt )
198    IF ( obs_nudge_opt == 1 ) THEN
199    CALL nl_get_fdda_end       ( grid%id , fdda_end )
200    CALL nl_get_obs_nudge_wind ( grid%id , obs_nudge_wind )
201    CALL nl_get_obs_coef_wind  ( grid%id , obs_coef_wind )
202    CALL nl_get_obs_nudge_temp ( grid%id , obs_nudge_temp )
203    CALL nl_get_obs_coef_temp  ( grid%id , obs_coef_temp )
204    CALL nl_get_obs_nudge_mois ( grid%id , obs_nudge_mois )
205    CALL nl_get_obs_coef_mois  ( grid%id , obs_coef_mois )
206    CALL nl_get_obs_nudge_pstr ( grid%id , obs_nudge_pstr )
207    CALL nl_get_obs_coef_pstr  ( grid%id , obs_coef_pstr )
208    CALL nl_get_obs_ionf       ( 1       , obs_ionf )
209    CALL nl_get_obs_idynin     ( 1       , obs_idynin )
210    CALL nl_get_obs_dtramp     ( 1       , obs_dtramp )
211    ENDIF
212#endif
213
214! julday and gmt can be set in namelist_03 for ideal.exe run
215    CALL nl_get_gmt (grid%id, gmt)
216    CALL nl_get_julyr (grid%id, julyr)
217    CALL nl_get_julday (grid%id, julday)
218    CALL nl_get_mminlu ( 1, char_junk(1:4) )
219    CALL nl_get_iswater (grid%id, iswater )
220    CALL nl_get_cen_lat ( grid%id , cen_lat )
221    CALL nl_get_cen_lon ( grid%id , cen_lon )
222    CALL nl_get_truelat1 ( grid%id , truelat1 )
223    CALL nl_get_truelat2 ( grid%id , truelat2 )
224    CALL nl_get_moad_cen_lat ( grid%id , moad_cen_lat )
225    CALL nl_get_stand_lon ( grid%id , stand_lon )
226    CALL nl_get_map_proj ( grid%id , map_proj )
227
228#if (EM_CORE == 1)
229    CALL nl_get_parent_id ( grid%id , parent_id )
230    CALL nl_get_i_parent_start ( grid%id , i_parent_start )
231    CALL nl_get_j_parent_start ( grid%id , j_parent_start )
232    CALL nl_get_parent_grid_ratio ( grid%id , parent_grid_ratio )
233#endif
234
235    CALL domain_clockprint(150, grid, &
236           'DEBUG output_wrf():  before call to domain_clock_get,')
237    CALL domain_clock_get( grid, current_time=currentTime, &
238                                 start_time=startTime,     &
239                                 current_timestr=current_date )
240    WRITE ( wrf_err_message , * ) 'output_wrf: begin, current_date=',current_date
241    CALL wrf_debug ( 300 , wrf_err_message )
242
243    WRITE( message , * ) "OUTPUT FROM " , TRIM(program_name)
244    CALL wrf_put_dom_ti_char ( fid , 'TITLE' , TRIM(message) , ierr )
245    ! added grib-specific metadata:  Todd Hutchinson 8/21/2005
246    IF ( ( use_package( io_form ) == IO_GRIB1 ) .OR. &
247         ( use_package( io_form ) == IO_GRIB2 ) ) THEN
248      CALL wrf_put_dom_ti_char ( fid, 'PROGRAM_NAME', TRIM(program_name) , ierr )
249    ENDIF
250    CALL nl_get_start_year(grid%id,start_year)
251    CALL nl_get_start_month(grid%id,start_month)
252    CALL nl_get_start_day(grid%id,start_day)
253    CALL nl_get_start_hour(grid%id,start_hour)
254    CALL nl_get_start_minute(grid%id,start_minute)
255    CALL nl_get_start_second(grid%id,start_second)
256#ifdef PLANET
257    WRITE ( start_date , FMT = '(I4.4,"-",I5.5,"_",I2.2,":",I2.2,":",I2.2)' ) &
258            start_year,start_day,start_hour,start_minute,start_second
259#else
260    WRITE ( start_date , FMT = '(I4.4,"-",I2.2,"-",I2.2,"_",I2.2,":",I2.2,":",I2.2)' ) &
261            start_year,start_month,start_day,start_hour,start_minute,start_second
262#endif
263    CALL wrf_put_dom_ti_char ( fid , 'START_DATE', TRIM(start_date) , ierr )
264    IF ( switch .EQ. model_input_only) THEN
265       CALL wrf_put_dom_ti_char ( fid , 'SIMULATION_START_DATE', TRIM(start_date) , ierr )
266    ELSE IF ( ( switch .EQ. restart_only ) .OR. ( switch .EQ. history_only ) ) THEN
267       CALL nl_get_simulation_start_year   ( 1, simulation_start_year   )
268       CALL nl_get_simulation_start_month  ( 1, simulation_start_month  )
269       CALL nl_get_simulation_start_day    ( 1, simulation_start_day    )
270       CALL nl_get_simulation_start_hour   ( 1, simulation_start_hour   )
271       CALL nl_get_simulation_start_minute ( 1, simulation_start_minute )
272       CALL nl_get_simulation_start_second ( 1, simulation_start_second )
273#ifdef PLANET
274       WRITE ( simulation_start_date , FMT = '(I4.4,"-",I5.5,"_",I2.2,":",I2.2,":",I2.2)' ) &
275               simulation_start_year,simulation_start_day,&
276               simulation_start_hour,simulation_start_minute,simulation_start_second
277#else
278       WRITE ( simulation_start_date , FMT = '(I4.4,"-",I2.2,"-",I2.2,"_",I2.2,":",I2.2,":",I2.2)' ) &
279               simulation_start_year,simulation_start_month,simulation_start_day,&
280               simulation_start_hour,simulation_start_minute,simulation_start_second
281#endif
282       CALL wrf_put_dom_ti_char ( fid , 'SIMULATION_START_DATE', TRIM(simulation_start_date) , ierr )
283    END IF
284
285    ibuf(1) = config_flags%e_we - config_flags%s_we + 1
286    CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_GRID_DIMENSION' ,  ibuf , 1 , ierr )
287
288    ibuf(1) = config_flags%e_sn - config_flags%s_sn + 1
289    CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_GRID_DIMENSION' , ibuf , 1 , ierr )
290
291    ibuf(1) = config_flags%e_vert - config_flags%s_vert + 1
292    CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_GRID_DIMENSION' , ibuf , 1 , ierr )
293
294#if (EM_CORE == 1)
295    IF (grid%map_proj == 6) THEN
296       ! Global ... dx determined automatically
297       ! Don't use value from namelist ... used derived value instead
298       CALL wrf_put_dom_ti_real ( fid , 'DX' , grid%dx , 1 , ierr )
299       CALL wrf_put_dom_ti_real ( fid , 'DY' , grid%dy , 1 , ierr )
300    ELSE
301       CALL wrf_put_dom_ti_real ( fid , 'DX' , config_flags%dx , 1 , ierr )
302       CALL wrf_put_dom_ti_real ( fid , 'DY' , config_flags%dy , 1 , ierr )
303    END IF
304#endif
305
306! added this metadatum for H. Chuan, NCEP, 030417, JM
307#if (NMM_CORE == 1)
308          CALL wrf_put_dom_ti_char ( fid , 'GRIDTYPE',  'E' , ierr )
309#endif
310#if (EM_CORE == 1)
311          CALL wrf_put_dom_ti_char ( fid , 'GRIDTYPE',  'C' , ierr )
312#endif
313#if (COAMPS_CORE == 1 )
314          CALL wrf_put_dom_ti_char ( fid , 'GRIDTYPE',  'B' , ierr )
315#endif
316
317! added these fields for W. Skamarock, 020402, JM
318    ibuf(1) = diff_opt
319    CALL wrf_put_dom_ti_integer ( fid , 'DIFF_OPT' ,  ibuf , 1 , ierr )
320    ibuf(1) = km_opt
321    CALL wrf_put_dom_ti_integer ( fid , 'KM_OPT' ,  ibuf , 1 , ierr )
322    ibuf(1) = damp_opt
323    CALL wrf_put_dom_ti_integer ( fid , 'DAMP_OPT' ,  ibuf , 1 , ierr )
324    rbuf(1) = khdif
325    CALL wrf_put_dom_ti_real    ( fid , 'KHDIF' ,  rbuf , 1 , ierr )
326    rbuf(1) = kvdif
327    CALL wrf_put_dom_ti_real    ( fid , 'KVDIF' ,  rbuf , 1 , ierr )
328    ibuf(1) = mp_physics
329    CALL wrf_put_dom_ti_integer ( fid , 'MP_PHYSICS' ,  ibuf , 1 , ierr )
330    ibuf(1) = ra_lw_physics
331    CALL wrf_put_dom_ti_integer ( fid , 'RA_LW_PHYSICS' ,  ibuf , 1 , ierr )
332    ibuf(1) = ra_sw_physics
333    CALL wrf_put_dom_ti_integer ( fid , 'RA_SW_PHYSICS' ,  ibuf , 1 , ierr )
334    ibuf(1) = sf_sfclay_physics
335    CALL wrf_put_dom_ti_integer ( fid , 'SF_SFCLAY_PHYSICS' ,  ibuf , 1 , ierr )
336    ibuf(1) = sf_surface_physics
337    CALL wrf_put_dom_ti_integer ( fid , 'SF_SURFACE_PHYSICS' ,  ibuf , 1 , ierr )
338    ibuf(1) = bl_pbl_physics
339    CALL wrf_put_dom_ti_integer ( fid , 'BL_PBL_PHYSICS' ,  ibuf , 1 , ierr )
340    ibuf(1) = cu_physics
341    CALL wrf_put_dom_ti_integer ( fid , 'CU_PHYSICS' ,  ibuf , 1 , ierr )
342
343    ! added netcdf-specific metadata:
344    IF ( ( use_package( io_form ) == IO_NETCDF ) .OR. &
345         ( use_package( io_form ) == IO_PHDF5  ) .OR. &
346         ( use_package( io_form ) == IO_PNETCDF ) ) THEN
347      CALL wrf_put_dom_ti_integer ( fid, 'SURFACE_INPUT_SOURCE', surface_input_source , 1 , ierr )
348      CALL wrf_put_dom_ti_integer ( fid, 'SST_UPDATE', sst_update , 1 , ierr )
349#if (EM_CORE == 1)
350      CALL wrf_put_dom_ti_integer ( fid, 'GRID_FDDA', grid_fdda , 1 , ierr )
351      CALL wrf_put_dom_ti_integer ( fid, 'GFDDA_INTERVAL_M', gfdda_interval_m , 1 , ierr )
352      CALL wrf_put_dom_ti_integer ( fid, 'GFDDA_END_H', gfdda_end_h , 1 , ierr )
353#endif
354
355      IF ( switch .EQ. history_only ) THEN
356      CALL wrf_put_dom_ti_integer ( fid, 'UCMCALL', ucmcall , 1 , ierr )
357      CALL wrf_put_dom_ti_integer ( fid, 'FEEDBACK', feedback , 1 , ierr )
358      CALL wrf_put_dom_ti_integer ( fid, 'SMOOTH_OPTION', smooth_option , 1 , ierr )
359      CALL wrf_put_dom_ti_real    ( fid, 'SWRAD_SCAT', swrad_scat , 1 , ierr )
360      CALL wrf_put_dom_ti_integer ( fid, 'W_DAMPING', w_damping , 1 , ierr )
361
362#if (EM_CORE == 1)
363      CALL wrf_put_dom_ti_logical ( fid, 'PD_MOIST', pd_moist , 1 , ierr )
364      CALL wrf_put_dom_ti_logical ( fid, 'PD_SCALAR', pd_scalar , 1 , ierr )
365      CALL wrf_put_dom_ti_logical ( fid, 'PD_TKE', pd_tke , 1 , ierr )
366      CALL wrf_put_dom_ti_integer ( fid, 'DIFF_6TH_OPT', diff_6th_opt , 1 , ierr )
367      CALL wrf_put_dom_ti_real    ( fid, 'DIFF_6TH_FACTOR', diff_6th_factor , 1 , ierr )
368
369      IF ( grid_fdda == 1 ) THEN
370        CALL wrf_put_dom_ti_real    ( fid, 'FGDT', fgdt , 1 , ierr )
371        CALL wrf_put_dom_ti_real    ( fid, 'GUV', guv , 1 , ierr )
372        CALL wrf_put_dom_ti_real    ( fid, 'GT', gt , 1 , ierr )
373        CALL wrf_put_dom_ti_real    ( fid, 'GQ', gq , 1 , ierr )
374        CALL wrf_put_dom_ti_integer ( fid, 'IF_RAMPING', if_ramping , 1 , ierr )
375        CALL wrf_put_dom_ti_real    ( fid, 'DTRAMP_MIN', dtramp_min , 1 , ierr )
376      ENDIF
377
378      CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_OPT', obs_nudge_opt , 1 , ierr )
379      IF ( obs_nudge_opt == 1 ) THEN
380        CALL wrf_put_dom_ti_real    ( fid, 'FDDA_END', fdda_end , 1 , ierr )
381        CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_WIND', obs_nudge_wind , 1 , ierr )
382        CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_WIND', obs_coef_wind , 1 , ierr )
383        CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_TEMP', obs_nudge_temp , 1 , ierr )
384        CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_TEMP', obs_coef_temp , 1 , ierr )
385        CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_MOIS', obs_nudge_mois , 1 , ierr )
386        CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_MOIS', obs_coef_mois , 1 , ierr )
387        CALL wrf_put_dom_ti_integer ( fid, 'OBS_NUDGE_PSTR', obs_nudge_pstr , 1 , ierr )
388        CALL wrf_put_dom_ti_real    ( fid, 'OBS_COEF_PSTR', obs_coef_pstr , 1 , ierr )
389        CALL wrf_put_dom_ti_integer ( fid, 'OBS_IONF', obs_ionf , 1 , ierr )
390        CALL wrf_put_dom_ti_integer ( fid, 'OBS_IDYNIN', obs_idynin , 1 , ierr )
391        CALL wrf_put_dom_ti_real    ( fid, 'OBS_DTRAMP', obs_dtramp , 1 , ierr )
392      ENDIF
393#endif
394      ENDIF ! history_only
395    ENDIF
396
397! added these fields for use by reassembly programs , 010831, JM
398! modified these fields so "patch" == "domain" when multi-file output
399! formats are not used.  051018, TBH
400
401    ibuf(1) = MAX(ips,ids)
402    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ids
403    CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_START_UNSTAG' ,  ibuf , 1 , ierr )
404    ibuf(1) = MIN(ipe,ide-1)
405    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ide - 1
406    CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_END_UNSTAG' ,  ibuf , 1 , ierr )
407    ibuf(1) = MAX(ips,ids)
408    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ids
409    CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_START_STAG' ,  ibuf , 1 , ierr )
410    ibuf(1) = MIN(ipe,ide)
411    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = ide
412    CALL wrf_put_dom_ti_integer ( fid , 'WEST-EAST_PATCH_END_STAG' ,  ibuf , 1 , ierr )
413    ibuf(1) = MAX(jps,jds)
414    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jds
415    CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_START_UNSTAG' ,  ibuf , 1 , ierr )
416    ibuf(1) = MIN(jpe,jde-1)
417    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jde - 1
418    CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_END_UNSTAG' ,  ibuf , 1 , ierr )
419    ibuf(1) = MAX(jps,jds)
420    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jds
421    CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_START_STAG' ,  ibuf , 1 , ierr )
422    ibuf(1) = MIN(jpe,jde)
423    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = jde
424    CALL wrf_put_dom_ti_integer ( fid , 'SOUTH-NORTH_PATCH_END_STAG' ,  ibuf , 1 , ierr )
425
426    ibuf(1) = MAX(kps,kds)
427    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kds
428    CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_START_UNSTAG' ,  ibuf , 1 , ierr )
429    ibuf(1) = MIN(kpe,kde-1)
430    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kde - 1
431    CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_END_UNSTAG' ,  ibuf , 1 , ierr )
432    ibuf(1) = MAX(kps,kds)
433    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kds
434    CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_START_STAG' ,  ibuf , 1 , ierr )
435    ibuf(1) = MIN(kpe,kde)
436    IF ( .NOT. multi_files ( io_form ) ) ibuf(1) = kde
437    CALL wrf_put_dom_ti_integer ( fid , 'BOTTOM-TOP_PATCH_END_STAG' ,  ibuf , 1 , ierr )
438#if (EM_CORE == 1)
439    ibuf(1) = grid%id
440    CALL wrf_put_dom_ti_integer ( fid , 'GRID_ID' ,  ibuf , 1 , ierr )
441    ibuf(1) = parent_id
442    CALL wrf_put_dom_ti_integer ( fid , 'PARENT_ID' ,  ibuf , 1 , ierr )
443    ibuf(1) = i_parent_start
444    CALL wrf_put_dom_ti_integer ( fid , 'I_PARENT_START' ,  ibuf , 1 , ierr )
445    ibuf(1) = j_parent_start
446    CALL wrf_put_dom_ti_integer ( fid , 'J_PARENT_START' ,  ibuf , 1 , ierr )
447    ibuf(1) = parent_grid_ratio
448    CALL wrf_put_dom_ti_integer ( fid , 'PARENT_GRID_RATIO' ,  ibuf , 1 , ierr )
449#endif
450
451! end add 010831 JM
452
453#if (EM_CORE != 1)
454    CALL wrf_put_dom_ti_real ( fid , 'DX' ,  config_flags%dx , 1 , ierr )
455    CALL wrf_put_dom_ti_real ( fid , 'DY' ,  config_flags%dy , 1 , ierr )
456#endif
457! Updated by T. Hutchinson to use adaptive time step.
458    CALL wrf_put_dom_ti_real ( fid , 'DT' ,  grid%dt , 1 , ierr )
459!    CALL wrf_put_dom_ti_real ( fid , 'DT' ,  config%dt , 1 , ierr )
460    CALL wrf_put_dom_ti_real ( fid , 'CEN_LAT' ,  config_flags%cen_lat , 1 , ierr )
461    CALL wrf_put_dom_ti_real ( fid , 'CEN_LON' ,  config_flags%cen_lon , 1 , ierr )
462    CALL wrf_put_dom_ti_real ( fid , 'TRUELAT1',  config_flags%truelat1, 1 , ierr )
463    CALL wrf_put_dom_ti_real ( fid , 'TRUELAT2',  config_flags%truelat2, 1 , ierr )
464    CALL wrf_put_dom_ti_real ( fid , 'MOAD_CEN_LAT',  config_flags%moad_cen_lat, 1 , ierr )
465    CALL wrf_put_dom_ti_real ( fid , 'STAND_LON',  config_flags%stand_lon, 1 , ierr )
466    IF ( switch .NE. boundary_only ) THEN
467#ifdef PLANET
468      ! When writing to restart files, use the values of the instantaneous
469      ! time for determining the values of JULYR, JULDAY, and GMT.  If the
470      ! original values in config_flags are used, this assumes that the
471      ! restart simulation will start with an itimestep NE 0.  If we use
472      ! the instantaneous time, we can start a restart simulation with a
473      ! different value of delta-t for timestep and still get the clocks
474      ! calendars (and orbital information!) correct.
475      !
476      ! Current time is still defined from above call to WRF_UTIL_ClockGet
477      CALL WRFU_TimeGet( currentTime, YY=julyr, dayOfYear=julday, H=p_hr, M=p_min, S=p_sec, MS=p_ms, rc=rc)
478      WRITE(wrf_err_message,*)'output_wrf: julyr,julday,hr,min,sec,ms = ',julyr,julday,p_hr,p_min,p_sec,p_ms
479      CALL wrf_debug( 100 , wrf_err_message )
480      gmt = REAL(p_hr)+REAL(p_min)/60.+REAL(p_sec)/3600.+REAL(p_ms)/3600000.
481      CALL wrf_put_dom_ti_real ( fid , 'GMT' ,  gmt , 1 , ierr )
482      CALL wrf_put_dom_ti_integer ( fid , 'JULYR' ,  julyr , 1 , ierr )
483      CALL wrf_put_dom_ti_integer ( fid , 'JULDAY' ,  julday , 1 , ierr )
484#else
485      CALL wrf_put_dom_ti_real ( fid , 'GMT' ,  config_flags%gmt , 1 , ierr )
486      CALL wrf_put_dom_ti_integer ( fid , 'JULYR' ,  config_flags%julyr , 1 , ierr )
487      CALL wrf_put_dom_ti_integer ( fid , 'JULDAY' ,  config_flags%julday , 1 , ierr )
488#endif
489    ENDIF
490#if (NMM_CORE == 1)
491        write(0,*) 'MMINLU would be: ', MMINLU(1:4)
492        MMINLU(1:4)='USGS'
493        write(0,*) 'MMINLU now: ', MMINLU(1:4)
494#endif
495    CALL wrf_put_dom_ti_integer ( fid , 'MAP_PROJ' ,  config_flags%map_proj , 1 , ierr )
496    CALL wrf_put_dom_ti_char ( fid , 'MMINLU',  mminlu(1:4) , ierr )
497    CALL wrf_put_dom_ti_integer ( fid , 'ISWATER' ,  iswater , 1 , ierr )
498!   CALL wrf_put_dom_ti_integer ( fid , 'ISWATER' ,  config_flags%iswater , 1 , ierr )
499    CALL wrf_put_dom_ti_integer ( fid , 'ISICE' ,  config_flags%isice , 1 , ierr )
500    CALL wrf_put_dom_ti_integer ( fid , 'ISURBAN' ,  config_flags%isurban , 1 , ierr )
501    CALL wrf_put_dom_ti_integer ( fid , 'ISOILWATER' ,  config_flags%isoilwater , 1 , ierr )
502! added these fields for restarting of moving nests, JM
503    CALL wrf_put_dom_ti_integer ( fid , 'I_PARENT_START' ,  config_flags%i_parent_start  , 1 , ierr )
504    CALL wrf_put_dom_ti_integer ( fid , 'J_PARENT_START' ,  config_flags%j_parent_start  , 1 , ierr )
505
506
507    IF ( switch .EQ. boundary_only ) THEN
508        CALL WRFU_TimeIntervalSet( bdy_increment, S=NINT(config_flags%bdyfrq),rc=rc)
509        next_time = currentTime + bdy_increment
510        CALL wrf_timetoa ( next_time, next_datestr )
511        CALL wrf_put_dom_td_char ( fid , 'THISBDYTIME' ,  current_date(1:19), current_date(1:19), ierr )
512        CALL wrf_put_dom_td_char ( fid , 'NEXTBDYTIME' ,  current_date(1:19), next_datestr(1:19), ierr )
513    ENDIF
514
515    ! added grib2-specific metadata:  Todd Hutchinson 8/21/2005
516    IF ( use_package( io_form ) == IO_GRIB2 ) THEN
517      CALL wrf_put_dom_ti_integer ( fid , 'BACKGROUND_PROC_ID' , config_flags%background_proc_id , 1 , ierr )
518      CALL wrf_put_dom_ti_integer ( fid , 'FORECAST_PROC_ID' , config_flags%forecast_proc_id , 1 , ierr )
519      CALL wrf_put_dom_ti_integer ( fid , 'PRODUCTION_STATUS' , config_flags%production_status , 1 , ierr )
520      CALL wrf_put_dom_ti_integer ( fid , 'COMPRESSION' , config_flags%compression , 1 , ierr )
521    ENDIF
522
523    CALL nl_get_adjust_output_times( grid%id, adjust )
524    current_date_save = current_date
525#if 1
526    IF ( switch .EQ. model_input_only ) THEN
527      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_inputout.inc' )
528      CALL wrf_inputout( fid , grid , config_flags, switch, dryrun,  ierr )
529    ELSE IF ( switch .EQ. aux_model_input1_only ) THEN
530      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput1out.inc' )
531      CALL wrf_auxinput1out( fid , grid , config_flags, switch, dryrun,  ierr )
532    ELSE IF ( switch .EQ. aux_model_input2_only ) THEN
533      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput2out.inc' )
534      CALL wrf_auxinput2out( fid , grid , config_flags, switch, dryrun,  ierr )
535    ELSE IF ( switch .EQ. aux_model_input3_only ) THEN
536      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput3out.inc' )
537      CALL wrf_auxinput3out( fid , grid , config_flags, switch, dryrun,  ierr )
538    ELSE IF ( switch .EQ. aux_model_input4_only ) THEN
539      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput4out.inc' )
540      CALL wrf_auxinput4out( fid , grid , config_flags, switch, dryrun,  ierr )
541    ELSE IF ( switch .EQ. aux_model_input5_only ) THEN
542      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput5out.inc' )
543      CALL wrf_auxinput5out( fid , grid , config_flags, switch, dryrun,  ierr )
544    ELSE IF ( switch .EQ. aux_model_input6_only ) THEN
545      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput6out.inc' )
546      CALL wrf_auxinput6out( fid , grid , config_flags, switch, dryrun,  ierr )
547    ELSE IF ( switch .EQ. aux_model_input7_only ) THEN
548      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput7out.inc' )
549      CALL wrf_auxinput7out( fid , grid , config_flags, switch, dryrun,  ierr )
550    ELSE IF ( switch .EQ. aux_model_input8_only ) THEN
551      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput8out.inc' )
552      CALL wrf_auxinput8out( fid , grid , config_flags, switch, dryrun,  ierr )
553    ELSE IF ( switch .EQ. aux_model_input9_only ) THEN
554      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput9out.inc' )
555      CALL wrf_auxinput9out( fid , grid , config_flags, switch, dryrun,  ierr )
556    ELSE IF ( switch .EQ. aux_model_input10_only ) THEN
557      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput10out.inc' )
558      CALL wrf_auxinput10out( fid , grid , config_flags, switch, dryrun,  ierr )
559    ELSE IF ( switch .EQ. aux_model_input11_only ) THEN
560      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxinput11out.inc' )
561      CALL wrf_auxinput11out( fid , grid , config_flags, switch, dryrun,  ierr )
562    ELSE IF ( switch .EQ. history_only ) THEN
563      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_histout.inc' )
564      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( HISTORY_ALARM ), currentTime, startTime, current_date )
565      CALL wrf_histout( fid , grid , config_flags, switch, dryrun,  ierr )
566    ELSE IF ( switch .EQ. aux_hist1_only ) THEN
567      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist1out' )
568      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST1_ALARM ), currentTime, startTime, current_date )
569      CALL wrf_auxhist1out( fid , grid , config_flags, switch, dryrun,  ierr )
570    ELSE IF ( switch .EQ. aux_hist2_only ) THEN
571      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist2out.inc' )
572      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST2_ALARM ), currentTime, startTime, current_date )
573      CALL wrf_auxhist2out( fid , grid , config_flags, switch, dryrun,  ierr )
574    ELSE IF ( switch .EQ. aux_hist3_only ) THEN
575      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist3out.inc' )
576      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST3_ALARM ), currentTime, startTime, current_date )
577      CALL wrf_auxhist3out( fid , grid , config_flags, switch, dryrun,  ierr )
578    ELSE IF ( switch .EQ. aux_hist4_only ) THEN
579      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist4out.inc' )
580      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST4_ALARM ), currentTime, startTime, current_date )
581      CALL wrf_auxhist4out( fid , grid , config_flags, switch, dryrun,  ierr )
582    ELSE IF ( switch .EQ. aux_hist5_only ) THEN
583      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist5out.inc' )
584      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST5_ALARM ), currentTime, startTime, current_date )
585      CALL wrf_auxhist5out( fid , grid , config_flags, switch, dryrun,  ierr )
586    ELSE IF ( switch .EQ. aux_hist6_only ) THEN
587      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist6out.inc' )
588      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST6_ALARM ), currentTime, startTime, current_date )
589      CALL wrf_auxhist6out( fid , grid , config_flags, switch, dryrun,  ierr )
590    ELSE IF ( switch .EQ. aux_hist7_only ) THEN
591      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist7out.inc' )
592      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST7_ALARM ), currentTime, startTime, current_date )
593      CALL wrf_auxhist7out( fid , grid , config_flags, switch, dryrun,  ierr )
594    ELSE IF ( switch .EQ. aux_hist8_only ) THEN
595      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist8out.inc' )
596      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST8_ALARM ), currentTime, startTime, current_date )
597      CALL wrf_auxhist8out( fid , grid , config_flags, switch, dryrun,  ierr )
598    ELSE IF ( switch .EQ. aux_hist9_only ) THEN
599      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist9out.inc' )
600      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST9_ALARM ), currentTime, startTime, current_date )
601      CALL wrf_auxhist9out( fid , grid , config_flags, switch, dryrun,  ierr )
602    ELSE IF ( switch .EQ. aux_hist10_only ) THEN
603      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist10out.inc' )
604      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST10_ALARM ), currentTime, startTime, current_date )
605      CALL wrf_auxhist10out( fid , grid , config_flags, switch, dryrun,  ierr )
606    ELSE IF ( switch .EQ. aux_hist11_only ) THEN
607      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_auxhist11out.inc' )
608      IF ( adjust ) CALL adjust_io_timestr( grid%io_intervals( AUXHIST11_ALARM ), currentTime, startTime, current_date )
609      CALL wrf_auxhist11out( fid , grid , config_flags, switch, dryrun,  ierr )
610    ELSE IF ( switch .EQ. restart_only ) THEN
611      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_restartout.inc' )
612      CALL wrf_restartout( fid , grid , config_flags, switch, dryrun,  ierr )
613    ELSE IF ( switch .EQ. boundary_only ) THEN
614      CALL wrf_debug ( 300 , 'output_wrf: calling code in wrf_bdyout.inc' )
615      CALL wrf_bdyout( fid , grid , config_flags, switch, dryrun,  ierr )
616    ENDIF
617#else
618    CALL wrf_message ( "ALL I/O DISABLED IN share/module_io_wrf.F")
619#endif
620    current_date = current_date_save
621
622    IF ( .NOT. dryrun ) THEN
623       CALL wrf_debug ( 300 , 'output_wrf: calling wrf_iosync ' )
624       CALL wrf_iosync ( fid , ierr )
625       CALL wrf_debug ( 300 , 'output_wrf: back from wrf_iosync ' )
626    ENDIF
627
628    WRITE(wrf_err_message,*)'output_wrf: end, fid = ',fid
629    CALL wrf_debug( 300 , wrf_err_message )
630
631    RETURN
632  END SUBROUTINE output_wrf
Note: See TracBrowser for help on using the repository browser.