source: trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/share/output_wrf.F @ 609

Last change on this file since 609 was 11, checked in by aslmd, 14 years ago

spiga@svn-planeto:ajoute le modele meso-echelle martien

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