!WRF:DRIVER_LAYER:MAIN
!
PROGRAM wrf,67
USE module_machine
USE module_domain
USE module_integrate
USE module_driver_constants
USE module_configure
USE module_timing
USE module_wrf_error
USE esmf_mod
#ifdef DM_PARALLEL
USE module_dm
#endif
IMPLICIT NONE
REAL :: time
INTEGER :: loop , &
levels_to_process
TYPE (domain) , POINTER :: keep_grid, grid_ptr, null_domain
TYPE (domain) :: dummy
TYPE (grid_config_rec_type) :: config_flags
INTEGER :: number_at_same_level
INTEGER :: time_step_begin_restart
INTEGER :: max_dom , domain_id , fid , oid , idum1 , idum2 , ierr
INTEGER :: debug_level
INTEGER :: rc
LOGICAL :: input_from_file
#ifdef DM_PARALLEL
INTEGER :: nbytes
INTEGER, PARAMETER :: configbuflen = 2*1024
INTEGER :: configbuf( configbuflen )
LOGICAL , EXTERNAL :: wrf_dm_on_monitor
#endif
CHARACTER (LEN=80) :: rstname
CHARACTER (LEN=80) :: message
INTERFACE
SUBROUTINE Set_Timekeeping( grid )
USE module_domain
TYPE(domain), POINTER :: grid
END SUBROUTINE Set_Timekeeping
END INTERFACE
! Define the name of this program (program_name defined in module_domain)
program_name = "WRF V1.3 MODEL"
! Get the NAMELIST data for input.
CALL init_modules
#ifdef DM_PARALLEL
IF ( wrf_dm_on_monitor() ) THEN
CALL initial_config
ENDIF
CALL get_config_as_buffer
( configbuf, configbuflen, nbytes )
CALL wrf_dm_bcast_bytes
( configbuf, nbytes )
CALL set_config_as_buffer
( configbuf, configbuflen )
CALL wrf_dm_initialize
#else
CALL initial_config
#endif
CALL get_debug_level
( debug_level )
CALL set_wrf_debug_level
( debug_level )
! allocated and configure the mother domain
NULLIFY( null_domain )
CALL wrf_message
( program_name )
CALL wrf_debug ( 100 , 'wrf: calling alloc_and_configure_domain ' )
CALL alloc_and_configure_domain
( domain_id = 1 , &
grid = head_grid , &
parent = null_domain , &
kid = -1 )
CALL wrf_debug ( 100 , 'wrf: calling model_to_grid_config_rec ' )
CALL model_to_grid_config_rec
( head_grid%id , model_config_rec , config_flags )
CALL wrf_debug ( 100 , 'wrf: calling set_scalar_indices_from_config ' )
CALL set_scalar_indices_from_config
( head_grid%id , idum1, idum2 )
CALL wrf_debug ( 100 , 'wrf: calling init_wrfio' )
CALL init_wrfio
#ifdef DM_PARALLEL
CALL get_config_as_buffer
( configbuf, configbuflen, nbytes )
CALL wrf_dm_bcast_bytes
( configbuf, nbytes )
CALL set_config_as_buffer
( configbuf, configbuflen )
#endif
CALL Set_Timekeeping
(head_grid)
write(0,*)'after Set_Timekeeping ',head_grid%dt
CALL med_initialdata_input
( head_grid , config_flags )
write(0,*)'after med_initialdata_input ',head_grid%dt
! If this is a "only write the restart file at the initial time and stop" run,
! write out a restart file and shut everything down. There is no other output
! file generated, just the restart at the initial time. This is a specialty
! use option, not typically activated.
IF ( config_flags%write_restart_at_0h ) THEN
write(0,*)'doing the "restart file at the initial time and stop" run'
CALL med_restart_out
( head_grid, config_flags )
CALL med_shutdown_io
( head_grid , config_flags )
CALL wrf_debug
( 0 , ' 0 h restart only wrf: SUCCESS COMPLETE WRF' )
CALL wrf_shutdown
stop
END IF
! The forecast integration for the most coarse grid is now started. The
! integration is from the first step (1) to the last step of the simulation.
head_grid%start_subtime = head_grid%start_time
head_grid%stop_subtime = head_grid%stop_time
CALL wrf_debug ( 100 , 'wrf: calling integrate' )
CALL integrate
( head_grid )
CALL wrf_debug
( 100 , 'wrf: back from integrate' )
CALL med_shutdown_io
( head_grid , config_flags )
CALL wrf_debug
( 100 , 'wrf: back from med_shutdown_io' )
CALL wrf_debug
( 0 , 'wrf: SUCCESS COMPLETE WRF' )
CALL wrf_shutdown
STOP
END PROGRAM wrf