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, isflux)
 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, isflux)
 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_USEDEVATION logical .true. use deviation from first step?
    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 104 of file scale_monitor.F90.

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().

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

Referenced by scale_monitor_cartesc::monitor_cartesc_setup().

188  integer, intent(in) :: ka, ks, ke
189  integer, intent(in) :: ia, is, ie
190  integer, intent(in) :: ja, js, je
191 
192  character(len=*), intent(in) :: dim_type
193  integer, intent(in) :: dim_size
194  real(RP), intent(in), optional :: area(ia,ja)
195  real(RP), intent(in), optional :: total_area
196  real(RP), intent(in), optional :: volume(ka,ia,ja)
197  real(RP), intent(in), optional :: total_volume
198 
199  integer :: n
200 
201  monitor_ndims = monitor_ndims + 1
202  n = monitor_ndims
203 
204  monitor_dims(n)%name = dim_type
205  monitor_dims(n)%dim_size = dim_size
206 
207  monitor_dims(n)%KA = ka
208  monitor_dims(n)%KS = ks
209  monitor_dims(n)%KE = ke
210  monitor_dims(n)%IA = ia
211  monitor_dims(n)%IS = is
212  monitor_dims(n)%IE = ie
213  monitor_dims(n)%JA = ja
214  monitor_dims(n)%JS = js
215  monitor_dims(n)%JE = je
216 
217  if ( dim_size >= 2 ) then
218  allocate( monitor_dims(n)%area(ia,ja) )
219  monitor_dims(n)%area(:,:) = area(:,:)
220  monitor_dims(n)%total_area = total_area
221  end if
222 
223  if ( dim_size >= 3 ) then
224  allocate( monitor_dims(n)%volume(ka,ia,ja) )
225  monitor_dims(n)%volume(:,:,:) = volume(:,:,:)
226  monitor_dims(n)%total_volume = total_volume
227  end if
228 
229  return
integer, public ia
of whole cells: x, local, with HALO
integer, public ja
of whole cells: y, local, with HALO
integer, public is
start point of inner domain: x, local
integer, public ie
end point of inner domain: x, local
integer, public ke
end point of inner domain: z, local
integer, public je
end point of inner domain: y, local
integer, public ks
start point of inner domain: z, local
integer, public js
start point of inner domain: y, local
integer, public ka
of whole cells: z, local, with HALO
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  isflux 
)

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]isfluxneed to integrate value?

Definition at line 239 of file scale_monitor.F90.

References scale_prc::prc_abort().

Referenced by mod_atmos_phy_mp_driver::atmos_phy_mp_driver_setup(), mod_atmos_vars::atmos_vars_setup(), and monitor_in_2d().

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

340  use scale_statistics, only: &
341  statistics_total
342  implicit none
343  integer, intent(in) :: itemid
344  real(RP), intent(in) :: var(:,:)
345 
346  integer :: dimid
347  real(DP) :: total
348  !---------------------------------------------------------------------------
349 
350  if( itemid <= 0 ) return
351 
352  dimid = monitor_items(itemid)%dimid
353 
354  call statistics_total( monitor_dims(dimid)%IA, monitor_dims(dimid)%IS, monitor_dims(dimid)%IE, &
355  monitor_dims(dimid)%JA, monitor_dims(dimid)%JS, monitor_dims(dimid)%JE, &
356  var(:,:), monitor_items(itemid)%name, & ! (in)
357  monitor_dims(dimid)%area(:,:), monitor_dims(dimid)%total_area, & ! (in)
358  log_suppress = .true., & ! (in)
359  sum = total ) ! (out)
360 
361  if ( monitor_items(itemid)%flux ) then
362  if ( monitor_items(itemid)%first ) then
363  monitor_items(itemid)%var = total * monitor_dt ! first put
364  monitor_items(itemid)%first = .false.
365  else
366  monitor_items(itemid)%var = monitor_items(itemid)%var + total * monitor_dt ! integrate by last put
367  endif
368  else
369  if ( monitor_usedevation ) then
370  if ( monitor_items(itemid)%first ) then
371  monitor_items(itemid)%var = 0.0_rp
372  monitor_items(itemid)%var0 = total
373  monitor_items(itemid)%first = .false.
374  else
375  monitor_items(itemid)%var = total - monitor_items(itemid)%var0 ! overwrite by last put
376  endif
377  else
378  monitor_items(itemid)%var = total ! overwrite by last put
379  endif
380  endif
381 
382  return
module Statistics

◆ 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 389 of file scale_monitor.F90.

