2 !WRF:MEDIATION_LAYER:IO
6 SUBROUTINE med_calc_model_time ( grid , config_flags )
8 USE module_domain , ONLY : domain, domain_clock_get
9 USE module_configure , ONLY : grid_config_rec_type
17 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
22 ! this is now handled by with calls to time manager
23 ! time = head_grid%dt * head_grid%total_time_steps
24 ! CALL calc_current_date (grid%id, time)
27 END SUBROUTINE med_calc_model_time
29 SUBROUTINE med_before_solve_io ( grid , config_flags )
31 USE module_state_description
32 USE module_domain , ONLY : domain, domain_clock_get
33 USE module_configure , ONLY : grid_config_rec_type
38 USE module_domain , ONLY : domain_clock_set, get_ijk_from_grid
39 USE module_configure , ONLY : model_config_rec
40 USE mediation_pertmod_io , ONLY : save_tl_pert, read_ad_forcing, save_xtraj, read_xtraj, read_xtraj_reverse
41 USE module_bc_em, ONLY : rk_phys_bc_dry_2
42 USE module_bc, ONLY : set_physical_bc3d
43 USE wrf_esmf_timemod, ONLY : ESMF_TimeInc
46 USE module_dm, ONLY : ntasks_x, ntasks_y, &
47 local_communicator, mytask, ntasks
48 USE module_comm_dm, ONLY : halo_em_init_1_sub, halo_em_init_2_sub, halo_em_init_5_sub
55 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
59 TYPE(WRFU_Time) :: currTime, startTime
61 CHARACTER*256 :: message
63 INTEGER :: ids , ide , jds , jde , kds , kde , &
64 ims , ime , jms , jme , kms , kme , &
65 ips , ipe , jps , jpe , kps , kpe, ij, im
66 CHARACTER*80 :: timestr
67 REAL, POINTER :: moist(:,:,:,:), scalar(:,:,:,:), chem(:,:,:,:), tracer(:,:,:,:)
69 ! In WRFPLUS NL run, boundary should be read before save xtraj.
71 CALL WRFU_ClockGet( grid%domain_clock, CurrTime=currTime, StartTime=startTime )
72 IF ( ( WRFU_AlarmIsRinging( grid%alarms( RESTART_ALARM ), rc=rc ) ) .AND. &
73 ( currTime .NE. startTime ) ) THEN
74 IF ( grid%id .EQ. 1 ) THEN
75 ! Only the parent initiates the restart writing. Otherwise, different
76 ! domains may be written out at different times and with different
77 ! time stamps in the file names.
78 CALL med_restart_out ( grid , config_flags )
80 CALL WRFU_AlarmRingerOff( grid%alarms( RESTART_ALARM ), rc=rc )
82 CALL WRFU_AlarmRingerOff( grid%alarms( RESTART_ALARM ), rc=rc )
85 ! - Look for boundary data after writing out history and restart files
86 CALL med_latbound_in ( grid , config_flags )
89 CALL WRFU_ClockGet( grid%domain_clock, CurrTime=currTime, StartTime=startTime )
91 IF( (WRFU_AlarmIsRinging( grid%alarms( HISTORY_ALARM ), rc=rc ) .AND. &
92 (grid%dfi_write_dfi_history .OR. grid%dfi_stage == DFI_FST .OR. grid%dfi_opt == DFI_NODFI) )) THEN
93 IF ( ( config_flags%restart ) .AND. &
94 ( config_flags%write_hist_at_0h_rst ) .AND. &
95 ( currTime .EQ. startTime ) ) THEN
96 ! output history at beginning of restart if alarm is ringing
97 CALL med_hist_out ( grid , HISTORY_ALARM, config_flags )
99 ELSE IF ( ( config_flags%restart ) .AND. &
100 ( .NOT. config_flags%write_hist_at_0h_rst ) .AND. &
101 ( currTime .EQ. startTime ) ) THEN
102 ! we do not do anything
104 CALL med_hist_out ( grid , HISTORY_ALARM, config_flags )
107 CALL WRFU_AlarmRingerOff( grid%alarms( HISTORY_ALARM ), rc=rc )
108 ELSE IF ( (config_flags%restart) .AND. ( currTime .EQ. startTime ) .AND. &
109 ( config_flags%write_hist_at_0h_rst ) ) THEN
110 ! output history at beginning of restart even if alarm is not ringing
111 CALL med_hist_out ( grid , HISTORY_ALARM, config_flags )
112 CALL WRFU_AlarmRingerOff( grid%alarms( HISTORY_ALARM ), rc=rc )
115 IF( WRFU_AlarmIsRinging( grid%alarms( INPUTOUT_ALARM ), rc=rc ) ) THEN
116 CALL med_filter_out ( grid , config_flags )
117 CALL WRFU_AlarmRingerOff( grid%alarms( INPUTOUT_ALARM ), rc=rc )
120 DO ialarm = first_auxhist, last_auxhist
122 rc = 1 ! dummy statement
123 ELSE IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
125 IF ( .NOT. grid%trajectory_io ) THEN
126 ! For wrfplus, only allow tl and nl output histoty files.
127 IF ( config_flags%dyn_opt .EQ. dyn_em_tl .OR. config_flags%dyn_opt .EQ. dyn_em ) THEN
128 CALL med_hist_out ( grid , ialarm, config_flags )
131 IF ( ialarm .EQ. auxhist8_only ) THEN ! TL perturbation only
132 CALL domain_clock_get ( grid, current_timestr=message )
133 IF ( config_flags%dyn_opt .EQ. dyn_em_tl .and. .not. config_flags%tl_standalone ) THEN
134 CALL save_tl_pert ( message )
135 ELSEIF ( config_flags%dyn_opt .EQ. dyn_em_tl .and. config_flags%tl_standalone ) THEN
136 CALL med_hist_out ( grid , ialarm, config_flags )
139 IF ( ialarm .EQ. auxhist6_only ) THEN ! trajectory only
140 CALL domain_clock_get ( grid, current_timestr=message )
141 IF ( config_flags%dyn_opt .EQ. dyn_em ) THEN
142 CALL save_xtraj ( message )
147 !----------------------------------------------------------------------
148 ! RASM Climate Diagnostics - JR, AS, MS - October 2016
149 !----------------------------------------------------------------------
150 IF ( (ialarm .EQ. AUXHIST5_ALARM) .AND. (config_flags%restart) .AND. ( currTime .EQ. startTime ) ) THEN
151 ! no AVG history output on the first time of the restart
152 ELSE IF ( (ialarm .EQ. AUXHIST6_ALARM) .AND. (config_flags%restart) .AND. ( currTime .EQ. startTime ) ) THEN
153 ! no DIURNAL history output on the first time of the restart
154 ELSE IF ( grid%dfi_stage == DFI_FST .OR. grid%dfi_opt == DFI_NODFI ) THEN
155 CALL med_hist_out ( grid , ialarm, config_flags )
157 !----------------------------------------------------------------------
158 ! end RASM Climate Diagnostics
159 !----------------------------------------------------------------------
161 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
165 DO ialarm = first_auxinput, last_auxinput
167 rc = 1 ! dummy statement
168 #if ( WRF_CHEM == 1 )
169 ! - Get chemistry data
170 ELSE IF( ialarm .EQ. AUXINPUT5_ALARM .AND. config_flags%chem_opt > 0 ) THEN
171 IF( config_flags%emiss_inpt_opt /= 0 ) THEN
172 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) .OR. &
173 ((config_flags%restart) .AND. ( currTime .EQ. startTime ))) THEN
174 call wrf_debug(15,' CALL med_read_wrf_chem_emiss ')
175 CALL med_read_wrf_chem_emiss ( grid , config_flags )
176 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
177 call wrf_debug(15,' Back from CALL med_read_wrf_chem_emiss ')
180 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
181 CALL med_auxinput_in ( grid, ialarm, config_flags )
182 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
185 ELSE IF(( ialarm .EQ. AUXINPUT7_ALARM .AND. config_flags%chem_opt > 0 ) .or. &
186 ( ialarm .EQ. AUXINPUT7_ALARM .AND. config_flags%tracer_opt > 0 ) )THEN
187 IF( config_flags%biomass_burn_opt /= 0 ) THEN
188 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) .OR. &
189 ((config_flags%restart) .AND. ( currTime .EQ. startTime ))) THEN
190 CALL med_auxinput_in ( grid, ialarm, config_flags )
191 WRITE ( message , FMT='(A,i3,A,i3)') 'Input data processed for aux input ',&
192 ialarm - first_auxinput + 1, ' for domain ',grid%id
193 CALL wrf_debug ( 15 , message )
194 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
197 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
198 CALL med_auxinput_in ( grid, ialarm, config_flags )
199 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
202 ELSE IF( ialarm .EQ. AUXINPUT13_ALARM .AND. config_flags%chem_opt > 0 ) THEN
203 IF( config_flags%emiss_opt_vol /= 0 ) THEN
204 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
205 call wrf_debug(15,' CALL med_read_wrf_volc_emiss ')
206 CALL med_read_wrf_volc_emiss ( grid , config_flags )
207 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
208 call wrf_debug(15,' Back from CALL med_read_wrf_volc_emiss ')
211 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
212 CALL med_auxinput_in ( grid, ialarm, config_flags )
213 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
217 ELSE IF( ialarm .EQ. AUXINPUT17_ALARM ) THEN
218 IF( config_flags%qna_update .EQ. 1) THEN
219 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
220 call wrf_debug(00,' CALL med_read_qna_emissions ')
221 CALL med_read_qna_emissions ( grid , config_flags )
222 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
223 call wrf_debug(00,' Back from CALL med_read_qna_emissions ')
226 IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
227 CALL med_auxinput_in ( grid, ialarm, config_flags )
228 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
232 ELSE IF( ialarm .EQ. AUXINPUT11_ALARM ) THEN
233 IF( config_flags%obs_nudge_opt .EQ. 1) THEN
234 CALL med_fddaobs_in ( grid , config_flags )
237 ELSE IF( WRFU_AlarmIsRinging( grid%alarms( ialarm ), rc=rc ) ) THEN
239 IF ( .NOT. grid%trajectory_io ) THEN
240 ! For adjoint integration with disk IO, the basic state is one step before the domain time.
241 IF ( config_flags%dyn_opt .EQ. dyn_em_ad .AND. ialarm .EQ. auxinput6_only ) THEN
242 grid%domain_clock%clockint%CurrTime = ESMF_TimeInc (grid%domain_clock%clockint%CurrTime, &
243 grid%domain_clock%clockint%TimeStep )
245 CALL med_auxinput_in ( grid, ialarm, config_flags )
246 IF ( config_flags%dyn_opt .EQ. dyn_em_ad .AND. ialarm .EQ. auxinput6_only ) THEN
247 CALL domain_clock_get( grid, current_time=currTime, start_time=startTime, &
248 current_timestr=timestr )
249 WRITE(message, FMT='(A,A)') 'read xtraj from file at time stamp:', TRIM(timestr)
250 CALL wrf_debug ( 1 , message )
252 IF ( config_flags%dyn_opt .EQ. dyn_em_ad .AND. ialarm .EQ. auxinput7_only ) THEN
253 CALL domain_clock_get( grid, current_time=currTime, start_time=startTime, &
254 current_timestr=timestr )
255 WRITE(message, FMT='(A,A)') 'read ad. forcing from file at time stamp:', TRIM(timestr)
256 CALL wrf_debug ( 1 , message )
258 IF ( ( config_flags%dyn_opt .EQ. dyn_em_ad .OR. config_flags%dyn_opt .EQ. dyn_em_tl ) &
259 .AND. ialarm .EQ. auxinput6_only ) THEN
260 CALL get_ijk_from_grid ( grid , &
261 ids, ide, jds, jde, kds, kde, &
262 ims, ime, jms, jme, kms, kme, &
263 ips, ipe, jps, jpe, kps, kpe )
267 scalar => grid%scalar
269 tracer => grid%tracer
270 # include "HALO_EM_INIT_1.inc"
271 # include "HALO_EM_INIT_2.inc"
272 # include "HALO_EM_INIT_5.inc"
274 DO ij = 1 , grid%num_tiles
275 CALL rk_phys_bc_dry_2( config_flags, &
276 grid%u_2, grid%v_2, grid%w_2, &
277 grid%t_2, grid%ph_2, grid%mu_2, &
278 ids, ide, jds, jde, kds, kde, &
279 ims, ime, jms, jme, kms, kme, &
280 ips, ipe, jps, jpe, kps, kpe, &
281 grid%i_start(ij), grid%i_end(ij), &
282 grid%j_start(ij), grid%j_end(ij), &
284 DO im = PARAM_FIRST_SCALAR , num_moist
285 CALL set_physical_bc3d( grid%moist(:,:,:,im), 'p', config_flags, &
286 ids, ide, jds, jde, kds, kde, &
287 ims, ime, jms, jme, kms, kme, &
288 ips, ipe, jps, jpe, kps, kpe, &
289 grid%i_start(ij), grid%i_end(ij), &
290 grid%j_start(ij), grid%j_end(ij), &
293 CALL set_physical_bc3d( grid%tke_2 , 'p', config_flags, &
294 ids, ide, jds, jde, kds, kde, &
295 ims, ime, jms, jme, kms, kme, &
296 ips, ipe, jps, jpe, kps, kpe, &
297 grid%i_start(ij), grid%i_end(ij), &
298 grid%j_start(ij), grid%j_end(ij), &
304 IF ( ialarm .EQ. auxinput6_only ) THEN ! Read Trajectory only
305 IF ( config_flags%dyn_opt .EQ. dyn_em_ad ) THEN
306 grid%domain_clock%clockint%CurrTime = ESMF_TimeInc (grid%domain_clock%clockint%CurrTime, &
307 grid%domain_clock%clockint%TimeStep )
309 CALL domain_clock_get ( grid, current_timestr=message )
310 IF ( config_flags%dyn_opt .EQ. dyn_em_ad ) THEN
311 CALL read_xtraj ( message )
312 ELSEIF ( config_flags%dyn_opt .EQ. dyn_em_tl ) THEN
313 CALL read_xtraj_reverse ( message )
316 IF ( ialarm .EQ. auxinput7_only ) THEN ! Read Adjoint Forcing only
317 CALL domain_clock_get ( grid, current_timestr=message )
318 IF ( config_flags%dyn_opt .EQ. dyn_em_ad ) THEN
319 CALL read_ad_forcing ( message )
323 IF ( .NOT. grid%trajectory_io ) THEN
324 WRITE ( message , FMT='(A,i3,A,i3)' ) 'Input data processed from aux input ' , &
325 ialarm - first_auxinput + 1, ' for domain ',grid%id
326 CALL wrf_debug ( 1 , message )
328 ! Reverse the current time
329 IF ( config_flags%dyn_opt .EQ. dyn_em_ad .AND. ialarm .EQ. auxinput6_only ) THEN
330 CALL domain_clock_set( grid, time_step_seconds=model_config_rec%time_step )
331 grid%domain_clock%clockint%CurrTime = ESMF_TimeInc (grid%domain_clock%clockint%CurrTime, &
332 grid%domain_clock%clockint%TimeStep )
333 CALL domain_clock_set( grid, time_step_seconds=-1*model_config_rec%time_step )
336 CALL med_auxinput_in ( grid, ialarm, config_flags )
337 WRITE ( message , FMT='(A,i3,A,i3)' ) 'Input data processed for aux input ' , &
338 ialarm - first_auxinput + 1, ' for domain ',grid%id
339 CALL wrf_debug ( 0 , message )
341 CALL WRFU_AlarmRingerOff( grid%alarms( ialarm ), rc=rc )
347 CALL WRFU_ClockGet( grid%domain_clock, CurrTime=currTime, StartTime=startTime )
348 IF ( ( WRFU_AlarmIsRinging( grid%alarms( RESTART_ALARM ), rc=rc ) ) .AND. &
349 ( currTime .NE. startTime ) ) THEN
350 IF ( grid%id .EQ. 1 ) THEN
351 ! Only the parent initiates the restart writing. Otherwise, different
352 ! domains may be written out at different times and with different
353 ! time stamps in the file names.
354 CALL med_restart_out ( grid , config_flags )
356 CALL WRFU_AlarmRingerOff( grid%alarms( RESTART_ALARM ), rc=rc )
358 CALL WRFU_AlarmRingerOff( grid%alarms( RESTART_ALARM ), rc=rc )
361 ! - Look for boundary data after writing out history and restart files
362 CALL med_latbound_in ( grid , config_flags )
366 END SUBROUTINE med_before_solve_io
369 SUBROUTINE med_last_ad_solve_io ( grid , config_flags )
371 USE module_state_description
372 USE module_domain , ONLY : domain, domain_clock_get
373 USE module_configure , ONLY : grid_config_rec_type
375 USE mediation_pertmod_io , ONLY : read_ad_forcing
383 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
388 TYPE(WRFU_Time) :: currTime, startTime
389 CHARACTER*256 :: message
390 CHARACTER*80 :: timestr
392 IF( WRFU_AlarmIsRinging( grid%alarms( AUXINPUT7_ALARM ), rc=rc ) ) THEN
393 IF ( .NOT. grid%trajectory_io ) THEN
394 CALL med_auxinput_in ( grid, AUXINPUT7_ALARM, config_flags )
396 CALL domain_clock_get ( grid, current_timestr=message )
397 CALL read_ad_forcing ( message )
399 IF ( .NOT. grid%trajectory_io ) THEN
400 CALL WRFU_ClockGet( grid%domain_clock, CurrTime=currTime, StartTime=startTime )
401 CALL domain_clock_get( grid, current_time=currTime, start_time=startTime, &
402 current_timestr=timestr )
403 WRITE(message, FMT='(A,A)') 'read ad. forcing from file at time stamp:', TRIM(timestr)
404 CALL wrf_debug ( 1 , message )
405 WRITE ( message , FMT='(A,i3,A,i3)' ) 'Input data processed from aux input ' , &
406 AUXINPUT7_ALARM - first_auxinput + 1, ' for domain ',grid%id
407 CALL wrf_debug ( 1 , message )
409 CALL WRFU_AlarmRingerOff( grid%alarms( AUXINPUT7_ALARM ), rc=rc )
413 END SUBROUTINE med_last_ad_solve_io
416 SUBROUTINE med_after_solve_io ( grid , config_flags )
418 USE module_domain , ONLY : domain
420 USE module_configure , ONLY : grid_config_rec_type
427 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
429 ! Compute time series variables
432 ! Compute track variables
433 CALL track_driver(grid)
436 END SUBROUTINE med_after_solve_io
438 SUBROUTINE med_pre_nest_initial ( parent , newid , config_flags )
441 USE module_domain , ONLY : domain, domain_clock_get
443 USE module_domain , ONLY : domain
446 USE module_utility , ONLY : WRFU_Time
448 USE module_utility , ONLY : WRFU_Time, WRFU_TimeEQ
452 USE module_configure , ONLY : grid_config_rec_type
458 TYPE(domain) , POINTER :: parent
459 INTEGER, INTENT(IN) :: newid
460 TYPE (grid_config_rec_type) , INTENT(INOUT) :: config_flags
461 TYPE (grid_config_rec_type) :: nest_config_flags
464 INTEGER :: itmp, fid, ierr, icnt
465 CHARACTER*256 :: rstname, message, timestr
467 TYPE(WRFU_Time) :: strt_time, cur_time
471 CALL domain_clock_get( parent, current_timestr=timestr, start_time=strt_time, current_time=cur_time )
472 CALL construct_filename2a ( rstname , config_flags%rst_inname , newid , 2 , timestr )
475 IF ( config_flags%restart .AND. (cur_time .EQ. strt_time) ) THEN
477 IF ( config_flags%restart .AND. WRFU_TimeEQ(cur_time,strt_time) ) THEN
479 WRITE(message,*)'RESTART: nest, opening ',TRIM(rstname),' for reading header information only'
480 CALL wrf_message ( message )
481 ! note that the parent pointer is not strictly correct, but nest is not allocated yet and
482 ! only the i/o communicator fields are used from "parent" (and those are dummies in current
484 CALL open_r_dataset ( fid , TRIM(rstname) , parent , config_flags , "DATASET=RESTART", ierr )
485 IF ( ierr .NE. 0 ) THEN
486 WRITE( message , '("program wrf: error opening ",A32," for reading")') TRIM(rstname)
487 CALL WRF_ERROR_FATAL ( message )
490 ! update the values of parent_start that were read in from the namelist (nest may have moved)
491 CALL wrf_get_dom_ti_integer ( fid , 'I_PARENT_START' , itmp , 1 , icnt, ierr )
492 IF ( ierr .EQ. 0 ) THEN
493 config_flags%i_parent_start = itmp
494 CALL nl_set_i_parent_start ( newid , config_flags%i_parent_start )
496 CALL wrf_get_dom_ti_integer ( fid , 'J_PARENT_START' , itmp , 1 , icnt, ierr )
497 IF ( ierr .EQ. 0 ) THEN
498 config_flags%j_parent_start = itmp
499 CALL nl_set_j_parent_start ( newid , config_flags%j_parent_start )
502 CALL close_dataset ( fid , config_flags , "DATASET=RESTART" )
506 END SUBROUTINE med_pre_nest_initial
509 SUBROUTINE med_nest_initial ( parent , nest , config_flags )
511 USE module_domain , ONLY : domain , domain_clock_get , get_ijk_from_grid
514 USE module_configure , ONLY : grid_config_rec_type
517 USE module_dm, ONLY : local_communicator, &
518 mpi_comm_to_mom, mpi_comm_to_kid, which_kid
525 TYPE(domain) , POINTER :: parent, nest
526 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
527 TYPE (grid_config_rec_type) :: nest_config_flags
530 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
531 TYPE(WRFU_Time) :: strt_time, cur_time
532 CHARACTER * 256 :: rstname , timestr
533 CHARACTER * 256 :: message
537 INTEGER :: ids , ide , jds , jde , kds , kde , &
538 ims , ime , jms , jme , kms , kme , &
539 ips , ipe , jps , jpe , kps , kpe
543 TYPE (WRFU_TimeInterval) :: interval, TimeSinceStart
544 INTEGER :: vortex_interval , n
546 INTEGER :: save_itimestep ! This is a kludge, correct fix will
547 ! involve integrating the time-step
548 ! counting into the time manager.
550 REAL, ALLOCATABLE, DIMENSION(:,:) :: save_acsnow &
561 SUBROUTINE med_interp_domain ( parent , nest )
562 USE module_domain , ONLY : domain
563 TYPE(domain) , POINTER :: parent , nest
564 END SUBROUTINE med_interp_domain
567 SUBROUTINE init_domain_vert_nesting ( parent, nest, use_baseparam_fr_nml )
568 !KAL this is a driver to initialize the vertical coordinates for the nest when vertical nesting is used.
569 USE module_domain, ONLY : domain
571 TYPE(domain), POINTER :: parent, nest
572 LOGICAL :: use_baseparam_fr_nml
573 END SUBROUTINE init_domain_vert_nesting
575 SUBROUTINE med_interp_domain_small ( parent , nest )
576 USE module_domain , ONLY : domain
577 TYPE(domain) , POINTER :: parent , nest
578 END SUBROUTINE med_interp_domain_small
580 SUBROUTINE med_initialdata_input_ptr( nest , config_flags )
581 USE module_domain , ONLY : domain
582 USE module_configure , ONLY : grid_config_rec_type
583 TYPE (grid_config_rec_type), INTENT(IN) :: config_flags
584 TYPE(domain) , POINTER :: nest
585 END SUBROUTINE med_initialdata_input_ptr
587 SUBROUTINE med_nest_feedback ( parent , nest , config_flags )
588 USE module_domain , ONLY : domain
589 USE module_configure , ONLY : grid_config_rec_type
590 TYPE (domain), POINTER :: nest , parent
591 TYPE (grid_config_rec_type), INTENT(IN) :: config_flags
592 END SUBROUTINE med_nest_feedback
594 SUBROUTINE start_domain ( grid , allowed_to_move )
595 USE module_domain , ONLY : domain
597 LOGICAL, INTENT(IN) :: allowed_to_move
598 END SUBROUTINE start_domain
600 SUBROUTINE blend_terrain ( ter_interpolated , ter_input , &
601 ids , ide , jds , jde , kds , kde , &
602 ims , ime , jms , jme , kms , kme , &
603 ips , ipe , jps , jpe , kps , kpe )
604 INTEGER :: ids , ide , jds , jde , kds , kde , &
605 ims , ime , jms , jme , kms , kme , &
606 ips , ipe , jps , jpe , kps , kpe
607 REAL , DIMENSION(ims:ime,jms:jme) :: ter_interpolated
608 REAL , DIMENSION(ims:ime,jms:jme) :: ter_input
609 END SUBROUTINE blend_terrain
611 SUBROUTINE copy_3d_field ( ter_interpolated , ter_input , &
612 ids , ide , jds , jde , kds , kde , &
613 ims , ime , jms , jme , kms , kme , &
614 ips , ipe , jps , jpe , kps , kpe )
615 INTEGER :: ids , ide , jds , jde , kds , kde , &
616 ims , ime , jms , jme , kms , kme , &
617 ips , ipe , jps , jpe , kps , kpe
618 REAL , DIMENSION(ims:ime,jms:jme) :: ter_interpolated
619 REAL , DIMENSION(ims:ime,jms:jme) :: ter_input
620 END SUBROUTINE copy_3d_field
622 SUBROUTINE input_terrain_rsmas ( grid , &
623 ids , ide , jds , jde , kds , kde , &
624 ims , ime , jms , jme , kms , kme , &
625 ips , ipe , jps , jpe , kps , kpe )
626 USE module_domain , ONLY : domain
627 TYPE ( domain ) :: grid
628 INTEGER :: ids , ide , jds , jde , kds , kde , &
629 ims , ime , jms , jme , kms , kme , &
630 ips , ipe , jps , jpe , kps , kpe
631 END SUBROUTINE input_terrain_rsmas
633 SUBROUTINE wrf_tsin ( grid , ierr )
635 TYPE ( domain ), INTENT(INOUT) :: grid
636 INTEGER, INTENT(INOUT) :: ierr
637 END SUBROUTINE wrf_tsin
643 CALL domain_clock_get( parent, start_time=strt_time, current_time=cur_time )
645 IF ( .not. ( config_flags%restart .AND. strt_time .EQ. cur_time ) ) THEN
646 nest%first_force = .true.
648 IF ( nest%active_this_task ) THEN
649 ! initialize nest with interpolated data from the parent
650 nest%imask_nostag = 1
653 nest%imask_xystag = 1
657 parent%nest_pos = parent%ht
658 where ( parent%nest_pos .gt. 0. ) parent%nest_pos = parent%nest_pos + 500. ! make a cliff
661 ! initialize some other constants (and 1d arrays in z)
662 CALL init_domain_constants ( parent, nest )
664 if (nest%e_vert /= parent%e_vert) then
665 ! set up coordinate variables for nest with vertical grid refinement (1d variables in z are done later in med_interp_domain)
666 CALL init_domain_vert_nesting ( parent, nest, config_flags%use_baseparam_fr_nml )
670 ! fill in entire fine grid domain with interpolated coarse grid data
671 CALL med_interp_domain( parent, nest )
673 ! De-reference dimension information stored in the grid data structure.
674 CALL get_ijk_from_grid ( nest , &
675 ids, ide, jds, jde, kds, kde, &
676 ims, ime, jms, jme, kms, kme, &
677 ips, ipe, jps, jpe, kps, kpe )
679 ! get the nest config flags
680 CALL model_to_grid_config_rec ( nest%id , model_config_rec , nest_config_flags )
682 IF ( nest_config_flags%input_from_file .OR. nest_config_flags%input_from_hires ) THEN
684 WRITE(message,FMT='(A,I2,A)') '*** Initializing nest domain #',nest%id,&
685 ' from an input file. ***'
686 CALL wrf_debug ( 0 , message )
688 ! Store horizontally interpolated terrain-based fields in temp location if the input
689 ! data is from a pristine, un-cycled model input file. For the original topo from
690 ! the real program, we will need to adjust the terrain (and a couple of other base-
691 ! state fields) so reflect the smoothing and matching between the parent and child
694 CALL copy_3d_field ( nest%ht_int , nest%ht , &
695 ids , ide , jds , jde , 1 , 1 , &
696 ims , ime , jms , jme , 1 , 1 , &
697 ips , ipe , jps , jpe , 1 , 1 )
698 CALL copy_3d_field ( nest%mub_fine , nest%mub , &
699 ids , ide , jds , jde , 1 , 1 , &
700 ims , ime , jms , jme , 1 , 1 , &
701 ips , ipe , jps , jpe , 1 , 1 )
702 CALL copy_3d_field ( nest%phb_fine , nest%phb , &
703 ids , ide , jds , jde , kds , kde , &
704 ims , ime , jms , jme , kms , kme , &
705 ips , ipe , jps , jpe , kps , kpe )
707 IF ( nest_config_flags%input_from_file ) THEN
708 ! read input from dataset
709 CALL med_initialdata_input_ptr( nest , nest_config_flags )
711 ELSE IF ( nest_config_flags%input_from_hires ) THEN
712 ! read in high res topography
713 CALL input_terrain_rsmas ( nest, &
714 ids , ide , jds , jde , 1 , 1 , &
715 ims , ime , jms , jme , 1 , 1 , &
716 ips , ipe , jps , jpe , 1 , 1 )
719 ! save elevation and mub for temp and qv adjustment
721 CALL copy_3d_field ( nest%ht_fine , nest%ht , &
722 ids , ide , jds , jde , 1 , 1 , &
723 ims , ime , jms , jme , 1 , 1 , &
724 ips , ipe , jps , jpe , 1 , 1 )
725 CALL copy_3d_field ( nest%mub_save , nest%mub , &
726 ids , ide , jds , jde , 1 , 1 , &
727 ims , ime , jms , jme , 1 , 1 , &
728 ips , ipe , jps , jpe , 1 , 1 )
730 ! blend parent and nest fields: terrain, mub, and phb. The ht, mub and phb are used in start_domain.
732 IF ( nest%save_topo_from_real == 1 ) THEN
733 CALL blend_terrain ( nest%ht_int , nest%ht , &
734 ids , ide , jds , jde , 1 , 1 , &
735 ims , ime , jms , jme , 1 , 1 , &
736 ips , ipe , jps , jpe , 1 , 1 )
737 CALL blend_terrain ( nest%mub_fine , nest%mub , &
738 ids , ide , jds , jde , 1 , 1 , &
739 ims , ime , jms , jme , 1 , 1 , &
740 ips , ipe , jps , jpe , 1 , 1 )
741 CALL blend_terrain ( nest%phb_fine , nest%phb , &
742 ids , ide , jds , jde , kds , kde , &
743 ims , ime , jms , jme , kms , kme , &
744 ips , ipe , jps , jpe , kps , kpe )
749 CALL adjust_tempqv ( nest%mub , nest%mub_save , &
750 nest%c3h , nest%c4h , nest%znw , nest%p_top , &
751 nest%t_2 , nest%p , nest%moist(ims,kms,jms,P_QV) , &
752 nest_config_flags%use_theta_m, &
753 ids , ide , jds , jde , kds , kde , &
754 ims , ime , jms , jme , kms , kme , &
755 ips , ipe , jps , jpe , kps , kpe )
758 WRITE(message,FMT='(A,I2,A,I2,A)') '*** Initializing nest domain #',nest%id,&
759 ' by horizontally interpolating parent domain #' ,parent%id, &
761 CALL wrf_debug ( 0 , message )
764 ! For nests without an input file, we still need to read time series locations
765 ! from the tslist file
766 IF ( nest%active_this_task) THEN
767 CALL push_communicators_for_domain( nest%id )
768 CALL wrf_tsin( nest , ierr )
769 CALL pop_communicators_for_domain
774 ! feedback, mostly for this new terrain, but it is the safe thing to do
775 parent%ht_coarse = parent%ht
777 CALL med_nest_feedback ( parent , nest , config_flags )
779 ! This is the new interpolation for specific 3d arrays that are sensitive to the
780 ! topography diffs betwixt the CG and the FG.
781 IF ( config_flags%nest_interp_coord .EQ. 1 ) THEN
782 call wrf_debug(1,'mediation_integrate.F, calling med_interp_domain_small')
783 CALL med_interp_domain_small( parent, nest )
784 call wrf_debug(1,'mediation_integrate.F, back from med_interp_domain_small')
787 ! set some other initial fields, fill out halos, base fields; re-do parent due
788 ! to new terrain elevation from feedback
790 IF ( nest%active_this_task) THEN
791 nest%imask_nostag = 1
794 nest%imask_xystag = 1
795 nest%press_adj = .TRUE.
796 CALL push_communicators_for_domain( nest%id )
797 CALL start_domain ( nest , .TRUE. )
798 CALL pop_communicators_for_domain
801 #if defined(DM_PARALLEL) && ! defined(STUBMPI)
802 CALL push_communicators_for_domain( parent%id )
803 CALL MPI_Barrier( local_communicator, ierr )
804 CALL pop_communicators_for_domain
807 IF ( parent%active_this_task ) THEN
808 CALL push_communicators_for_domain( parent%id )
810 CALL get_ijk_from_grid ( parent , &
811 ids, ide, jds, jde, kds, kde, &
812 ims, ime, jms, jme, kms, kme, &
813 ips, ipe, jps, jpe, kps, kpe )
815 ALLOCATE( save_acsnow(ims:ime,jms:jme) )
816 ALLOCATE( save_acsnom(ims:ime,jms:jme) )
817 ALLOCATE( save_cuppt(ims:ime,jms:jme) )
818 ALLOCATE( save_rainc(ims:ime,jms:jme) )
819 ALLOCATE( save_rainnc(ims:ime,jms:jme) )
820 ALLOCATE( save_sfcevp(ims:ime,jms:jme) )
821 ALLOCATE( save_sfcrunoff(ims:ime,jms:jme) )
822 ALLOCATE( save_udrunoff(ims:ime,jms:jme) )
823 save_acsnow = parent%acsnow
824 save_acsnom = parent%acsnom
825 save_cuppt = parent%cuppt
826 save_rainc = parent%rainc
827 save_rainnc = parent%rainnc
828 save_sfcevp = parent%sfcevp
829 save_sfcrunoff = parent%sfcrunoff
830 save_udrunoff = parent%udrunoff
831 save_itimestep = parent%itimestep
832 parent%imask_nostag = 1
833 parent%imask_xstag = 1
834 parent%imask_ystag = 1
835 parent%imask_xystag = 1
837 parent%press_adj = .FALSE.
838 CALL start_domain ( parent , .TRUE. )
840 parent%acsnow = save_acsnow
841 parent%acsnom = save_acsnom
842 parent%cuppt = save_cuppt
843 parent%rainc = save_rainc
844 parent%rainnc = save_rainnc
845 parent%sfcevp = save_sfcevp
846 parent%sfcrunoff = save_sfcrunoff
847 parent%udrunoff = save_udrunoff
848 parent%itimestep = save_itimestep
849 DEALLOCATE( save_acsnow )
850 DEALLOCATE( save_acsnom )
851 DEALLOCATE( save_cuppt )
852 DEALLOCATE( save_rainc )
853 DEALLOCATE( save_rainnc )
854 DEALLOCATE( save_sfcevp )
855 DEALLOCATE( save_sfcrunoff )
856 DEALLOCATE( save_udrunoff )
857 ! end of kludge: 20040604
858 CALL pop_communicators_for_domain
863 !TODO -- have to look at restarts yet
865 IF ( wrf_dm_on_monitor() ) CALL start_timing
867 CALL domain_clock_get( nest, current_timestr=timestr )
868 CALL construct_filename2a ( rstname , config_flags%rst_inname , nest%id , 2 , timestr )
870 WRITE(message,*)'RESTART: nest, opening ',TRIM(rstname),' for reading'
871 CALL wrf_message ( message )
872 CALL model_to_grid_config_rec ( nest%id , model_config_rec , nest_config_flags )
873 CALL open_r_dataset ( fid , TRIM(rstname) , nest , nest_config_flags , "DATASET=RESTART", ierr )
874 IF ( ierr .NE. 0 ) THEN
875 WRITE( message , '("program wrf: error opening ",A32," for reading")') TRIM(rstname)
876 CALL WRF_ERROR_FATAL ( message )
878 CALL input_restart ( fid, nest , nest_config_flags , ierr )
879 CALL close_dataset ( fid , nest_config_flags , "DATASET=RESTART" )
881 IF ( wrf_dm_on_monitor() ) THEN
882 WRITE ( message , FMT = '("processing restart file for domain ",I8)' ) nest%id
883 CALL end_timing ( TRIM(message) )
886 nest%imask_nostag = 1
889 nest%imask_xystag = 1
890 nest%press_adj = .FALSE.
891 CALL start_domain ( nest , .TRUE. )
893 ! this doesn't need to be done for moving nests, since ht_coarse is part of the restart
894 parent%ht_coarse = parent%ht
897 ! In case of a restart, assume that the movement has already occurred in the previous
898 ! run and turn off the alarm for the starting time. We must impose a requirement that the
899 ! run be restarted on-interval. Test for that and print a warning if it isn't.
900 ! Note, simulation_start, etc. should be available as metadata in the restart file, and
901 ! these will have gotten, set, and retrievable as rconfig data been set in share/input_wrf.F
902 ! using the nl_get routines below. JM 20060314
904 CALL nl_get_vortex_interval ( nest%id , vortex_interval )
905 CALL WRFU_TimeIntervalSet( interval, M=vortex_interval, rc=rc )
907 CALL domain_clock_get( nest, timeSinceSimulationStart=TimeSinceStart )
908 n = WRFU_TimeIntervalDIVQuot( TimeSinceStart , interval )
909 IF ( ( interval * n ) .NE. TimeSinceStart ) THEN
910 CALL wrf_message('WARNING: Restart is not on a vortex_interval time boundary.')
911 CALL wrf_message('The code will work but results will not agree exactly with a ')
912 CALL wrf_message('a run that was done straight-through, without a restart.')
914 !! In case of a restart, assume that the movement has already occurred in the previous
915 !! run and turn off the alarm for the starting time. We must impose a requirement that the
916 !! run be restarted on-interval. Test for that and print a warning if it isn't.
917 !! Note, simulation_start, etc. should be available as metadata in the restart file, and
918 !! these will have gotten, set, and retrievable as rconfig data been set in share/input_wrf.F
919 !! using the nl_get routines below. JM 20060314
920 ! CALL WRFU_AlarmRingerOff( nest%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
923 ! this code, currently commented out, is an attempt to have the
924 ! vortex centering interval be set according to simulation start
925 ! time (rather than run start time) in case of a restart. But
926 ! there are other problems (the WRF clock is currently using
927 ! run-start as it's start time) so the alarm still would not fire
928 ! right if the model were started off-interval. Leave it here and
929 ! enable when the clock is changed to use sim-start for start time.
931 CALL nl_get_vortex_interval ( nest%id , vortex_interval )
932 CALL WRFU_TimeIntervalSet( interval, M=vortex_interval, rc=rc )
934 CALL domain_clock_get( nest, timeSinceSimulationStart=TimeSinceStart )
936 CALL domain_alarm_create( nest, COMPUTE_VORTEX_CENTER_ALARM, interval )
937 CALL WRFU_AlarmEnable( nest%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
938 n = WRFU_TimeIntervalDIVQuot( TimeSinceStart , interval )
939 IF ( ( interval * n ) .EQ. TimeSinceStart ) THEN
940 CALL WRFU_AlarmRingerOn( nest%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
942 CALL WRFU_AlarmRingerOff( nest%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
952 END SUBROUTINE med_nest_initial
954 SUBROUTINE init_domain_constants ( parent , nest )
955 USE module_domain , ONLY : domain
957 TYPE(domain) :: parent , nest
959 CALL init_domain_constants_em ( parent, nest )
961 END SUBROUTINE init_domain_constants
964 SUBROUTINE med_nest_force ( parent , nest )
966 USE module_domain , ONLY : domain
968 USE module_configure , ONLY : grid_config_rec_type
976 TYPE(domain) , POINTER :: parent, nest
978 INTEGER :: idum1 , idum2 , fid, rc
981 SUBROUTINE med_force_domain ( parent , nest )
982 USE module_domain , ONLY : domain
983 TYPE(domain) , POINTER :: parent , nest
984 END SUBROUTINE med_force_domain
985 SUBROUTINE med_interp_domain ( parent , nest )
986 USE module_domain , ONLY : domain
987 TYPE(domain) , POINTER :: parent , nest
988 END SUBROUTINE med_interp_domain
991 IF ( .NOT. WRFU_ClockIsStopTime(nest%domain_clock ,rc=rc) ) THEN
992 ! initialize nest with interpolated data from the parent
993 IF ( nest%active_this_task ) THEN
994 nest%imask_nostag = 1
997 nest%imask_xystag = 1
999 CALL med_force_domain( parent, nest )
1002 ! might also have calls here to do input from a file into the nest
1005 END SUBROUTINE med_nest_force
1007 SUBROUTINE med_nest_feedback ( parent , nest , config_flags )
1009 USE module_domain , ONLY : domain , get_ijk_from_grid
1011 USE module_configure , ONLY : grid_config_rec_type
1019 TYPE(domain) , POINTER :: parent, nest
1020 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1022 INTEGER :: idum1 , idum2 , fid, rc
1023 INTEGER :: ids , ide , jds , jde , kds , kde , &
1024 ims , ime , jms , jme , kms , kme , &
1025 ips , ipe , jps , jpe , kps , kpe
1029 SUBROUTINE med_feedback_domain ( parent , nest )
1030 USE module_domain , ONLY : domain
1031 TYPE(domain) , POINTER :: parent , nest
1032 END SUBROUTINE med_feedback_domain
1035 ! feedback nest to the parent
1036 IF ( config_flags%feedback .NE. 0 ) THEN
1037 CALL med_feedback_domain( parent, nest )
1039 IF ( parent%active_this_task) THEN
1040 CALL get_ijk_from_grid ( parent , &
1041 ids, ide, jds, jde, kds, kde, &
1042 ims, ime, jms, jme, kms, kme, &
1043 ips, ipe, jps, jpe, kps, kpe )
1044 ! gopal's change- added ifdef
1045 #if ( EM_CORE == 1 )
1046 DO j = jps, MIN(jpe,jde-1)
1047 DO i = ips, MIN(ipe,ide-1)
1048 IF ( parent%nest_pos(i,j) .EQ. 9021000. ) THEN
1049 parent%nest_pos(i,j) = parent%ht(i,j)*1.5 + 1000.
1050 ELSE IF ( parent%ht(i,j) .NE. 0. ) THEN
1051 parent%nest_pos(i,j) = parent%ht(i,j) + 500.
1053 parent%nest_pos(i,j) = 0.
1063 END SUBROUTINE med_nest_feedback
1065 SUBROUTINE med_last_solve_io ( grid , config_flags )
1067 USE module_state_description
1068 USE module_domain , ONLY : domain, domain_clock_get
1069 USE module_configure , ONLY : grid_config_rec_type
1072 #if ( WRFPLUS == 1 )
1073 USE mediation_pertmod_io , ONLY : save_xtraj, save_tl_pert
1080 TYPE(domain) :: grid
1081 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1084 CHARACTER*256 :: message
1086 ! #if (EM_CORE == 1)
1087 IF( WRFU_AlarmIsRinging( grid%alarms( HISTORY_ALARM ), rc=rc ) .AND. &
1088 (grid%dfi_write_dfi_history .OR. grid%dfi_stage == DFI_FST .OR. grid%dfi_opt == DFI_NODFI) ) THEN
1090 ! IF( WRFU_AlarmIsRinging( grid%alarms( HISTORY_ALARM ), rc=rc )) THEN
1092 CALL med_hist_out ( grid , HISTORY_ALARM , config_flags )
1095 IF( WRFU_AlarmIsRinging( grid%alarms( INPUTOUT_ALARM ), rc=rc ) ) THEN
1096 CALL med_filter_out ( grid , config_flags )
1099 ! registry-generated file of the following
1100 ! IF( WRFU_AlarmIsRinging( grid%alarms( AUXHIST1_ALARM ), rc=rc ) ) THEN
1101 ! CALL med_hist_out ( grid , AUXHIST1_ALARM , config_flags )
1103 IF ( grid%dfi_stage == DFI_FST .OR. grid%dfi_opt == DFI_NODFI ) THEN
1104 #include "med_last_solve_io.inc"
1108 IF( WRFU_AlarmIsRinging( grid%alarms( RESTART_ALARM ), rc=rc ) ) THEN
1109 IF ( grid%id .EQ. 1 ) THEN
1110 CALL med_restart_out ( grid , config_flags )
1114 ! Write out time series
1115 CALL write_ts( grid )
1118 END SUBROUTINE med_last_solve_io
1122 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1124 RECURSIVE SUBROUTINE med_restart_out ( grid , config_flags )
1126 USE module_domain , ONLY : domain , domain_clock_get
1127 USE module_io_domain
1129 USE module_configure , ONLY : grid_config_rec_type
1131 ! USE module_bc_time_utilities
1137 TYPE(domain) :: grid
1138 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1141 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
1142 CHARACTER*256 :: rstname , outname
1143 INTEGER :: fid , rid, kid
1144 CHARACTER (LEN=256) :: message
1147 CHARACTER*80 :: timestr
1148 TYPE (grid_config_rec_type) :: kid_config_flags
1150 IF ( wrf_dm_on_monitor() ) THEN
1154 ! take this out - no effect - LPC
1155 ! rid=grid%id !zhang's doing
1157 ! write out this domains restart file first
1159 CALL domain_clock_get( grid, current_timestr=timestr )
1160 CALL construct_filename2a ( rstname , config_flags%rst_outname , grid%id , 2 , timestr )
1162 WRITE( message , '("med_restart_out: opening ",A," for writing")' ) TRIM ( rstname )
1163 CALL wrf_debug( 1 , message )
1164 CALL open_w_dataset ( rid, TRIM(rstname), grid , &
1165 config_flags , output_restart , "DATASET=RESTART", ierr )
1167 IF ( ierr .NE. 0 ) THEN
1168 CALL WRF_message( message )
1170 CALL output_restart ( rid, grid , config_flags , ierr )
1171 IF ( wrf_dm_on_monitor() ) THEN
1172 WRITE ( message , FMT = '("Writing restart for domain ",I8)' ) grid%id
1173 CALL end_timing ( TRIM(message) )
1175 CALL close_dataset ( rid , config_flags , "DATASET=RESTART" )
1177 ! call recursively for children, (if any)
1178 DO kid = 1, max_nests
1179 IF ( ASSOCIATED( grid%nests(kid)%ptr ) ) THEN
1180 CALL model_to_grid_config_rec ( grid%nests(kid)%ptr%id , model_config_rec , kid_config_flags )
1181 CALL med_restart_out ( grid%nests(kid)%ptr , kid_config_flags )
1186 END SUBROUTINE med_restart_out
1188 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1190 SUBROUTINE med_hist_out ( grid , stream, config_flags )
1192 USE module_domain , ONLY : domain
1194 USE module_io_domain
1195 USE module_configure , ONLY : grid_config_rec_type
1196 USE module_dm, ONLY : intercomm_active
1197 ! USE module_bc_time_utilities
1202 TYPE(domain) :: grid
1203 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1204 INTEGER , INTENT(IN) :: stream
1206 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
1207 CHARACTER*256 :: fname, n2
1208 CHARACTER (LEN=256) :: message
1211 IF ( .NOT. grid%active_this_task ) RETURN
1213 IF ( wrf_dm_on_monitor() ) THEN
1217 IF ( stream .LT. first_history .OR. stream .GT. last_auxhist ) THEN
1218 WRITE(message,*)'med_hist_out: invalid history stream ',stream
1219 CALL wrf_error_fatal( message )
1222 SELECT CASE( stream )
1223 CASE ( HISTORY_ALARM )
1224 CALL open_hist_w( grid, config_flags, stream, HISTORY_ALARM, &
1225 config_flags%history_outname, grid%oid, &
1226 output_history, fname, n2, ierr )
1227 CALL output_history ( grid%oid, grid , config_flags , ierr )
1229 ! registry-generated selections and calls top open_hist_w for aux streams
1230 #include "med_hist_out_opens.inc"
1234 WRITE(message,*)'med_hist_out: opened ',TRIM(fname),' as ',TRIM(n2)
1235 CALL wrf_debug( 1, message )
1237 grid%nframes(stream) = grid%nframes(stream) + 1
1239 SELECT CASE( stream )
1240 CASE ( HISTORY_ALARM )
1241 IF ( grid%nframes(stream) >= config_flags%frames_per_outfile ) THEN
1242 write(0,*)__FILE__,__LINE__,trim(n2)
1243 write(0,*)__FILE__,__LINE__,' grid%id ',grid%id,' grid%oid ',grid%oid
1244 CALL close_dataset ( grid%oid , config_flags , n2 )
1246 grid%nframes(stream) = 0
1248 ! registry-generated selections and calls top close_dataset for aux streams
1249 #include "med_hist_out_closes.inc"
1252 IF ( wrf_dm_on_monitor() ) THEN
1253 WRITE ( message , FMT = '("Writing ",A," for domain ",I8)' )TRIM(fname),grid%id
1254 CALL end_timing ( TRIM(message) )
1258 END SUBROUTINE med_hist_out
1261 SUBROUTINE med_fddaobs_in ( grid , config_flags )
1262 USE module_domain , ONLY : domain
1263 USE module_configure , ONLY : grid_config_rec_type
1265 TYPE(domain) :: grid
1266 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1267 CALL wrf_fddaobs_in( grid, config_flags )
1269 END SUBROUTINE med_fddaobs_in
1272 SUBROUTINE med_auxinput_in ( grid , stream, config_flags )
1274 USE module_domain , ONLY : domain
1275 USE module_io_domain
1277 USE module_configure , ONLY : grid_config_rec_type
1278 ! USE module_bc_time_utilities
1283 TYPE(domain) :: grid
1284 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1285 INTEGER , INTENT(IN) :: stream
1287 CHARACTER (LEN=256) :: message
1290 IF ( stream .LT. first_auxinput .OR. stream .GT. last_auxinput ) THEN
1291 WRITE(message,*)'med_auxinput_in: invalid input stream ',stream
1292 CALL wrf_error_fatal( message )
1295 grid%nframes(stream) = grid%nframes(stream) + 1
1297 SELECT CASE( stream )
1298 ! registry-generated file of calls to open filename
1299 ! CASE ( AUXINPUT1_ALARM )
1300 ! CALL open_aux_u( grid, config_flags, stream, AUXINPUT1_ALARM, &
1301 ! config_flags%auxinput1_inname, grid%auxinput1_oid, &
1302 ! input_auxinput1, ierr )
1303 ! CALL input_auxinput1 ( grid%auxinput1_oid, grid , config_flags , ierr )
1304 #include "med_auxinput_in.inc"
1307 SELECT CASE( stream )
1308 ! registry-generated selections and calls top close_dataset for aux streams
1309 #include "med_auxinput_in_closes.inc"
1313 END SUBROUTINE med_auxinput_in
1315 SUBROUTINE med_filter_out ( grid , config_flags )
1317 USE module_domain , ONLY : domain , domain_clock_get
1318 USE module_io_domain
1320 USE module_configure , ONLY : grid_config_rec_type
1322 USE module_bc_time_utilities
1327 TYPE(domain) :: grid
1328 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1330 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
1331 CHARACTER*256 :: rstname , outname
1332 INTEGER :: fid , rid
1333 CHARACTER (LEN=256) :: message
1336 CHARACTER*80 :: timestr
1338 IF ( config_flags%write_input ) THEN
1340 IF ( wrf_dm_on_monitor() ) THEN
1344 CALL domain_clock_get( grid, current_timestr=timestr )
1345 CALL construct_filename2a ( outname , config_flags%input_outname , grid%id , 2 , timestr )
1347 WRITE ( message , '("med_filter_out 1: opening ",A," for writing. ")') TRIM ( outname )
1348 CALL wrf_debug( 1, message )
1350 CALL open_w_dataset ( fid, TRIM(outname), grid , &
1351 config_flags , output_input , "DATASET=INPUT", ierr )
1352 IF ( ierr .NE. 0 ) THEN
1353 CALL wrf_error_fatal( message )
1356 IF ( ierr .NE. 0 ) THEN
1357 CALL wrf_error_fatal( message )
1360 CALL output_input ( fid, grid , config_flags , ierr )
1361 CALL close_dataset ( fid , config_flags , "DATASET=INPUT" )
1363 IF ( wrf_dm_on_monitor() ) THEN
1364 WRITE ( message , FMT = '("Writing filter output for domain ",I8)' ) grid%id
1365 CALL end_timing ( TRIM(message) )
1370 END SUBROUTINE med_filter_out
1372 SUBROUTINE med_latbound_in ( grid , config_flags )
1374 USE module_domain , ONLY : domain , domain_clock_get, head_grid
1375 USE module_io_domain
1377 USE module_configure , ONLY : grid_config_rec_type
1379 ! USE module_bc_time_utilities
1384 #include "wrf_status_codes.h"
1387 TYPE(domain) :: grid
1388 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1391 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
1392 LOGICAL :: lbc_opened
1393 INTEGER :: idum1 , idum2 , ierr , open_status , fid, rc
1395 CHARACTER (LEN=256) :: message
1396 CHARACTER (LEN=256) :: bdyname
1397 Type (WRFU_Time ) :: startTime, stopTime, currentTime
1398 Type (WRFU_TimeInterval ) :: stepTime
1399 integer myproc,i,j,k
1400 CHARACTER(LEN=80) :: timestr
1402 #include "wrf_io_flags.h"
1404 CALL wrf_debug ( 200 , 'in med_latbound_in' )
1406 ! #if (EM_CORE == 1)
1407 ! Avoid trying to re-read the boundary conditions if we are doing DFI integration
1408 ! and do not expect to find boundary conditions for the current time
1409 IF ( (grid%dfi_opt .EQ. DFI_DDFI .OR. grid%dfi_opt .EQ. DFI_TDFI) .AND. grid%dfi_stage .EQ. DFI_FWD ) RETURN
1412 IF ( grid%active_this_task .AND. grid%id .EQ. 1 .AND. config_flags%specified .AND. config_flags%io_form_boundary .GT. 0 ) THEN
1414 CALL domain_clock_get( grid, current_time=currentTime, &
1415 start_time=startTime, &
1416 stop_time=stopTime, &
1417 time_step=stepTime )
1420 !jm The test below never worked because set_time_time_read_again is never called to store a
1421 !jm time that lbc_read_time can compare with currentTime (see module_bc_time_utilities). This means
1422 !jm lbc_read_time will never return anything but false -- will also generate an ESMF error that the
1423 !jm stored time was never initialized. Removing that branch from the conditional.
1424 !jm IF ( ( lbc_read_time( currentTime ) ) .AND. &
1425 !jm ( currentTime + stepTime .GE. stopTime ) .AND. &
1426 !jm ( currentTime .NE. startTime ) ) THEN
1427 !jm CALL wrf_debug( 100 , 'med_latbound_in: Skipping attempt to read lateral boundary file during last time step ' )
1429 !jm ELSE IF ( WRFU_AlarmIsRinging( grid%alarms( BOUNDARY_ALARM ), rc=rc ) ) THEN
1431 IF ( WRFU_AlarmIsRinging( grid%alarms( BOUNDARY_ALARM ), rc=rc ) ) THEN
1432 CALL wrf_debug ( 100 , 'in med_latbound_in preparing to read' )
1433 CALL WRFU_AlarmRingerOff( grid%alarms( BOUNDARY_ALARM ), rc=rc )
1434 IF ( wrf_dm_on_monitor() ) CALL start_timing
1436 ! Possibility to have a <date> as part of the bdy_inname.
1437 IF ( config_flags%multi_bdy_files ) THEN
1438 CALL domain_clock_get( grid, current_timestr=timestr )
1439 CALL construct_filename2a ( bdyname , config_flags%bdy_inname , grid%id , 2 , timestr )
1441 ! typically a <date> wouldn't be part of the bdy_inname, so just pass a dummy
1443 CALL construct_filename2a ( bdyname , config_flags%bdy_inname , grid%id , 2 , " " )
1447 CALL wrf_inquire_opened(grid%lbc_fid , TRIM(bdyname) , open_status , ierr )
1448 IF ( open_status .EQ. WRF_FILE_OPENED_FOR_READ ) THEN
1451 lbc_opened = .FALSE.
1453 CALL wrf_dm_bcast_bytes ( lbc_opened , LWORDSIZE )
1454 IF ( .NOT. lbc_opened ) THEN
1455 IF ( config_flags%multi_bdy_files ) THEN
1456 CALL construct_filename2a ( bdyname , config_flags%bdy_inname , grid%id , 2 , timestr )
1458 CALL construct_filename2a ( bdyname , config_flags%bdy_inname , grid%id , 2 , " " )
1460 WRITE(message,*)'Opening: ',TRIM(bdyname)
1461 CALL wrf_debug(100,TRIM(message))
1462 CALL open_r_dataset ( grid%lbc_fid, TRIM(bdyname) , grid , config_flags , "DATASET=BOUNDARY", ierr )
1463 IF ( ierr .NE. 0 ) THEN
1464 WRITE( message, * ) 'med_latbound_in: error opening ',TRIM(bdyname), ' for reading. IERR = ',ierr
1465 CALL WRF_ERROR_FATAL( message )
1468 CALL wrf_debug( 100 , bdyname // ' is already opened' )
1470 CALL wrf_debug( 100 , 'med_latbound_in: calling input_boundary ' )
1471 CALL input_boundary ( grid%lbc_fid, grid , config_flags , ierr )
1473 ! #if (EM_CORE == 1)
1474 IF ( (config_flags%dfi_opt .NE. DFI_NODFI) .AND. (head_grid%dfi_stage .NE. DFI_FST) ) THEN
1475 CALL wrf_debug( 100 , 'med_latbound_in: closing boundary file ' )
1476 CALL close_dataset ( grid%lbc_fid , config_flags , "DATASET=BOUNDARY" )
1480 CALL domain_clock_get( grid, current_time=currentTime )
1481 #if ( WRFPLUS == 1 )
1482 IF ( config_flags%dyn_opt .NE. dyn_em_ad ) THEN
1483 DO WHILE (currentTime .GE. grid%next_bdy_time ) ! next_bdy_time is set by input_boundary from bdy file
1484 CALL wrf_debug( 100 , 'med_latbound_in: calling input_boundary ' )
1485 CALL input_boundary ( grid%lbc_fid, grid , config_flags , ierr )
1488 DO WHILE (currentTime .GT. grid%next_bdy_time ) ! next_bdy_time is set by input_boundary from bdy file
1489 CALL wrf_debug( 100 , 'med_latbound_in: calling input_boundary ' )
1490 CALL input_boundary ( grid%lbc_fid, grid , config_flags , ierr )
1494 DO WHILE (currentTime .GE. grid%next_bdy_time ) ! next_bdy_time is set by input_boundary from bdy file
1495 CALL wrf_debug( 100 , 'med_latbound_in: calling input_boundary ' )
1496 CALL input_boundary ( grid%lbc_fid, grid , config_flags , ierr )
1499 ! Close the bdy file so that next time around, we'll open it again.
1500 IF ( config_flags%multi_bdy_files ) THEN
1501 CALL close_dataset ( grid%lbc_fid , config_flags , "DATASET=BOUNDARY" )
1503 #if ( WRFPLUS == 1 )
1504 IF ( config_flags%dyn_opt .NE. dyn_em_ad ) THEN
1505 CALL WRFU_AlarmSet( grid%alarms( BOUNDARY_ALARM ), RingTime=grid%next_bdy_time, rc=rc )
1507 CALL WRFU_AlarmSet( grid%alarms( BOUNDARY_ALARM ), RingTime=grid%this_bdy_time, rc=rc )
1508 CALL wrf_inquire_opened(grid%lbc_fid , TRIM(bdyname) , open_status , ierr )
1509 IF ( open_status .EQ. WRF_FILE_OPENED_FOR_READ ) THEN
1510 CALL wrf_debug( 100 , 'med_latbound_in: closing boundary file ' )
1511 CALL close_dataset ( grid%lbc_fid , config_flags , "DATASET=BOUNDARY" )
1515 CALL WRFU_AlarmSet( grid%alarms( BOUNDARY_ALARM ), RingTime=grid%next_bdy_time, rc=rc )
1518 IF ( ierr .NE. 0 .and. ierr .NE. WRF_WARN_NETCDF ) THEN
1519 WRITE( message, * ) 'med_latbound_in: error reading ',TRIM(bdyname), ' IERR = ',ierr
1520 CALL WRF_ERROR_FATAL( message )
1522 IF ( currentTime .EQ. grid%this_bdy_time ) grid%dtbc = 0.
1524 IF ( wrf_dm_on_monitor() ) THEN
1525 WRITE ( message , FMT = '("processing lateral boundary for domain ",I8)' ) grid%id
1526 CALL end_timing ( TRIM(message) )
1531 END SUBROUTINE med_latbound_in
1533 SUBROUTINE med_setup_step ( grid , config_flags )
1535 USE module_domain , ONLY : domain
1536 USE module_configure , ONLY : grid_config_rec_type
1542 !The driver layer routine integrate() calls this mediation layer routine
1543 !prior to initiating a time step on the domain specified by the argument
1544 !grid. This provides the model-layer contributor an opportunity to make
1545 !any pre-time-step initializations that pertain to a particular model
1546 !domain. In WRF, this routine is used to call
1547 !set_scalar_indices_from_config for the specified domain.
1552 TYPE(domain) :: grid
1553 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1555 INTEGER :: idum1 , idum2
1557 CALL set_scalar_indices_from_config ( grid%id , idum1 , idum2 )
1561 END SUBROUTINE med_setup_step
1563 SUBROUTINE med_endup_step ( grid , config_flags )
1565 USE module_domain , ONLY : domain
1566 USE module_configure , ONLY : grid_config_rec_type, model_config_rec
1572 !The driver layer routine integrate() calls this mediation layer routine
1573 !prior to initiating a time step on the domain specified by the argument
1574 !grid. This provides the model-layer contributor an opportunity to make
1575 !any pre-time-step initializations that pertain to a particular model
1576 !domain. In WRF, this routine is used to call
1577 !set_scalar_indices_from_config for the specified domain.
1582 TYPE(domain) :: grid
1583 TYPE (grid_config_rec_type) , INTENT(OUT) :: config_flags
1585 INTEGER :: idum1 , idum2
1587 IF ( grid%id .EQ. 1 ) THEN
1588 ! turn off the restart flag after the first mother-domain step is finished
1589 model_config_rec%restart = .FALSE.
1590 config_flags%restart = .FALSE.
1591 CALL nl_set_restart(1, .FALSE.)
1597 END SUBROUTINE med_endup_step
1599 SUBROUTINE open_aux_u ( grid , config_flags, stream, alarm_id, &
1600 auxinput_inname, oid, insub, ierr )
1602 USE module_domain , ONLY : domain , domain_clock_get
1603 USE module_io_domain
1605 USE module_configure , ONLY : grid_config_rec_type
1606 ! USE module_bc_time_utilities
1611 TYPE(domain) :: grid
1612 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1613 INTEGER , INTENT(IN) :: stream
1614 INTEGER , INTENT(IN) :: alarm_id
1615 CHARACTER*(*) , INTENT(IN) :: auxinput_inname
1616 INTEGER , INTENT(INOUT) :: oid
1618 INTEGER , INTENT(OUT) :: ierr
1621 CHARACTER*256 :: fname, n2
1622 CHARACTER (LEN=256) :: message
1623 CHARACTER*80 :: timestr
1624 TYPE(WRFU_Time) :: ST,CT
1627 IF ( stream .LT. first_stream .OR. stream .GT. last_stream ) THEN
1628 WRITE(message,*)'open_aux_u: invalid input stream ',stream
1629 CALL wrf_error_fatal( message )
1634 IF ( oid .eq. 0 ) THEN
1635 CALL domain_clock_get( grid, current_time=CT, start_time=ST, &
1636 current_timestr=timestr )
1637 CALL nl_get_adjust_input_times( grid%id, adjust )
1639 CALL adjust_io_timestr( grid%io_intervals( alarm_id ), CT, ST, timestr )
1641 CALL construct_filename2a ( fname , auxinput_inname, &
1642 grid%id , 2 , timestr )
1643 stream_l = stream-auxinput1_only+1
1644 IF ( stream_l .GE. 10 ) THEN
1645 WRITE(n2,'("DATASET=AUXINPUT",I2)')stream_l
1647 WRITE(n2,'("DATASET=AUXINPUT",I1)')stream_l
1649 WRITE ( message , '("open_aux_u : opening ",A," for reading. DATASET ",A)') TRIM ( fname ),TRIM(n2)
1650 CALL wrf_debug( 1, message )
1653 !Open_u_dataset is called rather than open_r_dataset to allow interfaces
1654 !that can do blending or masking to update an existing field. (MCEL IO does this).
1655 !No effect for other interfaces; open_u_dataset is equivalent to open_r_dataset
1659 CALL open_u_dataset ( oid, TRIM(fname), grid , &
1660 config_flags , insub , n2, ierr )
1662 IF ( ierr .NE. 0 ) THEN
1663 WRITE ( message , '("open_aux_u : error opening ",A," for reading. ",I5)') &
1664 TRIM ( fname ), ierr
1665 CALL wrf_message( message )
1668 END SUBROUTINE open_aux_u
1670 SUBROUTINE open_hist_w ( grid , config_flags, stream, alarm_id, &
1671 hist_outname, oid, outsub, fname, n2, ierr )
1673 USE module_domain , ONLY : domain , domain_clock_get
1674 USE module_io_domain
1676 USE module_configure , ONLY : grid_config_rec_type
1677 ! USE module_bc_time_utilities
1681 TYPE(domain) :: grid
1682 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1683 INTEGER , INTENT(IN) :: stream
1684 INTEGER , INTENT(IN) :: alarm_id
1685 CHARACTER*(*) , INTENT(IN) :: hist_outname
1686 INTEGER , INTENT(INOUT) :: oid
1688 CHARACTER*(*) , INTENT(OUT) :: fname, n2
1689 INTEGER , INTENT(OUT) :: ierr
1693 CHARACTER (LEN=256) :: message
1694 CHARACTER*80 :: timestr
1695 TYPE(WRFU_Time) :: ST,CT
1698 IF ( stream .LT. first_history .OR. stream .GT. last_history ) THEN
1699 WRITE(message,*)'open_hist_w: invalid history stream ',stream
1700 CALL wrf_error_fatal( message )
1707 ! Note that computation of fname and n2 are outside of the oid IF statement
1708 ! since they are OUT args and may be used by callers even if oid/=0.
1709 CALL domain_clock_get( grid, current_time=CT, start_time=ST, &
1710 current_timestr=timestr )
1711 CALL nl_get_adjust_output_times( grid%id, adjust )
1713 CALL adjust_io_timestr( grid%io_intervals( alarm_id ), CT, ST, timestr )
1716 !----------------------------------------------------------------------
1717 ! RASM Climate Diagnostics - JR, AS, MS - October 2016
1718 !----------------------------------------------------------------------
1719 IF( alarm_id .EQ. AUXHIST5_ALARM .AND. config_flags%mean_diag .EQ. 1 ) THEN
1720 WRITE(message, *) "RASM STATS: MEAN AUXHIST5 oid=", oid, " fname=", trim(fname), " alarmI_id=", alarm_id, " Time_outNow=", timestr
1721 CALL wrf_debug(200, message )
1722 WRITE(message, *) "RASM STATS: MEAN AUXHIST5 Time_outbefore =...", trim(grid%OUTDATE_MEAN)
1723 CALL wrf_debug(200, message )
1724 timestr = grid%OUTDATE_MEAN
1725 ELSE IF( alarm_id .EQ. AUXHIST6_ALARM .AND. config_flags%diurnal_diag .EQ. 1 ) THEN
1726 WRITE(message, *) "RASM STATS: DIURNAL AUXHIST6 oid=", oid, " fname=", trim(fname), " alarmI_id=", alarm_id, " Time_outNow=", timestr
1727 CALL wrf_debug(200, message )
1728 WRITE(message, *) "RASM STATS: DIURNAL AUXHIST6 Time_outbefore =...", trim(grid%OUTDATE_DIURN)
1729 CALL wrf_debug(200, message )
1730 timestr = grid%OUTDATE_DIURN
1732 !----------------------------------------------------------------------
1733 ! end RASM Climate Diagnostics
1734 !----------------------------------------------------------------------
1736 CALL construct_filename2a ( fname , hist_outname, &
1737 grid%id , 2 , timestr )
1738 stream_l = stream-auxhist1_only+1
1739 IF ( stream .EQ. history_only ) THEN
1740 WRITE(n2,'("DATASET=HISTORY")')
1741 ELSE IF ( stream_l .GE. 10 ) THEN
1742 WRITE(n2,'("DATASET=AUXHIST",I2)')stream_l
1744 WRITE(n2,'("DATASET=AUXHIST",I1)')stream_l
1746 IF ( oid .eq. 0 ) THEN
1747 WRITE ( message , '("open_hist_w : opening ",A," for writing. ")') TRIM ( fname )
1748 CALL wrf_debug( 1, message )
1751 !Open_u_dataset is called rather than open_r_dataset to allow interfaces
1752 !that can do blending or masking to update an existing field. (MCEL IO does this).
1753 !No effect for other interfaces; open_u_dataset is equivalent to open_r_dataset
1757 CALL open_w_dataset ( oid, TRIM(fname), grid , &
1758 config_flags , outsub , n2, ierr )
1760 IF ( ierr .NE. 0 ) THEN
1761 WRITE ( message , '("open_hist_w : error opening ",A," for writing. ",I5)') &
1762 TRIM ( fname ), ierr
1763 CALL wrf_message( message )
1767 END SUBROUTINE open_hist_w
1770 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1772 #if ( WRF_CHEM == 1 )
1775 SUBROUTINE med_read_wrf_chem_input ( grid , config_flags )
1777 USE module_domain , ONLY : domain , domain_clock_get
1778 USE module_io_domain
1780 USE module_configure , ONLY : grid_config_rec_type
1782 USE module_bc_time_utilities
1786 USE module_date_time
1792 TYPE(domain) :: grid
1794 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1797 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
1799 INTEGER :: ierr, efid
1800 REAL :: time, tupdate
1801 real, allocatable :: dumc0(:,:,:)
1802 CHARACTER (LEN=256) :: message, current_date_char, date_string
1803 CHARACTER (LEN=256) :: inpname
1805 #include "wrf_io_flags.h"
1806 ! IF ( grid%id .EQ. 1 ) THEN
1808 CALL domain_clock_get( grid, current_timestr=current_date_char )
1810 CALL construct_filename1 ( inpname , config_flags%auxinput12_inname , grid%id , 2 )
1811 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_input: Open file ',TRIM(inpname)
1812 CALL wrf_message( TRIM(message) )
1814 if( grid%auxinput12_oid .NE. 0 ) then
1815 CALL close_dataset ( grid%auxinput12_oid , config_flags , "DATASET=AUXINPUT12" )
1818 CALL open_r_dataset ( grid%auxinput12_oid, TRIM(inpname) , grid , config_flags, &
1819 "DATASET=AUXINPUT12", ierr )
1820 IF ( ierr .NE. 0 ) THEN
1821 WRITE( message , * ) 'med_read_wrf_chem_input error opening ', TRIM( inpname )
1822 CALL wrf_error_fatal( TRIM( message ) )
1825 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_input: Read chemistry from wrfout at time ',&
1826 TRIM(current_date_char)
1827 CALL wrf_message( TRIM(message) )
1829 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput12' )
1830 CALL input_auxinput12 ( grid%auxinput12_oid, grid , config_flags , ierr )
1832 CALL close_dataset ( grid%auxinput12_oid , config_flags , "DATASET=AUXINPUT12" )
1835 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_chem_input: exit' )
1837 END SUBROUTINE med_read_wrf_chem_input
1838 !------------------------------------------------------------------------
1839 ! Chemistry emissions input control. Three options are available and are
1840 ! set via the namelist variable io_style_emissions:
1842 ! 0 = Emissions are not read in from a file. They will contain their
1843 ! default values, which can be set in the Registry.
1844 ! (Intended for debugging of chem code)
1846 ! 1 = Emissions are read in from two 12 hour files that are cycled.
1847 ! With this choice, auxinput5_inname should be set to
1848 ! the value "wrfchemi_hhZ_d<domain>".
1850 ! 2 = Emissions are read in from files identified by date and that have
1851 ! a length defined by frames_per_auxinput5. Both
1852 ! auxinput5_inname should be set to
1853 ! "wrfchemi_d<domain>_<date>".
1854 !------------------------------------------------------------------------
1855 SUBROUTINE med_read_wrf_chem_emiss ( grid , config_flags )
1857 USE module_domain , ONLY : domain , domain_clock_get
1858 USE module_io_domain
1860 USE module_configure , ONLY : grid_config_rec_type
1862 USE module_bc_time_utilities
1866 USE module_date_time
1872 TYPE(domain) :: grid
1874 ! TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
1875 TYPE (grid_config_rec_type) :: config_flags
1876 Type (WRFU_Time ) :: stopTime, currentTime
1877 Type (WRFU_TimeInterval ) :: stepTime
1880 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
1882 INTEGER :: ierr, efid
1883 INTEGER :: ihr, ihrdiff, i
1884 REAL :: time, tupdate
1885 real, allocatable :: dumc0(:,:,:)
1886 CHARACTER (LEN=256) :: message, current_date_char, date_string
1887 CHARACTER (LEN=256) :: inpname
1889 #include "wrf_io_flags.h"
1891 CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
1893 ! This "if" should be commented out when using emission files for nested
1894 ! domains. Also comment out the "ENDIF" line noted below.
1895 ! IF ( grid%id .EQ. 1 ) THEN
1897 CALL domain_clock_get( grid, current_time=currentTime, &
1898 current_timestr=current_date_char, &
1899 stop_time=stopTime, &
1900 time_step=stepTime )
1902 time = float(grid%itimestep) * grid%dt
1905 ! io_style_emissions option 0: no emissions read in...
1907 if( config_flags%io_style_emissions == 0 ) then
1910 ! io_style_emissions option 1: cycle through two 12 hour input files...
1912 else if( config_flags%io_style_emissions == 1 ) then
1914 tupdate = mod( time, (12. * 3600.) )
1915 read(current_date_char(12:13),'(I2)') ihr
1919 IF( tupdate .LT. grid%dt ) THEN
1922 IF( ihr .EQ. 00 .OR. ihr .EQ. 12 ) THEN
1926 IF( currentTime + stepTime .GE. stopTime .AND. &
1927 grid%auxinput5_oid .NE. 0 ) THEN
1928 CALL close_dataset ( grid%auxinput5_oid , config_flags , "DATASET=AUXINPUT5" )
1932 ! write(message,FMT='(A,F10.1,A)') ' EMISSIONS UPDATE TIME ',time,TRIM(current_date_char(12:13))
1933 ! CALL wrf_message( TRIM(message) )
1935 IF ( tupdate .EQ. 0. .AND. ihr .LT. 12 ) THEN
1937 CALL construct_filename1 ( inpname , 'wrfchemi_00z' , grid%id , 2 )
1938 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_emissions: Open file ',TRIM(inpname)
1939 CALL wrf_message( TRIM(message) )
1941 if( grid%auxinput5_oid .NE. 0 ) then
1942 CALL close_dataset ( grid%auxinput5_oid , config_flags , "DATASET=AUXINPUT5" )
1945 CALL open_r_dataset ( grid%auxinput5_oid, TRIM(inpname) , grid , config_flags, &
1946 "DATASET=AUXINPUT5", ierr )
1947 IF ( ierr .NE. 0 ) THEN
1948 WRITE( message , * ) 'med_read_wrf_chem_emissions: error opening ', TRIM( inpname )
1949 CALL wrf_error_fatal( TRIM( message ) )
1952 ELSE IF ( tupdate .EQ. 0. .AND. ihr .GE. 12 ) THEN
1955 CALL construct_filename1 ( inpname , 'wrfchemi_12z' , grid%id , 2 )
1956 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_emissions: Open file ',TRIM(inpname)
1957 CALL wrf_message( TRIM(message) )
1959 if( grid%auxinput5_oid .NE. 0 ) then
1960 CALL close_dataset ( grid%auxinput5_oid , config_flags , "DATASET=AUXINPUT5" )
1963 CALL open_r_dataset ( grid%auxinput5_oid, TRIM(inpname) , grid , config_flags, &
1964 "DATASET=AUXINPUT5", ierr )
1965 IF ( ierr .NE. 0 ) THEN
1966 WRITE( message , * ) 'med_read_wrf_chem_emissions: error opening ', TRIM( inpname )
1967 CALL wrf_error_fatal( TRIM( message ) )
1971 WRITE( message, '(A,2F10.1)' ) ' HOURLY EMISSIONS UPDATE TIME ',time,mod(time,3600.)
1972 CALL wrf_message( TRIM(message) )
1974 ! hourly updates to emissions
1975 IF ( ( mod( time, 3600. ) .LT. grid%dt ) .AND. &
1976 ( currentTime + stepTime .LT. stopTime ) ) THEN
1977 ! IF ( wrf_dm_on_monitor() ) CALL start_timing
1979 WRITE(message,'(A,A)')'mediation_integrate: med_read_wrf_chem_emissions: Read emissions for time ',TRIM(current_date_char)
1980 CALL wrf_message( TRIM(message) )
1982 IF ( tupdate .EQ. 0. .AND. ihrdiff .GT. 0) THEN
1983 IF( ihrdiff .GT. 12) THEN
1984 WRITE(message,'(A)')'mediation_integrate: med_read_wrf_chem_emissions: Error in emissions time, skipping all times in file '
1985 CALL wrf_message( TRIM(message) )
1988 WRITE(message,'(A,I4)')'mediation_integrate: med_read_wrf_chem_emissions: Skip emissions ',i
1989 CALL wrf_message( TRIM(message) )
1990 CALL input_auxinput5 ( grid%auxinput5_oid, grid , config_flags , ierr )
1994 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput5' )
1995 CALL input_auxinput5 ( grid%auxinput5_oid, grid , config_flags , ierr )
1997 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_chem_emissions: Do not read emissions' )
2001 ! io_style_emissions option 2: use dated emission files whose length is
2002 ! set via frames_per_auxinput5...
2004 else if( config_flags%io_style_emissions == 2 ) then
2005 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_emissions: Read emissions for time ',TRIM(current_date_char)
2006 CALL wrf_message( TRIM(message) )
2008 ! Code to read hourly emission files...
2010 if( grid%auxinput5_oid == 0 ) then
2011 CALL construct_filename2a(inpname , grid%emi_inname, grid%id , 2, current_date_char)
2012 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_emissions: Open file ',TRIM(inpname)
2013 CALL wrf_message( TRIM(message) )
2014 CALL open_r_dataset ( grid%auxinput5_oid, TRIM(inpname) , grid , config_flags, &
2015 "DATASET=AUXINPUT5", ierr )
2016 IF ( ierr .NE. 0 ) THEN
2017 WRITE( message , * ) 'med_read_wrf_chem_emissions: error opening ', TRIM( inpname )
2018 CALL wrf_error_fatal( TRIM( message ) )
2022 ! Read the emissions data.
2024 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput5' )
2025 CALL input_auxinput5 ( grid%auxinput5_oid, grid , config_flags , ierr )
2027 ! If reached the indicated number of frames in the emissions file, close it.
2029 grid%emissframes = grid%emissframes + 1
2030 IF ( grid%emissframes >= config_flags%frames_per_auxinput5 ) THEN
2031 CALL close_dataset ( grid%auxinput5_oid , config_flags , "DATASET=AUXINPUT5" )
2032 grid%emissframes = 0
2033 grid%auxinput5_oid = 0
2037 ! unknown io_style_emissions option...
2040 call wrf_error_fatal("Unknown emission style selected via io_style_emissions.")
2043 ! The following line should be commented out when using emission files
2044 ! for nested domains. Also comment out the "if" noted above.
2047 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_chem_emissions: exit' )
2049 END SUBROUTINE med_read_wrf_chem_emiss
2051 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2052 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2054 SUBROUTINE med_read_wrf_chem_bioemiss ( grid , config_flags )
2056 USE module_domain , ONLY : domain , domain_clock_get
2057 USE module_io_domain
2059 USE module_configure , ONLY : grid_config_rec_type
2061 USE module_bc_time_utilities
2065 USE module_date_time
2071 TYPE(domain) :: grid
2073 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
2076 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
2078 INTEGER :: ierr, efid
2079 REAL :: time, tupdate
2080 real, allocatable :: dumc0(:,:,:)
2081 CHARACTER (LEN=256) :: message, current_date_char, date_string
2082 CHARACTER (LEN=256) :: inpname
2084 #include "wrf_io_flags.h"
2085 ! IF ( grid%id .EQ. 1 ) THEN
2087 CALL domain_clock_get( grid, current_timestr=current_date_char )
2089 CALL construct_filename1 ( inpname , 'wrfbiochemi' , grid%id , 2 )
2090 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_bioemissions: Open file ',TRIM(inpname)
2091 CALL wrf_message( TRIM(message) )
2093 if( grid%auxinput6_oid .NE. 0 ) then
2094 CALL close_dataset ( grid%auxinput6_oid , config_flags , "DATASET=AUXINPUT6" )
2097 CALL open_r_dataset ( grid%auxinput6_oid, TRIM(inpname) , grid , config_flags, &
2098 "DATASET=AUXINPUT6", ierr )
2099 IF ( ierr .NE. 0 ) THEN
2100 WRITE( message , * ) 'med_read_wrf_chem_bioemissions: error opening ', TRIM( inpname )
2101 CALL wrf_error_fatal( TRIM( message ) )
2104 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_bioemissions: Read biogenic emissions at time ',&
2105 TRIM(current_date_char)
2106 CALL wrf_message( TRIM(message) )
2108 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput6' )
2109 CALL input_auxinput6 ( grid%auxinput6_oid, grid , config_flags , ierr )
2111 CALL close_dataset ( grid%auxinput6_oid , config_flags , "DATASET=AUXINPUT6" )
2114 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_chem_bioemissions: exit' )
2116 END SUBROUTINE med_read_wrf_chem_bioemiss
2117 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2118 SUBROUTINE med_read_wrf_chem_emissopt4 ( grid , config_flags )
2120 USE module_domain , ONLY : domain , domain_clock_get
2121 USE module_io_domain
2123 USE module_configure , ONLY : grid_config_rec_type
2125 USE module_bc_time_utilities
2129 USE module_date_time
2135 TYPE(domain) :: grid
2137 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
2140 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
2142 INTEGER :: ierr, efid
2143 REAL :: time, tupdate
2144 real, allocatable :: dumc0(:,:,:)
2145 CHARACTER (LEN=256) :: message, current_date_char, date_string
2146 CHARACTER (LEN=256) :: inpname
2148 #include "wrf_io_flags.h"
2149 ! IF ( grid%id .EQ. 1 ) THEN
2151 CALL domain_clock_get( grid, current_timestr=current_date_char )
2153 CALL construct_filename1 ( inpname , 'wrfchemi' , grid%id , 2 )
2154 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_emissions: Open file ',TRIM(inpname)
2155 CALL wrf_message( TRIM(message) )
2157 if( grid%auxinput5_oid .NE. 0 ) then
2158 CALL close_dataset ( grid%auxinput5_oid , config_flags , "DATASET=AUXINPUT5" )
2161 CALL open_r_dataset ( grid%auxinput5_oid, TRIM(inpname) , grid , config_flags, &
2162 "DATASET=AUXINPUT5", ierr )
2163 IF ( ierr .NE. 0 ) THEN
2164 WRITE( message , * ) 'med_read_wrf_chem_emissions: error opening ', TRIM( inpname )
2165 CALL wrf_error_fatal( TRIM( message ) )
2168 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_emissions: Read biogenic emissions at time ',&
2169 TRIM(current_date_char)
2170 CALL wrf_message( TRIM(message) )
2172 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput5' )
2173 CALL input_auxinput5 ( grid%auxinput5_oid, grid , config_flags , ierr )
2175 CALL close_dataset ( grid%auxinput5_oid , config_flags , "DATASET=AUXINPUT5" )
2178 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_chem_emissions: exit' )
2180 END SUBROUTINE med_read_wrf_chem_emissopt4
2182 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2183 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2185 SUBROUTINE med_read_wrf_chem_dms_emiss ( grid , config_flags )
2187 USE module_domain , ONLY : domain , domain_clock_get
2188 USE module_io_domain
2190 USE module_configure , ONLY : grid_config_rec_type
2192 USE module_bc_time_utilities
2196 USE module_date_time
2202 TYPE(domain) :: grid
2204 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
2207 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
2209 INTEGER :: ierr, efid
2210 REAL :: time, tupdate
2211 real, allocatable :: dumc0(:,:,:)
2212 CHARACTER (LEN=256) :: message, current_date_char, date_string
2213 CHARACTER (LEN=256) :: inpname
2215 #include "wrf_io_flags.h"
2216 ! IF ( grid%id .EQ. 1 ) THEN
2218 CALL domain_clock_get( grid, current_timestr=current_date_char )
2220 CALL construct_filename1 ( inpname , 'wrfchemi_dms' , grid%id , 2 )
2221 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_dms_emiss: Open file ',TRIM(inpname)
2222 CALL wrf_message( TRIM(message) )
2224 if( grid%auxinput7_oid .NE. 0 ) then
2225 CALL close_dataset ( grid%auxinput7_oid , config_flags , "DATASET=AUXINPUT7" )
2228 CALL open_r_dataset ( grid%auxinput7_oid, TRIM(inpname) , grid , config_flags, &
2229 "DATASET=AUXINPUT7", ierr )
2230 IF ( ierr .NE. 0 ) THEN
2231 WRITE( message , * ) 'med_read_wrf_chem_dms_emiss: error opening ', TRIM( inpname )
2232 CALL wrf_error_fatal( TRIM( message ) )
2235 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_dms_emiss: Read dms reference fields',&
2236 TRIM(current_date_char)
2237 CALL wrf_message( TRIM(message) )
2239 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput7' )
2240 CALL input_auxinput7 ( grid%auxinput7_oid, grid , config_flags , ierr )
2242 CALL close_dataset ( grid%auxinput7_oid , config_flags , "DATASET=AUXINPUT7" )
2245 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_chem_dms_emiss: exit' )
2247 END SUBROUTINE med_read_wrf_chem_dms_emiss
2249 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2250 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2252 SUBROUTINE med_read_wrf_chem_gocart_bg ( grid , config_flags )
2254 USE module_domain , ONLY : domain , domain_clock_get
2255 USE module_io_domain
2257 USE module_configure , ONLY : grid_config_rec_type
2259 USE module_bc_time_utilities
2263 USE module_date_time
2269 TYPE(domain) :: grid
2271 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
2274 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
2276 INTEGER :: ierr, efid
2277 REAL :: time, tupdate
2278 real, allocatable :: dumc0(:,:,:)
2279 CHARACTER (LEN=256) :: message, current_date_char, date_string
2280 CHARACTER (LEN=256) :: inpname
2282 #include "wrf_io_flags.h"
2283 ! IF ( grid%id .EQ. 1 ) THEN
2285 CALL domain_clock_get( grid, current_timestr=current_date_char )
2287 CALL construct_filename1 ( inpname , 'wrfchemi_gocart_bg' , grid%id , 2 )
2288 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_gocart_bg: Open file ',TRIM(inpname)
2289 CALL wrf_message( TRIM(message) )
2291 if( grid%auxinput8_oid .NE. 0 ) then
2292 CALL close_dataset ( grid%auxinput8_oid , config_flags , "DATASET=AUXINPUT8" )
2295 CALL open_r_dataset ( grid%auxinput8_oid, TRIM(inpname) , grid , config_flags, &
2296 "DATASET=AUXINPUT8", ierr )
2297 IF ( ierr .NE. 0 ) THEN
2298 WRITE( message , * ) 'med_read_wrf_chem_gocart_bg: error opening ', TRIM( inpname )
2299 CALL wrf_error_fatal( TRIM( message ) )
2302 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_gocart_bg: Read gocart_bg at time ',&
2303 TRIM(current_date_char)
2304 CALL wrf_message( TRIM(message) )
2306 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput8' )
2307 CALL input_auxinput8 ( grid%auxinput8_oid, grid , config_flags , ierr )
2309 CALL close_dataset ( grid%auxinput8_oid , config_flags , "DATASET=AUXINPUT8" )
2312 ! CALL wrf_global_to_patch_real ( backg_no3_io , grid%backg_no3 , grid%domdesc, ' ' , 'xyz' , &
2313 ! ids, ide-1 , jds , jde-1 , kds , kde-1, &
2314 ! ims, ime , jms , jme , kms , kme , &
2315 ! ips, ipe , jps , jpe , kps , kpe )
2318 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_chem_gocart_bg: exit' )
2320 END SUBROUTINE med_read_wrf_chem_gocart_bg
2321 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2323 SUBROUTINE med_read_wrf_volc_emiss ( grid , config_flags )
2325 USE module_domain , ONLY : domain , domain_clock_get
2326 USE module_io_domain
2328 USE module_configure , ONLY : grid_config_rec_type
2330 USE module_bc_time_utilities
2334 USE module_date_time
2340 TYPE(domain) :: grid
2342 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
2345 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
2347 INTEGER :: ierr, efid
2348 REAL :: time, tupdate
2349 real, allocatable :: dumc0(:,:,:)
2350 CHARACTER (LEN=256) :: message, current_date_char, date_string
2351 CHARACTER (LEN=256) :: inpname
2353 #include "wrf_io_flags.h"
2354 CALL domain_clock_get( grid, current_timestr=current_date_char )
2356 CALL construct_filename1 ( inpname , 'wrfchemv' , grid%id , 2 )
2357 WRITE(message,*)'mediation_integrate: med_read_wrf_volc_emiss: Open file ',TRIM(inpname)
2358 CALL wrf_message( TRIM(message) )
2360 if( grid%auxinput13_oid .NE. 0 ) then
2361 CALL close_dataset ( grid%auxinput13_oid , config_flags , "DATASET=AUXINPUT13" )
2364 CALL open_r_dataset ( grid%auxinput13_oid, TRIM(inpname) , grid , config_flags, &
2365 "DATASET=AUXINPUT13", ierr )
2366 IF ( ierr .NE. 0 ) THEN
2367 WRITE( message , * ) 'med_read_wrf_volc_emiss: error opening ', TRIM( inpname )
2368 CALL wrf_error_fatal( TRIM( message ) )
2371 WRITE(message,*)'mediation_integrate: med_read_wrf_volc_emiss: Read volcanic ash emissions',&
2372 TRIM(current_date_char)
2373 CALL wrf_message( TRIM(message) )
2375 CALL wrf_debug (100 , 'mediation_integrate: calling input_auxinput13' )
2376 CALL input_auxinput13 ( grid%auxinput13_oid, grid , config_flags , ierr )
2378 CALL close_dataset ( grid%auxinput13_oid , config_flags , "DATASET=AUXINPUT13" )
2380 CALL wrf_debug (100 , 'mediation_integrate: med_read_wrf_volc_emiss: exit' )
2382 END SUBROUTINE med_read_wrf_volc_emiss
2384 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2385 SUBROUTINE med_read_wrf_chem_emissopt3 ( grid , config_flags )
2387 USE module_domain , ONLY : domain , domain_clock_get
2388 USE module_io_domain
2390 USE module_configure , ONLY : grid_config_rec_type
2392 USE module_bc_time_utilities
2396 USE module_date_time
2402 TYPE(domain) :: grid
2404 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
2407 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
2409 INTEGER :: ierr, efid
2410 REAL :: time, tupdate
2411 real, allocatable :: dumc0(:,:,:)
2412 CHARACTER (LEN=256) :: message, current_date_char, date_string
2413 CHARACTER (LEN=256) :: inpname
2415 #include "wrf_io_flags.h"
2416 ! IF ( grid%id .EQ. 1 ) THEN
2418 CALL domain_clock_get( grid, current_timestr=current_date_char )
2420 CALL construct_filename1 ( inpname , 'wrffirechemi' , grid%id , 2 )
2421 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_fireemissions: Open file ',TRIM(inpname)
2422 CALL wrf_message( TRIM(message) )
2424 if( grid%auxinput7_oid .NE. 0 ) then
2425 CALL close_dataset ( grid%auxinput7_oid , config_flags , "DATASET=AUXINPUT7" )
2428 CALL open_r_dataset ( grid%auxinput7_oid, TRIM(inpname) , grid , config_flags, &
2429 "DATASET=AUXINPUT7", ierr )
2430 IF ( ierr .NE. 0 ) THEN
2431 WRITE( message , * ) 'med_read_wrf_chem_fireemissions: error opening ', TRIM( inpname )
2432 CALL wrf_error_fatal( TRIM( message ) )
2435 WRITE(message,*)'mediation_integrate: med_read_wrf_chem_fireemissions: Read fire emissions at time ',&
2436 TRIM(current_date_char)
2437 CALL wrf_message( TRIM(message) )
2439 CALL wrf_debug (00 , 'mediation_integrate: calling input_auxinput7' )
2440 CALL input_auxinput7 ( grid%auxinput7_oid, grid , config_flags , ierr )
2442 CALL close_dataset ( grid%auxinput7_oid , config_flags , "DATASET=AUXINPUT7" )
2445 CALL wrf_debug (00 , 'mediation_integrate: med_read_wrf_chem_fireemissions: exit' )
2447 END SUBROUTINE med_read_wrf_chem_emissopt3
2451 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2453 SUBROUTINE med_read_qna_emissions ( grid , config_flags )
2455 USE module_domain , ONLY : domain , domain_clock_get
2456 USE module_io_domain
2458 USE module_configure , ONLY : grid_config_rec_type
2460 USE module_bc_time_utilities
2464 USE module_date_time
2470 TYPE(domain) :: grid
2472 TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
2475 LOGICAL, EXTERNAL :: wrf_dm_on_monitor
2477 INTEGER :: ierr, efid
2478 REAL :: time, tupdate
2479 real, allocatable :: dumc0(:,:,:)
2480 CHARACTER (LEN=256) :: message, current_date_char, date_string
2481 CHARACTER (LEN=256) :: inpname
2483 #include "wrf_io_flags.h"
2485 CALL domain_clock_get( grid, current_timestr=current_date_char )
2487 CALL construct_filename1 ( inpname , 'wrfqnainp' , grid%id , 2 )
2488 WRITE(message,*)'mediation_integrate: med_read_qna_emissions: Open file ',TRIM(inpname)
2489 CALL wrf_message( TRIM(message) )
2491 if( grid%auxinput17_oid .NE. 0 ) then
2492 CALL close_dataset ( grid%auxinput17_oid , config_flags , "DATASET=AUXINPUT17" )
2495 CALL open_r_dataset ( grid%auxinput17_oid, TRIM(inpname) , grid , config_flags, &
2496 "DATASET=AUXINPUT17", ierr )
2497 IF ( ierr .NE. 0 ) THEN
2498 WRITE( message , * ) 'med_read_qna_emissions: error opening ', TRIM( inpname )
2499 CALL wrf_error_fatal( TRIM( message ) )
2502 WRITE(message,*)'mediation_integrate: med_read_qna_emissions: Read surface aerosol emissions at time ',&
2503 TRIM(current_date_char)
2504 CALL wrf_message( TRIM(message) )
2506 CALL wrf_debug (00 , 'mediation_integrate: calling input_auxinput17' )
2507 CALL input_auxinput17 ( grid%auxinput17_oid, grid , config_flags , ierr )
2509 CALL close_dataset ( grid%auxinput17_oid , config_flags , "DATASET=AUXINPUT17" )
2511 CALL wrf_debug (00 , 'mediation_integrate: med_read_qna_emissions: exit' )
2513 END SUBROUTINE med_read_qna_emissions