SCALE-RM
Data Types | Functions/Subroutines
scale_monitor Module Reference

module MONITOR More...

Functions/Subroutines

subroutine, public monitor_setup (dt)
 Setup. More...
 
subroutine, public monitor_set_dim (KA, KS, KE, IA, IS, IE, JA, JS, JE, dim_type, dim_size, area, total_area, volume, total_volume)
 Set area and volume. More...
 
subroutine, public monitor_reg (name, desc, unit, itemid, ndims, dim_type, is_tendency)
 Search existing item, or matching check between requested and registered item. More...
 
subroutine monitor_put_2d (itemid, var)
 Put total value to the monitor buffer. More...
 
subroutine monitor_put_3d (itemid, var)
 Put total value to the monitor buffer. More...
 
subroutine monitor_in_2d (var, name, desc, unit, ndims, dim_type, is_tendency)
 Wrapper routine of MONITOR_reg+MONITOR_put. More...
 
subroutine, public monitor_write (memo, nowstep)
 Flush monitor buffer to formatted file. More...
 
subroutine, public monitor_finalize
 Close file. More...
 

Detailed Description

module MONITOR

Description
Monitor output module
Author
Team SCALE
NAMELIST
  • PARAM_MONITOR
    nametypedefault valuecomment
    MONITOR_OUT_BASENAME character(len=H_LONG) 'monitor' filename of monitor output
    MONITOR_USEDEVIATION logical .true. use deviation from first step?
    MONITOR_GLOBAL_SUM logical .true. global or local sum
    MONITOR_STEP_INTERVAL integer 1 step interval

  • MONITOR_ITEM
    nametypedefault valuecomment
    NAME character(len=*) name

History Output
No history output

Function/Subroutine Documentation

◆ monitor_setup()

subroutine, public scale_monitor::monitor_setup ( real(dp), intent(in)  dt)

Setup.

Definition at line 105 of file scale_monitor.F90.

105  use scale_prc, only: &
106  prc_abort
107  implicit none
108 
109  real(DP), intent(in) :: dt
110 
111  namelist / param_monitor / &
112  monitor_out_basename, &
113  monitor_usedeviation, &
114  monitor_global_sum, &
115  monitor_step_interval
116 
117  character(len=H_SHORT) :: NAME
118 
119  namelist / monitor_item / &
120  name
121 
122  integer :: ierr
123  integer :: n
124  !---------------------------------------------------------------------------
125 
126  log_newline
127  log_info("MONITOR_setup",*) 'Setup'
128 
129  !--- read namelist
130  rewind(io_fid_conf)
131  read(io_fid_conf,nml=param_monitor,iostat=ierr)
132  if( ierr < 0 ) then !--- missing
133  log_info('MONITOR_setup',*) 'Not found namelist. Default used.'
134  elseif( ierr > 0 ) then !--- fatal error
135  log_error('MONITOR_setup',*) 'Not appropriate names in namelist PARAM_MONITOR. Check!'
136  call prc_abort
137  endif
138  log_nml(param_monitor)
139 
140  ! listup monitor request
141  rewind(io_fid_conf)
142  do n = 1, monitor_req_max
143  read(io_fid_conf,nml=monitor_item,iostat=ierr)
144  if( ierr /= 0 ) exit
145  enddo
146  monitor_nreqs = n - 1
147 
148  if ( monitor_nreqs > monitor_req_max ) then
149  log_error('MONITOR_setup',*) 'request of monitor file is exceed! n >', monitor_req_max
150  call prc_abort
151  elseif( monitor_nreqs == 0 ) then
152  log_info('MONITOR_setup',*) 'No monitor file specified.'
153  return
154  else
155  log_info('MONITOR_setup',*) 'Number of requested monitor item : ', monitor_nreqs
156  log_info('MONITOR_setup',*) 'Monitor output interval [step] : ', monitor_step_interval
157  log_info('MONITOR_setup',*) 'Use deviation from first step? : ', monitor_usedeviation
158  endif
159 
160  allocate( monitor_items(monitor_nreqs) )
161 
162  rewind(io_fid_conf)
163  do n = 1, monitor_nreqs
164  ! set default
165  name = 'unknown'
166 
167  read(io_fid_conf,nml=monitor_item,iostat=ierr)
168  if( ierr /= 0 ) exit
169 
170  if ( io_fid_nml /= io_fid_log ) then
171  log_nml(monitor_item)
172  end if
173 
174  monitor_reqs(n) = name
175  enddo
176 
177 
178  monitor_dt = dt
179 
180  return