389  use scale_statistics, only: &
390  statistics_total
391  implicit none
392 
393  integer, intent(in) :: itemid
394  real(RP), intent(in) :: var(:,:,:)
395 
396  integer :: dimid
397 
398  real(DP) :: total
399  !---------------------------------------------------------------------------
400 
401  if( itemid <= 0 ) return
402 
403  dimid = monitor_items(itemid)%dimid
404 
405 
406  call statistics_total( monitor_dims(dimid)%KA, monitor_dims(dimid)%KS, monitor_dims(dimid)%KE, &
407  monitor_dims(dimid)%IA, monitor_dims(dimid)%IS, monitor_dims(dimid)%IE, &
408  monitor_dims(dimid)%JA, monitor_dims(dimid)%JS, monitor_dims(dimid)%JE, &
409  var(:,:,:), monitor_items(itemid)%name, & ! (in)
410  monitor_dims(dimid)%volume(:,:,:), monitor_dims(dimid)%total_volume, & ! (in)
411  log_suppress = .true., & ! (in)
412  sum = total ) ! (out)
413 
414  if ( monitor_items(itemid)%flux ) then
415  if ( monitor_items(itemid)%first ) then
416  monitor_items(itemid)%var = total * monitor_dt ! first put
417  monitor_items(itemid)%first = .false.
418  else
419  monitor_items(itemid)%var = monitor_items(itemid)%var + total * monitor_dt ! integrate by last put
420  endif
421  else
422  if ( monitor_usedevation ) then
423  if ( monitor_items(itemid)%first ) then
424  monitor_items(itemid)%var = 0.0_rp
425  monitor_items(itemid)%var0 = total
426  monitor_items(itemid)%first = .false.
427  else
428  monitor_items(itemid)%var = total - monitor_items(itemid)%var0 ! overwrite by last put
429  endif
430  else
431  monitor_items(itemid)%var = total ! overwrite by last put
432  endif
433  endif
434 
435  return
module Statistics

◆ 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  isflux 
)

Wrapper routine of MONITOR_reg+MONITOR_put.

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

Definition at line 445 of file scale_monitor.F90.

References monitor_reg().

445  implicit none
446 
447  real(RP), intent(in) :: var(:,:)
448  character(len=*), intent(in) :: name
449  character(len=*), intent(in) :: desc
450  character(len=*), intent(in) :: unit
451 
452  integer, intent(in), optional :: ndims
453  character(len=*), intent(in), optional :: dim_type
454  logical, intent(in), optional :: isflux
455 
456  integer :: itemid
457  !---------------------------------------------------------------------------
458 
459  call monitor_reg( name, desc, unit, & ! (in)
460  itemid, & ! (out)
461  ndims=ndims, dim_type=dim_type, & ! (in)
462  isflux=isflux ) ! (in)
463  call monitor_put( itemid, var(:,:) )
464 
465  return
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 501 of file scale_monitor.F90.

References scale_io::io_get_available_fid(), scale_io::io_log_allnode, scale_io::io_make_idstr(), 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().

501  implicit none
502  character(len=*), intent(in) :: memo
503  integer , intent(in) :: nowstep
504 
505  logical, save :: firsttime = .true.
506 
507  integer :: n
508  !---------------------------------------------------------------------------
509 
510  if( monitor_nitems == 0 ) return
511 
512  call prof_rapstart('FILE_O_ASCII', 2)
513 
514  if (firsttime) then
515  firsttime = .false.
516  call monitor_writeheader
517  endif
518 
519  if ( monitor_fid > 0 ) then
520 
521  if ( mod(nowstep-1,monitor_step_interval) == 0 ) then
522  log_progress(*) 'output monitor'
523 
524  write(monitor_fid,'(A,i7,A,A4,A)',advance='no') 'STEP=',nowstep,' (',memo,')'
525  do n = 1, monitor_nitems
526  write(monitor_fid,'(A,ES15.8)',advance='no') ' ', monitor_items(n)%var
527  enddo
528  write(monitor_fid,*)
529  endif
530 
531  endif
532 
533  call prof_rapend ('FILE_O_ASCII', 2)
534 
535  return
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 604 of file scale_monitor.F90.

References scale_io::io_make_idstr(), and scale_prc::prc_myrank.

Referenced by mod_rm_driver::rm_driver().

604  use scale_prc, only: &
605  prc_myrank
606  implicit none
607 
608  character(len=H_LONG) :: fname
609 
610  integer :: n
611  !---------------------------------------------------------------------------
612 
613  if ( monitor_fid > 0 ) then
614  call io_make_idstr(fname,trim(monitor_out_basename),'pe',prc_myrank)
615 
616  log_newline
617  log_info('MONITOR_finalize',*) 'Close ASCII file for monitor, name : ', trim(fname)
618 
619  close(monitor_fid)
620  endif
621 
622  do n = 1, monitor_ndims
623  if ( monitor_dims(n)%dim_size >= 2 ) deallocate( monitor_dims(n)%area )
624  if ( monitor_dims(n)%dim_size >= 3 ) deallocate( monitor_dims(n)%volume )
625  end do
626  monitor_ndims = 0
627 
628  if ( allocated(monitor_items) ) deallocate( monitor_items )
629  monitor_nitems = 0
630 
631  return
module PROCESS
Definition: scale_prc.F90:11
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:89
subroutine, public io_make_idstr(outstr, instr, ext, rank, isrgn)
generate process specific filename
Definition: scale_io.F90:334
Here is the call graph for this function:
Here is the caller graph for this function: