SCALE-RM
mod_rm_driver.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
11 !-------------------------------------------------------------------------------
12 #include "scalelib.h"
14  !-----------------------------------------------------------------------------
15  !
16  !++ used modules
17  !
18  use scale_precision
19  use scale_io
20  use scale_prof
21  !-----------------------------------------------------------------------------
22  implicit none
23  private
24  !-----------------------------------------------------------------------------
25  !
26  !++ included parameters
27  !
28 #include "scale-rm.h"
29  !-----------------------------------------------------------------------------
30  !
31  !++ Public procedure
32  !
33  public :: rm_driver
34 
35  !-----------------------------------------------------------------------------
36  !
37  !++ Public parameters & variables
38  !
39  !-----------------------------------------------------------------------------
40  !
41  !++ Private procedure
42  !
43  !-----------------------------------------------------------------------------
44  !
45  !++ Private parameters & variables
46  !
47  character(len=H_MID), private, parameter :: modelname = "SCALE-RM ver. "//version
48 
49  !-----------------------------------------------------------------------------
50 contains
51  !-----------------------------------------------------------------------------
53  subroutine rm_driver( &
54  comm_world, &
55  intercomm_parent, &
56  intercomm_child, &
57  cnf_fname )
58  use scale_file, only: &
60  use scale_prc, only: &
61  prc_abort, &
63  use scale_fpm, only: &
64  fpm_alive, &
65  fpm_polling, &
67  use scale_prc_cartesc, only: &
69  use scale_const, only: &
71  use scale_calendar, only: &
73  use scale_random, only: &
75  use scale_atmos_hydrometeor, only: &
79  use scale_atmos_grid_cartesc, only: &
81  dx, &
82  dy
89  use scale_ocean_grid_cartesc, only: &
95  use scale_land_grid_cartesc, only: &
97  use scale_land_grid_cartesc_real, only: &
101  use scale_urban_grid_cartesc, only: &
103  use scale_urban_grid_cartesc_real, only: &
105  use scale_file_cartesc, only: &
108  use scale_comm_cartesc, only: &
109  comm_setup , &
111  use scale_comm_cartesc_nest, only: &
113  use scale_topography, only: &
114  topo_setup
115  use scale_landuse, only: &
117  use scale_statistics, only: &
119  use scale_time, only: &
120  time_nowdate, &
121  time_nowms, &
122  time_nowstep, &
123  time_dtsec
124  use scale_atmos_hydrostatic, only: &
126  use scale_atmos_thermodyn, only: &
128  use scale_atmos_saturation, only: &
130  use scale_bulkflux, only: &
134  use scale_file_history, only: &
138  use scale_file_history_cartesc, only: &
140  use scale_monitor_cartesc, only: &
142  use scale_monitor, only: &
143  monitor_write, &
145 
146  use mod_atmos_driver, only: &
148  use mod_admin_versioncheck, only: &
150  use mod_admin_time, only: &
158  time_doresume, &
159  time_doend
160  use mod_admin_restart, only: &
163  use mod_atmos_admin, only: &
165  atmos_do, &
167  use mod_atmos_vars, only: &
171  use mod_atmos_driver, only: &
177  use mod_atmos_phy_mp_vars, only: &
178  qa_mp
179  use mod_ocean_admin, only: &
181  ocean_do
182  use mod_ocean_vars, only: &
184  use mod_ocean_driver, only: &
188  use mod_land_admin, only: &
190  land_do
191  use mod_land_vars, only: &
193  use mod_land_driver, only: &
197  use mod_urban_admin, only: &
199  urban_do, &
200  urban_land
201  use mod_urban_vars, only: &
203  use mod_urban_driver, only: &
207  use mod_lake_admin, only: &
209  lake_do
210  use mod_cpl_admin, only: &
211  cpl_admin_setup, &
212  cpl_sw
213  use mod_cpl_vars, only: &
215  use mod_user, only: &
217  user_setup, &
220  implicit none
221 
222  integer, intent(in) :: comm_world
223  integer, intent(in) :: intercomm_parent
224  integer, intent(in) :: intercomm_child
225  character(len=*), intent(in) :: cnf_fname
226 
227  integer :: myrank
228  integer :: fpm_counter
229  logical :: ismaster
230  logical :: sign_exit
231  !---------------------------------------------------------------------------
232 
233  !########## Initial setup ##########
234 
235  ! setup standard I/O
236  call io_setup( modelname, cnf_fname )
237 
238  ! setup MPI
239  call prc_local_setup( comm_world, & ! [IN]
240  myrank, & ! [OUT]
241  ismaster ) ! [OUT]
242 
243  ! setup Log
244  call io_log_setup( myrank, ismaster )
245 
246  ! namelist compatibility check
247  call admin_versioncheck
248 
249  ! setup process
250  call prc_cartesc_setup
251 
252  ! setup PROF
253  call prof_setup
254 
255  !###########################################################################
256  ! profiler start
257  call prof_setprefx('INIT')
258  call prof_rapstart('Initialize', 0)
259 
260  ! setup constants
261  call const_setup
262 
263  ! setup calendar
264  call calendar_setup
265 
266  ! setup random number
267  call random_setup
268 
269  ! setup submodel administrator
270  call atmos_admin_setup
271  call ocean_admin_setup
272  call land_admin_setup
273  call urban_admin_setup
274  call lake_admin_setup
275  call cpl_admin_setup
276 
277  ! setup horizontal/vertical grid coordinates (cartesian,idealized)
278  if ( atmos_do ) then
281  endif
282 
283  if ( ocean_do ) then
286  endif
287 
288  if ( land_do ) then
291  endif
292 
293  if ( urban_do ) then
296  endif
297 
298  ! setup tracer index
300  call atmos_driver_tracer_setup
301  call user_tracer_setup
302 
303  ! setup file I/O
304  call file_cartesc_setup
305 
306  ! setup mpi communication
307  call comm_setup
308 
309  ! setup topography
310  call topo_setup
311  ! setup land use category index/fraction
312  call landuse_setup( ocean_do, (.not. urban_land), lake_do )
313 
314  ! setup grid coordinates (real world)
315  if ( atmos_do ) then
317  ! setup grid transfer metrics (uses in ATMOS_dynamics)
319  endif
323 
324  ! setup restart
326  ! setup time
327  call admin_time_setup( setup_timeintegration = .true. )
328  ! setup statistics
329  call statistics_setup
330  ! setup history I/O
332  ! setup monitor I/O
334  ! setup external in
336 
337  ! setup nesting grid
338  call comm_cartesc_nest_setup ( qa_mp, atmos_phy_mp_type, intercomm_parent, intercomm_child )
339 
340  ! setup common tools
344 
345  call bulkflux_setup( sqrt(dx**2+dy**2) )
346 
347  ! setup variable container
348  if ( atmos_do ) call atmos_vars_setup
349  if ( ocean_do ) call ocean_vars_setup
350  if ( land_do ) call land_vars_setup
351  if ( urban_do ) call urban_vars_setup
352  if ( cpl_sw ) call cpl_vars_setup
353 
354  ! setup driver
355  if ( atmos_do ) call atmos_driver_setup
356  if ( ocean_do ) call ocean_driver_setup
357  if ( land_do ) call land_driver_setup
358  if ( urban_do ) call urban_driver_setup
359 
360  call user_setup
361 
362  call prof_rapend('Initialize', 0)
363 
364  !########## main ##########
365 
366 #ifdef FIPP
367  call fipp_start
368 #endif
369 #ifdef PAPI
370  call prof_papi_rapstart
371 #endif
372 
373  log_newline
374  log_progress(*) 'START TIMESTEP'
375  call prof_setprefx('MAIN')
376  call prof_rapstart('Main_Loop', 0)
377 
378  fpm_counter = 0
379  do
380  ! report current time
382 
383  if ( time_doresume ) then
384  ! set state from restart files
385  call restart_read
386 
387  ! history&monitor file output
388  call monitor_write('MAIN', time_nowstep)
389  call file_history_write ! if needed
390  endif
391 
392  ! time advance
393  call admin_time_advance
395 
396  ! change to next state
401  call user_update
402  ! restart output
404 
405  ! calc tendencies and diagnostices
406  if( atmos_do .AND. time_doatmos_step ) call atmos_driver_calc_tendency( force = .false. )
407  if( ocean_do .AND. time_doocean_step ) call ocean_driver_calc_tendency( force = .false. )
408  if( land_do .AND. time_doland_step ) call land_driver_calc_tendency( force = .false. )
409  if( urban_do .AND. time_dourban_step ) call urban_driver_calc_tendency( force = .false. )
410  if( cpl_sw .AND. time_doatmos_step ) call atmos_driver_calc_tendency_from_sflux( force = .false. )
411  call user_calc_tendency
412 
413  ! history&monitor file output
414  call monitor_write('MAIN', time_nowstep)
415  call file_history_write
416 
417  if( time_doend ) exit
418 
419  if( io_l ) call flush(io_fid_log)
420 
421  ! FPM polling
422  if ( fpm_alive .AND. fpm_polling_freq > 0 ) then
423  if ( fpm_counter > fpm_polling_freq ) then
424  sign_exit = .false.
425  call fpm_polling( .true., sign_exit )
426  if ( sign_exit ) then
427  log_error("scalerm",*) 'receive stop signal'
428  call prc_abort
429  endif
430  fpm_counter = 0
431  endif
432 
433  fpm_counter = fpm_counter + 1
434  endif
435 
436  enddo
437 
438  call prof_rapend('Main_Loop', 0)
439 
440  log_progress(*) 'END TIMESTEP'
441  log_newline
442 
443 #ifdef FIPP
444  call fipp_stop
445 #endif
446 #ifdef PAPI
447  call prof_papi_rapstop
448 #endif
449 
450  !########## Finalize ##########
451 
452  call prof_setprefx('FIN')
453 
454  call prof_rapstart('All', 1)
455 
457 
458  ! check data
460 
461  call prof_rapstart('Monit', 2)
462  call monitor_finalize
463  call prof_rapend ('Monit', 2)
464 
465  call prof_rapstart('File', 2)
467  ! clean up resource allocated for I/O
469 
470  call comm_cleanup
471 
472  call file_close_all
473  call prof_rapend ('File', 2)
474 
475  call prof_rapend ('All', 1)
476 
477  call prof_rapreport
478 #ifdef PAPI
479  call prof_papi_rapreport
480 #endif
481 
482  return
483  end subroutine rm_driver
484 
485  !-----------------------------------------------------------------------------
486  subroutine restart_read
488  use scale_atmos_grid_cartesc, only: &
489  cz => atmos_grid_cartesc_cz, &
490  fz => atmos_grid_cartesc_fz, &
491  fdz => atmos_grid_cartesc_fdz, &
493  use scale_atmos_grid_cartesc_real, only: &
494  real_cz => atmos_grid_cartesc_real_cz, &
495  real_fz => atmos_grid_cartesc_real_fz, &
496  real_phi => atmos_grid_cartesc_real_phi, &
498  use scale_time, only: &
500  use mod_admin_restart, only: &
502  use mod_atmos_admin, only: &
503  atmos_do
504  use mod_atmos_driver, only: &
508  use mod_atmos_vars, only: &
513  dens, &
514  pott, &
515  temp, &
516  pres, &
517  qv
518  use mod_atmos_bnd_driver, only: &
520  use scale_atmos_refstate, only: &
522  use mod_ocean_admin, only: &
523  ocean_do
524  use mod_ocean_driver, only: &
527  use mod_ocean_vars, only: &
529  use mod_land_admin, only: &
530  land_do
531  use mod_land_driver, only: &
534  use mod_land_vars, only: &
536  use mod_urban_admin, only: &
537  urban_do
538  use mod_urban_driver, only: &
541  use mod_urban_vars, only: &
543  use mod_cpl_admin, only: &
544  cpl_sw
545  use mod_user, only: &
547  implicit none
548  !---------------------------------------------------------------------------
549 
550  ! read restart data
551  call admin_restart_read
552 
553  if ( atmos_do ) then
554  ! calc diagnostics
556  call atmos_refstate_update( ka, ks, ke, ia, isb, ieb, ja, jsb, jeb, &
557  dens(:,:,:), pott(:,:,:), temp(:,:,:), pres(:,:,:), qv(:,:,:), & ! [IN]
558  cz(:), fz(:), fdz(:), rcdz(:), & ! [IN]
559  real_cz(:,:,:), real_fz(:,:,:), real_phi(:,:,:), area(:,:), & ! [IN]
560  time_nowdaysec, & ! [IN]
561  force = .true. )
564  endif
565 
566  ! setup surface condition
567  if( atmos_do ) call atmos_surface_set( countup=.false. )
568  if( ocean_do ) call ocean_surface_set( countup=.false. )
569  if( land_do ) call land_surface_set ( countup=.false. )
570  if( urban_do ) call urban_surface_set( countup=.false. )
571 
572  ! calc tendencies
573  if( atmos_do ) call atmos_driver_calc_tendency ( force=.true. )
574  if( ocean_do ) call ocean_driver_calc_tendency ( force=.true. )
575  if( land_do ) call land_driver_calc_tendency ( force=.true. )
576  if( urban_do ) call urban_driver_calc_tendency ( force=.true. )
577  if( cpl_sw ) call atmos_driver_calc_tendency_from_sflux( force=.true. )
578  call user_calc_tendency
579 
580  !########## History & Monitor ##########
581  if( atmos_do ) call atmos_vars_history
582  if( ocean_do ) call ocean_vars_history
583  if( land_do ) call land_vars_history
584  if( urban_do ) call urban_vars_history
585 
586  call atmos_vars_monitor
587 
588  return
589  end subroutine restart_read
590 
591 end module mod_rm_driver
module ATMOS admin
module Land admin
subroutine, public atmos_refstate_update(KA, KS, KE, IA, IS, IE, JA, JS, JE, DENS, POTT, TEMP, PRES, QV, CZ, FZ, FDZ, RCDZ, REAL_CZ, REAL_FZ, REAL_PHI, AREA, nowsec, force)
Update reference state profile (Horizontal average)
subroutine, public file_close_all(skip_abort)
integer, public time_nowstep
current step [number]
Definition: scale_time.F90:74
integer, public fpm_polling_freq
Definition: scale_fpm.F90:31
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_phi
geopotential [m2/s2] (cell center)
subroutine, public file_cartesc_setup
Setup.
subroutine, public urban_driver_calc_tendency(force)
Calclate tendency.
subroutine, public urban_grid_cartesc_setup
Setup.
subroutine, public prof_setup
Definition: scale_prof.F90:103
subroutine, public atmos_surface_set(countup)
Set surface boundary condition.
module atmosphere / saturation
logical, public time_dourban_step
execute urban component in this step?
subroutine, public prof_setprefx(prefxname)
Definition: scale_prof.F90:139
subroutine, public atmos_saturation_setup
Setup.
subroutine, public landuse_setup(OCEAN_do, URBAN_do, LAKE_do)
Setup.
module file / external_input_cartesC
subroutine, public ocean_grid_cartesc_index_setup
Setup.
subroutine, public land_driver_update
Land step.
real(dp), public time_nowms
subsecond part of current time [millisec]
Definition: scale_time.F90:70
logical, public time_doend
finish program in this step?
subroutine, public ocean_driver_setup
Setup.
subroutine, public land_grid_cartesc_real_setup
Setup real grid.
subroutine, public atmos_boundary_driver_set
set
subroutine, public ocean_grid_cartesc_real_setup
Setup area and volume.
integer, public ia
of whole cells: x, local, with HALO
module Atmosphere / Physics Cloud Microphysics
module URBAN driver
module land / grid / cartesianC / real
module USER
Definition: mod_user.F90:12
module land / grid / cartesianC / index
subroutine, public random_setup
Setup.
subroutine, public file_cartesc_cleanup
deallocate buffers
module Atmosphere Grid CartesianC metirc
subroutine, public user_calc_tendency
Calculation tendency.
Definition: mod_user.F90:125
subroutine, public urban_driver_update
Urban step.
subroutine, public atmos_grid_cartesc_metric_setup
Setup.
module atmosphere / reference state
logical, public ocean_do
subroutine, public land_vars_setup
Setup.
module ATMOSPHERIC Variables
subroutine, public ocean_vars_history
History output set for ocean variables.
subroutine restart_read
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:73
logical, public lake_do
subroutine, public monitor_cartesc_setup(dt, ATMOS_do, OCEAN_do, LAND_do, URBAN_do)
Setup.
subroutine, public urban_vars_history
History output set for urban variables.
subroutine, public prc_cartesc_setup
Setup Processor topology.
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_fz
geopotential height [m] (wxy)
integer, public ja
of whole cells: y, local, with HALO
module process / cartesC
subroutine, public atmos_vars_calc_diagnostics
Calc diagnostic variables.
logical, public urban_land
subroutine, public land_grid_cartesc_setup
Setup.
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fdz
z-length of grid(i+1) to grid(i) [m]
subroutine, public user_tracer_setup
Config before setup of tracers.
Definition: mod_user.F90:54
real(rp), dimension(:,:,:), allocatable, target, public dens
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_fz
face coordinate [m]: z, local
subroutine, public ocean_driver_update
Ocean step.
module URBAN Variables
subroutine, public land_grid_cartesc_index_setup
Setup.
logical, public fpm_alive
Definition: scale_fpm.F90:32
subroutine, public atmos_grid_cartesc_real_setup
Setup.
subroutine, public atmos_driver_calc_tendency_from_sflux(force)
Calculation tendency from surface flux with coupler.
module urban / grid / icosahedralA / index
subroutine, public atmos_driver_calc_tendency(force)
Calculation tendency.
subroutine, public monitor_write(memo, nowstep)
Flush monitor buffer to formatted file.
subroutine, public land_admin_setup
Setup.
module COMMUNICATION
module Lake admin
subroutine, public urban_surface_set(countup)
Set surface boundary to other model.
module SCALE-RM (a main routine of regional model)
subroutine, public atmos_grid_cartesc_index_setup(KMAX, IMAXG, JMAXG, IMAX, JMAX, KHALO, IHALO, JHALO, IBLOCK, JBLOCK)
setup index
module file
Definition: scale_file.F90:15
logical, public io_l
output log or not? (this process)
Definition: scale_io.F90:61
subroutine, public admin_time_setup(setup_TimeIntegration)
Setup.
subroutine, public admin_restart_setup
Setup.
subroutine, public comm_cartesc_nest_setup(QA_MP, MP_TYPE_in, inter_parent, inter_child)
Setup.
subroutine, public topo_setup
Setup.
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_rcdz
reciprocal of center-dz
module atmosphere / hydrometeor
module ADMIN VERSIONCHECK
logical, public time_doocean_step
execute ocean component in this step?
subroutine, public calendar_setup
Setup.
module LANDUSE
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:38
logical, public time_doresume
resume in this step?
module atmosphere / grid / cartesC index
integer, public ke
end point of inner domain: z, local
module ocean / grid / cartesianC / real
subroutine, public land_driver_setup
Setup.
subroutine, public atmos_driver_tracer_setup
Tracer setup.
module OCEAN driver
subroutine, public cpl_vars_setup
Setup.
subroutine, public ocean_surface_set(countup)
Put surface boundary to other model.
module COUPLER Variables
module MONITOR
module ATMOSPHERE / Boundary treatment
module PROCESS
Definition: scale_prc.F90:11
real(rp), dimension(:,:,:), allocatable, target, public temp
subroutine, public atmos_vars_setup
Setup.
module ATMOSPHERE driver
subroutine, public const_setup
Setup.
logical, public atmos_do
subroutine, public statistics_setup
Setup.
subroutine, public atmos_grid_cartesc_setup(basename, aggregate)
Setup.
module atmosphere / hydrostatic barance
module TIME
Definition: scale_time.F90:16
module atmosphere / grid / cartesC
integer, public ks
start point of inner domain: z, local
module MONITOR CartesC
subroutine, public rm_driver(comm_world, intercomm_parent, intercomm_child, cnf_fname)
Setup.
subroutine, public lake_admin_setup
Setup.
module urban / grid / cartesianC
module Ocean admin
subroutine, public atmos_thermodyn_setup
Setup.
real(rp), dimension(:,:,:), allocatable, target, public pott
subroutine, public atmos_driver_setup
Setup.
subroutine, public fpm_polling(run_stat, stop_signal)
Main system of FPM.
Definition: scale_fpm.F90:176
logical, public cpl_sw
module LAND Variables
subroutine, public file_history_write
module administrator for restart
subroutine, public file_history_finalize
finalization
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:338
subroutine, public urban_vars_setup
Setup.
real(rp), dimension(:,:,:), allocatable, pointer, target, public qv
subroutine, public prc_local_setup(comm, myrank, ismaster)
Setup MPI in local communicator.
Definition: scale_prc.F90:219
subroutine, public urban_driver_setup
Setup.
module CONSTANT
Definition: scale_const.F90:11
subroutine, public land_driver_calc_tendency(force)
Calculate tendency.
module Communication CartesianC nesting
subroutine, public urban_grid_cartesc_real_setup
Setup real grid.
subroutine, public io_setup(APPNAME, conf_name, allow_noconf)
Setup.
Definition: scale_io.F90:87
subroutine, public file_history_cartesc_setup
Setup.
character(len=h_short), public atmos_phy_mp_type
subroutine, public ocean_admin_setup
Setup.
module land / grid / cartesianC
subroutine, public prof_rapstart(rapname_base, level)
Start raptime.
Definition: scale_prof.F90:157
module FPM
Definition: scale_fpm.F90:10
subroutine, public atmos_vars_monitor
monitor output
subroutine, public admin_restart_write
Write data to restart files.
module ocean / grid / cartesianC / index
real(rp), dimension(:,:,:), allocatable, public atmos_grid_cartesc_real_cz
geopotential height [m] (zxy)
subroutine, public comm_cleanup
subroutine, public monitor_finalize
Close file.
module profiler
Definition: scale_prof.F90:11
logical, public atmos_restart_check
Check value consistency?
module Surface bulk flux
subroutine, public urban_grid_cartesc_index_setup
Setup.
subroutine, public atmos_hydrometeor_setup
Setup.
module atmosphere / thermodyn
subroutine, public admin_time_advance
Advance the time & evaluate restart & stop.
module Atmosphere GRID CartesC Real(real space)
subroutine, public atmos_driver_finalize
Finalize.
subroutine, public cpl_admin_setup
Setup.
real(rp), dimension(:,:), allocatable, public atmos_grid_cartesc_real_area
horizontal area ( xy, normal z) [m2]
subroutine, public atmos_vars_history_setpres
Set pressure for history output.
logical, public time_doatmos_step
execute atmosphere component in this step?
module PRECISION
module file / cartesianC
subroutine, public ocean_driver_calc_tendency(force)
Calculate tendency.
subroutine, public io_log_setup(myrank, is_master)
Setup LOG.
Definition: scale_io.F90:142
subroutine, public atmos_admin_setup
Setup.
integer, public ka
of whole cells: z, local, with HALO
subroutine, public ocean_vars_setup
Setup.
module TOPOGRAPHY
subroutine, public land_vars_history
History output set for land variables.
module urban / grid / cartesianC / real
module ADMIN TIME
module CALENDAR
module file / history_cartesC
module Statistics
integer, dimension(6), public time_nowdate
current time [YYYY MM DD HH MM SS]
Definition: scale_time.F90:69
subroutine, public comm_setup
Setup.
subroutine, public admin_versioncheck
Setup.
module STDIO
Definition: scale_io.F90:10
subroutine, public urban_admin_setup
Setup.
subroutine, public user_setup
Setup before setup of other components.
Definition: mod_user.F90:83
subroutine, public bulkflux_setup(dx)
subroutine, public atmos_vars_history
History output set for atmospheric variables.
module RANDOM
module Coupler admin
subroutine, public prof_rapend(rapname_base, level)
Save raptime.
Definition: scale_prof.F90:210
subroutine, public atmos_vars_restart_check
Check and compare between last data and sample data.
integer, public io_fid_log
Log file ID.
Definition: scale_io.F90:56
module Urban admin
logical, public urban_do
real(rp), dimension(:), allocatable, public atmos_grid_cartesc_cz
center coordinate [m]: z, local
module LAND driver
subroutine, public atmos_driver_update
advance atmospheric state
real(rp), dimension(:,:,:), allocatable, target, public pres
logical, public time_doland_step
execute land component in this step?
subroutine, public ocean_grid_cartesc_setup
Setup.
subroutine, public land_surface_set(countup)
Put surface boundary to other model.
subroutine, public user_update
User step.
Definition: mod_user.F90:134
module OCEAN Variables
logical, public land_do
subroutine, public atmos_hydrostatic_setup
Setup.
subroutine, public admin_restart_read
Read from restart files.
module ocean / grid / cartesianC
module file_history
subroutine, public admin_time_checkstate
Evaluate component execution.
subroutine, public prof_rapreport
Report raptime.
Definition: scale_prof.F90:258
subroutine, public file_history_set_nowdate(NOWDATE, NOWMS, NOWSTEP)
set now step