References scale_io::io_fid_conf, scale_io::io_fid_log, scale_io::io_fid_nml, and scale_prc::prc_abort().

Referenced by scale_monitor_cartesc::monitor_cartesc_setup().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ monitor_set_dim()

subroutine, public scale_monitor::monitor_set_dim ( integer, intent(in)  KA,
integer, intent(in)  KS,
integer, intent(in)  KE,
integer, intent(in)  IA,
integer, intent(in)  IS,
integer, intent(in)  IE,
integer, intent(in)  JA,
integer, intent(in)  JS,
integer, intent(in)  JE,
character(len=*), intent(in)  dim_type,
integer, intent(in)  dim_size,
real(rp), dimension(ia,ja), intent(in), optional  area,
real(rp), intent(in), optional  total_area,
real(rp), dimension(ka,ia,ja), intent(in), optional  volume,
real(rp), intent(in), optional  total_volume 
)

Set area and volume.

Definition at line 190 of file scale_monitor.F90.

190  integer, intent(in) :: KA, KS, KE
191  integer, intent(in) :: IA, IS, IE
192  integer, intent(in) :: JA, JS, JE
193 
194  character(len=*), intent(in) :: dim_type
195  integer, intent(in) :: dim_size
196  real(RP), intent(in), optional :: area(IA,JA)
197  real(RP), intent(in), optional :: total_area
198  real(RP), intent(in), optional :: volume(KA,IA,JA)
199  real(RP), intent(in), optional :: total_volume
200 
201  integer :: n
202 
203  monitor_ndims = monitor_ndims + 1
204  n = monitor_ndims
205 
206  monitor_dims(n)%name = dim_type
207  monitor_dims(n)%dim_size = dim_size
208 
209  monitor_dims(n)%KA = ka
210  monitor_dims(n)%KS = ks
211  monitor_dims(n)%KE = ke
212  monitor_dims(n)%IA = ia
213  monitor_dims(n)%IS = is
214  monitor_dims(n)%IE = ie
215  monitor_dims(n)%JA = ja
216  monitor_dims(n)%JS = js
217  monitor_dims(n)%JE = je
218 
219  if ( dim_size >= 2 ) then
220  allocate( monitor_dims(n)%area(ia,ja) )
221  monitor_dims(n)%area(:,:) = area(:,:)
222  !$acc enter data copyin(MONITOR_dims(n)%area)
223  monitor_dims(n)%total_area = total_area
224  end if
225 
226  if ( dim_size >= 3 ) then
227  allocate( monitor_dims(n)%volume(ka,ia,ja) )
228  monitor_dims(n)%volume(:,:,:) = volume(:,:,:)
229  !$acc enter data copyin(MONITOR_dims(n)%volume)
230  monitor_dims(n)%total_volume = total_volume
231  end if
232 
233  return

Referenced by scale_monitor_cartesc::monitor_cartesc_setup().

Here is the caller graph for this function:

◆ monitor_reg()

subroutine, public scale_monitor::monitor_reg ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  unit,
integer, intent(out)  itemid,
integer, intent(in), optional  ndims,
character(len=*), intent(in), optional  dim_type,
logical, intent(in), optional  is_tendency 
)

Search existing item, or matching check between requested and registered item.

Parameters
[in]namename of the item
[in]descdescription of the item
[in]unitunit of the item
[out]itemidindex number of the item
[in]ndims# of dimension
[in]dim_typedimension type
[in]is_tendencyneed to integrate value?

Definition at line 243 of file scale_monitor.F90.

243  use scale_prc, only: &
244  prc_abort
245  implicit none
246 
247  character(len=*), intent(in) :: name
248  character(len=*), intent(in) :: desc
249  character(len=*), intent(in) :: unit
250 
251  integer, intent(out) :: itemid
252 
253  integer, intent(in), optional :: ndims
254  character(len=*), intent(in), optional :: dim_type
255  logical, intent(in), optional :: is_tendency
256 
257  integer :: n, reqid, dimid
258  !---------------------------------------------------------------------------
259 
260  !--- search existing item
261  do itemid = 1, monitor_nitems
262  if ( name == monitor_items(itemid)%name ) return ! match existing item
263  enddo
264 
265  do reqid = 1, monitor_nreqs
266  if ( name == monitor_reqs(reqid) ) then
267 
268  call prof_rapstart('Monit', 2)
269 
270  monitor_nitems = monitor_nitems + 1
271  itemid = monitor_nitems
272 
273  ! new file registration
274  monitor_items(itemid)%name = name
275  monitor_items(itemid)%desc = desc
276  monitor_items(itemid)%unit = unit
277 
278  dimid = -1
279  if ( present(dim_type) ) then
280  do n = 1, monitor_ndims
281  if ( monitor_dims(n)%name == dim_type ) then
282  dimid = n
283  exit
284  end if
285  end do
286  if ( dimid < 0 ) then
287  log_error('MONITOR_reg',*) 'dim_type (', trim(dim_type), ') must be registerd by MONITOR_set_dim'
288  call prc_abort
289  end if
290  else if ( present(ndims) ) then
291  do n = 1, monitor_ndims
292  if ( monitor_dims(n)%dim_size == ndims ) then
293  dimid = n
294  exit
295  end if
296  end do
297  if ( dimid == -1 ) then
298  log_error('MONITOR_reg','(a,i1,a)') 'dim_type of ', ndims, 'D must be registerd with MONITOR_set_dim'
299  call prc_abort
300  end if
301  else
302  ! ndims = 3 is assumed as default
303  do n = 1, monitor_ndims
304  if ( monitor_dims(n)%dim_size == 3 ) then
305  dimid = n
306  exit
307  end if
308  end do
309  if ( dimid == -1 ) then
310  log_error('MONITOR_reg',*) 'dim_type or ndims must be specified'
311  call prc_abort
312  end if
313  end if
314 
315  monitor_items(itemid)%dimid = dimid
316 
317  monitor_items(itemid)%var = 0.0_dp
318  monitor_items(itemid)%var0 = 0.0_dp
319  monitor_items(itemid)%first = .true.
320  if ( present(is_tendency) ) then
321  monitor_items(itemid)%tendency = is_tendency
322  else
323  monitor_items(itemid)%tendency = .false.
324  end if
325 
326  log_newline
327  log_info('MONOTOR_reg','(A,I3)') ' Item registration No.= ', itemid
328  log_info_cont(*) 'Name : ', trim(monitor_items(itemid)%name)
329  log_info_cont(*) 'Description : ', trim(monitor_items(itemid)%desc)
330  log_info_cont(*) 'Unit : ', trim(monitor_items(itemid)%unit)
331  log_info_cont(*) 'Dimension type : ', trim(monitor_dims(monitor_items(itemid)%dimid)%name)
332  log_info_cont(*) 'Integ. with dt? : ', monitor_items(itemid)%tendency
333 
334  call prof_rapend('Monit', 2)
335 
336  return
337  end if
338  end do
339 
340  itemid = -1 ! not found
341 
342  return

References scale_prc::prc_abort(), scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by scale_atmos_dyn_tstep_large_fvm_heve::atmos_dyn_tstep_large_fvm_heve_setup(), mod_atmos_phy_mp_driver::atmos_phy_mp_driver_setup(), mod_atmos_phy_tb_driver::atmos_phy_tb_driver_setup(), mod_atmos_vars::atmos_vars_setup(), mod_land_vars::land_vars_setup(), monitor_in_2d(), mod_ocean_vars::ocean_vars_setup(), and mod_urban_vars::urban_vars_setup().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ monitor_put_2d()

subroutine scale_monitor::monitor_put_2d ( integer, intent(in)  itemid,
real(rp), dimension(:,:), intent(in)  var 
)

Put total value to the monitor buffer.

Parameters
[in]itemidindex number of the item
[in]varvalue

Definition at line 349 of file scale_monitor.F90.

349  use scale_statistics, only: &
350  statistics_total
351  implicit none
352  integer, intent(in) :: itemid
353  real(RP), intent(in) :: var(:,:)
354 
355  integer :: dimid
356  real(DP) :: total
357  !---------------------------------------------------------------------------
358 
359  if( itemid <= 0 ) return
360 
361  call prof_rapstart('Monit', 2)
362 
363  dimid = monitor_items(itemid)%dimid
364 
365  call statistics_total( monitor_dims(dimid)%IA, monitor_dims(dimid)%IS, monitor_dims(dimid)%IE, &
366  monitor_dims(dimid)%JA, monitor_dims(dimid)%JS, monitor_dims(dimid)%JE, &
367  var(:,:), monitor_items(itemid)%name, & ! (in)
368  monitor_dims(dimid)%area(:,:), monitor_dims(dimid)%total_area, & ! (in)
369  log_suppress = .true., global = monitor_global_sum, & ! (in)
370  sum = total ) ! (out)
371 
372  if ( monitor_items(itemid)%tendency ) then
373  if ( monitor_items(itemid)%first ) then
374  monitor_items(itemid)%var = 0.0_rp
375  monitor_items(itemid)%first = .false.
376  else
377  monitor_items(itemid)%var = monitor_items(itemid)%var + total * monitor_dt ! integrate by last put
378  endif
379  else
380  if ( monitor_usedeviation ) then
381  if ( monitor_items(itemid)%first ) then
382  monitor_items(itemid)%var = 0.0_rp
383  monitor_items(itemid)%var0 = total
384  monitor_items(itemid)%first = .false.
385  else
386  monitor_items(itemid)%var = total - monitor_items(itemid)%var0 ! overwrite by last put
387  endif
388  else
389  monitor_items(itemid)%var = total ! overwrite by last put
390  endif
391  endif
392 
393  call prof_rapend('Monit', 2)
394 
395  return

References scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Here is the call graph for this function:

◆ monitor_put_3d()

subroutine scale_monitor::monitor_put_3d ( integer, intent(in)  itemid,
real(rp), dimension(:,:,:), intent(in)  var 
)

Put total value to the monitor buffer.

Parameters
[in]itemidindex number of the item
[in]varvalue

Definition at line 402 of file scale_monitor.F90.

402  use scale_statistics, only: &
403  statistics_total
404  implicit none
405 
406  integer, intent(in) :: itemid
407  real(RP), intent(in) :: var(:,:,:)
408 
409  integer :: dimid
410 
411  real(DP) :: total
412  !---------------------------------------------------------------------------
413 
414  if( itemid <= 0 ) return
415 
416  call prof_rapstart('Monit', 2)
417 
418  dimid = monitor_items(itemid)%dimid
419 
420 
421  call statistics_total( monitor_dims(dimid)%KA, monitor_dims(dimid)%KS, monitor_dims(dimid)%KE, &
422  monitor_dims(dimid)%IA, monitor_dims(dimid)%IS, monitor_dims(dimid)%IE, &
423  monitor_dims(dimid)%JA, monitor_dims(dimid)%JS, monitor_dims(dimid)%JE, &
424  var(:,:,:), monitor_items(itemid)%name, & ! (in)
425  monitor_dims(dimid)%volume(:,:,:), monitor_dims(dimid)%total_volume, & ! (in)
426  log_suppress = .true., global = monitor_global_sum, & ! (in)
427  sum = total ) ! (out)
428 
429  if ( monitor_items(itemid)%tendency ) then
430  if ( monitor_items(itemid)%first ) then
431  monitor_items(itemid)%var = total * monitor_dt ! first put
432  monitor_items(itemid)%first = .false.
433  else
434  monitor_items(itemid)%var = monitor_items(itemid)%var + total * monitor_dt ! integrate by last put
435  endif
436  else
437  if ( monitor_usedeviation ) then
438  if ( monitor_items(itemid)%first ) then
439  monitor_items(itemid)%var = 0.0_rp
440  monitor_items(itemid)%var0 = total
441  monitor_items(itemid)%first = .false.
442  else
443  monitor_items(itemid)%var = total - monitor_items(itemid)%var0 ! overwrite by last put
444  endif
445  else
446  monitor_items(itemid)%var = total ! overwrite by last put
447  endif
448  endif
449 
450  call prof_rapend('Monit', 2)
451 
452  return

References scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Here is the call graph for this function:

◆ monitor_in_2d()

subroutine scale_monitor::monitor_in_2d ( real(rp), dimension(:,:), intent(in)  var,
character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  unit,
integer, intent(in), optional  ndims,
character(len=*), intent(in), optional  dim_type,
logical, intent(in), optional  is_tendency 
)

Wrapper routine of MONITOR_reg+MONITOR_put.

Parameters
[in]varvalue
[in]descdescription
[in]ndims# of dimension
[in]dim_typedimension type
[in]is_tendencyneed to integrate values?

Definition at line 462 of file scale_monitor.F90.

462  implicit none
463 
464  real(RP), intent(in) :: var(:,:)
465  character(len=*), intent(in) :: name
466  character(len=*), intent(in) :: desc
467  character(len=*), intent(in) :: unit
468 
469  integer, intent(in), optional :: ndims
470  character(len=*), intent(in), optional :: dim_type
471  logical, intent(in), optional :: is_tendency
472 
473  integer :: itemid
474  !---------------------------------------------------------------------------
475 
476  call monitor_reg( name, desc, unit, & ! (in)
477  itemid, & ! (out)
478  ndims=ndims, dim_type=dim_type, & ! (in)
479  is_tendency=is_tendency ) ! (in)
480  call monitor_put( itemid, var(:,:) )
481 
482  return

References monitor_reg().

Here is the call graph for this function:

◆ monitor_write()

subroutine, public scale_monitor::monitor_write ( character(len=*), intent(in)  memo,
integer, intent(in)  nowstep 
)

Flush monitor buffer to formatted file.

Parameters
[in]memonote

Definition at line 518 of file scale_monitor.F90.

518  implicit none
519  character(len=*), intent(in) :: memo
520  integer , intent(in) :: nowstep
521 
522  logical, save :: firsttime = .true.
523 
524  integer :: n
525  !---------------------------------------------------------------------------
526 
527  if( monitor_nitems == 0 ) return
528 
529  call prof_rapstart('Monit', 2)
530 
531  if (firsttime) then
532  firsttime = .false.
533  call monitor_writeheader
534  endif
535 
536  if ( monitor_fid > 0 ) then
537 
538  if ( mod(nowstep-1,monitor_step_interval) == 0 ) then
539  log_progress(*) 'output monitor'
540 
541  write(monitor_fid,'(A,i7,A,A4,A)',advance='no') 'STEP=',nowstep,' (',memo,')'
542  do n = 1, monitor_nitems
543  write(monitor_fid,'(A,ES15.8)',advance='no') ' ', monitor_items(n)%var
544  enddo
545  write(monitor_fid,*)
546  endif
547 
548  endif
549 
550  call prof_rapend('Monit', 2)
551 
552  return

References scale_io::io_get_available_fid(), scale_io::io_get_fname(), scale_io::io_log_allnode, scale_prc::prc_abort(), scale_prc::prc_ismaster, scale_prc::prc_myrank, scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by mod_rm_driver::rm_driver().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ monitor_finalize()

subroutine, public scale_monitor::monitor_finalize

Close file.

Definition at line 625 of file scale_monitor.F90.

625  use scale_prc, only: &
626  prc_myrank
627  implicit none
628 
629  character(len=H_LONG) :: fname
630 
631  integer :: n
632  !---------------------------------------------------------------------------
633 
634  if ( monitor_fid > 0 ) then
635  log_newline
636  log_info('MONITOR_finalize',*) 'Close monitor file'
637 
638  close(monitor_fid)
639  endif
640 
641  do n = 1, monitor_ndims
642  if ( monitor_dims(n)%dim_size >= 2 ) then
643  !$acc exit data delete(MONITOR_dims(n)%area)
644  deallocate( monitor_dims(n)%area )
645  end if
646  if ( monitor_dims(n)%dim_size >= 3 ) then
647  !$acc exit data delete(MONITOR_dims(n)%volume)
648  deallocate( monitor_dims(n)%volume )
649  end if
650  end do
651  monitor_ndims = 0
652 
653  if ( allocated(monitor_items) ) deallocate( monitor_items )
654  monitor_nitems = 0
655 
656  return

References scale_prc::prc_myrank.

Referenced by mod_rm_driver::rm_driver().

Here is the caller graph for this function:
scale_statistics
module Statistics
Definition: scale_statistics.F90:11
scale_atmos_grid_cartesc_index::ke
integer, public ke
end point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:52
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:350
scale_atmos_grid_cartesc_index::ka
integer, public ka
Definition: scale_atmos_grid_cartesC_index.F90:47
scale_prc::prc_myrank
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:91
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_atmos_grid_cartesc_index::ie
integer, public ie
end point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:54
scale_atmos_grid_cartesc_index::ia
integer, public ia
Definition: scale_atmos_grid_cartesC_index.F90:48
scale_atmos_grid_cartesc_index::is
integer, public is
start point of inner domain: x, local
Definition: scale_atmos_grid_cartesC_index.F90:53
scale_atmos_grid_cartesc_index::ja
integer, public ja
Definition: scale_atmos_grid_cartesC_index.F90:49
scale_atmos_grid_cartesc_index::ks
integer, public ks
start point of inner domain: z, local
Definition: scale_atmos_grid_cartesC_index.F90:51
scale_atmos_grid_cartesc_index::js
integer, public js
start point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:55
scale_atmos_grid_cartesc_index::je
integer, public je
end point of inner domain: y, local
Definition: scale_atmos_grid_cartesC_index.F90:56