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

module MONITOR More...

Functions/Subroutines

subroutine, public monit_setup
 Setup. More...
 
subroutine, public monit_reg (itemid, item, desc, unit, ndim, isflux)
 Search existing item, or matching check between requested and registered item. More...
 
subroutine monit_put_3d (itemid, var)
 Put total value to the monitor buffer. More...
 
subroutine monit_in_2d (var, item, desc, unit, ndim, isflux)
 Wrapper routine of MONIT_reg+MONIT_put. More...
 
subroutine, public monit_write (memo)
 Flush monitor buffer to formatted file. More...
 
subroutine, public monit_finalize
 Close file. More...
 

Detailed Description

module MONITOR

Description
Monitor output module
Author
Team SCALE
History
  • 2012-03-22 (H.Yashiro) [new]
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

  • MONITITEM
    nametypedefault valuecomment
    ITEM character(len=*) name of the item

History Output
No history output

Function/Subroutine Documentation

◆ monit_setup()

subroutine, public scale_monitor::monit_setup ( )

Setup.

Definition at line 89 of file scale_monitor.F90.

References scale_stdio::io_fid_conf, scale_stdio::io_fid_log, scale_stdio::io_fid_nml, scale_stdio::io_l, scale_stdio::io_nml, and scale_process::prc_mpistop().

Referenced by mod_rm_driver::scalerm().

89  use scale_process, only: &
91  implicit none
92 
93  namelist / param_monitor / &
94  monitor_out_basename, &
95  monitor_usedevation, &
96  monitor_step_interval
97 
98  character(len=H_SHORT) :: ITEM
99 
100  namelist / monititem / &
101  item
102 
103  integer :: ierr
104  integer :: n
105  !---------------------------------------------------------------------------
106 
107  if( io_l ) write(io_fid_log,*)
108  if( io_l ) write(io_fid_log,*) '++++++ Module[MONITOR] / Categ[IO] / Origin[SCALElib]'
109 
110  !--- read namelist
111  rewind(io_fid_conf)
112  read(io_fid_conf,nml=param_monitor,iostat=ierr)
113  if( ierr < 0 ) then !--- missing
114  if( io_l ) write(io_fid_log,*) '*** Not found namelist. Default used.'
115  elseif( ierr > 0 ) then !--- fatal error
116  write(*,*) 'xxx Not appropriate names in namelist PARAM_MONITOR. Check!'
117  call prc_mpistop
118  endif
119  if( io_nml ) write(io_fid_nml,nml=param_monitor)
120 
121  ! listup monitor request
122  rewind(io_fid_conf)
123  do n = 1, monit_req_limit
124  read(io_fid_conf,nml=monititem,iostat=ierr)
125  if( ierr /= 0 ) exit
126  enddo
127  monit_req_nmax = n - 1
128 
129  if( io_l ) write(io_fid_log,*)
130  if ( monit_req_nmax > monit_req_limit ) then
131  if( io_l ) write(io_fid_log,*) '*** request of monitor file is exceed! n >', monit_req_limit
132  elseif( monit_req_nmax == 0 ) then
133  if( io_l ) write(io_fid_log,*) '*** No monitor file specified.'
134  return
135  else
136  if( io_l ) write(io_fid_log,*) '*** Number of requested monitor item: ', monit_req_nmax
137  if( io_l ) write(io_fid_log,*) '*** Monitor output interval [step] : ', monitor_step_interval
138  if( io_l ) write(io_fid_log,*) '*** Use deviation from first step? : ', monitor_usedevation
139  endif
140 
141  allocate( monit_item(monit_req_nmax) )
142  allocate( monit_desc(monit_req_nmax) )
143  allocate( monit_unit(monit_req_nmax) )
144  allocate( monit_ktype(monit_req_nmax) )
145  allocate( monit_kmax(monit_req_nmax) )
146  allocate( monit_var(monit_req_nmax) )
147  allocate( monit_var0(monit_req_nmax) )
148  allocate( monit_first(monit_req_nmax) )
149  allocate( monit_flux(monit_req_nmax) )
150 
151  rewind(io_fid_conf)
152  do n = 1, monit_req_nmax
153  ! set default
154  item = 'unknown'
155 
156  read(io_fid_conf,nml=monititem,iostat=ierr)
157  if( ierr /= 0 ) exit
158 
159  if( io_nml .AND. io_fid_nml /= io_fid_log ) write(io_fid_nml,nml=monititem)
160 
161  monit_req_item(n) = item
162  enddo
163 
164  return
subroutine, public prc_mpistop
Abort MPI.
module PROCESS
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
Here is the call graph for this function:
Here is the caller graph for this function:

◆ monit_reg()

subroutine, public scale_monitor::monit_reg ( integer, intent(out)  itemid,
character(len=*), intent(in)  item,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  unit,
integer, intent(in)  ndim,
logical, intent(in)  isflux 
)

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

Parameters
[out]itemidindex number of the item
[in]itemname of the item
[in]descdescription of the item
[in]unitunit of the item
[in]ndimdimension of the item
[in]isfluxneed to integrate value?

Definition at line 176 of file scale_monitor.F90.

References scale_stdio::io_fid_log, scale_stdio::io_l, scale_grid_index::kmax, and scale_time::time_dtsec.

Referenced by mod_atmos_vars::atmos_vars_setup(), and monit_in_2d().

176  implicit none
177 
178  integer, intent(out) :: itemid
179  character(len=*), intent(in) :: item
180  character(len=*), intent(in) :: desc
181  character(len=*), intent(in) :: unit
182  integer, intent(in) :: ndim
183  logical, intent(in) :: isflux
184 
185  character(len=8) :: lname
186 
187  integer :: n, nmax, reqid
188  !---------------------------------------------------------------------------
189 
190  !--- search existing item
191  itemid = -1
192  nmax = min( monit_id_count, monit_req_nmax )
193  do n = 1, nmax
194  if ( item == monit_item(n) ) then ! match existing item
195  itemid = n
196  return
197  endif
198  enddo
199 
200  if ( itemid < 0 ) then ! request-register matching check
201  do n = 1, monit_req_nmax
202  if ( item == monit_req_item(n) ) then
203  monit_id_count = monit_id_count + 1
204  itemid = monit_id_count
205  reqid = n
206 
207  ! new file registration
208  monit_item(itemid) = trim(item)
209  monit_desc(itemid) = trim(desc)
210  monit_unit(itemid) = trim(unit)
211  if ( ndim == 2 ) then
212  monit_ktype(itemid) = 'ZSFC'
213  monit_kmax(itemid) = 1
214  elseif( ndim == 3 ) then
215  write(lname,'(A,I4.4)') 'ZDEF', kmax
216  monit_ktype(itemid) = lname
217  monit_kmax(itemid) = kmax
218  endif
219  monit_var(itemid) = 0.0_rp
220  monit_var0(itemid) = 0.0_rp
221  monit_first(itemid) = .true.
222  monit_flux(itemid) = isflux
223 
224  if( io_l ) write(io_fid_log,*)
225  if( io_l ) write(io_fid_log,'(1x,A,I3)') ' *** [MONIT] Item registration No.= ', itemid
226  if( io_l ) write(io_fid_log,*) ' ] Name : ', trim(monit_item(itemid))
227  if( io_l ) write(io_fid_log,*) ' ] Description : ', trim(monit_desc(itemid))
228  if( io_l ) write(io_fid_log,*) ' ] Unit : ', trim(monit_unit(itemid))
229  if( io_l ) write(io_fid_log,*) ' ] Vert. type : ', trim(monit_ktype(itemid))
230  if( io_l ) write(io_fid_log,*) ' ] # of layer : ', monit_kmax(itemid)
231  if( io_l ) write(io_fid_log,*) ' ] Integ. with dt? : ', monit_flux(itemid)
232  endif
233  enddo
234  endif
235 
236  return
Here is the caller graph for this function:

◆ monit_put_3d()

subroutine scale_monitor::monit_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 289 of file scale_monitor.F90.

References scale_time::time_dtsec.

289  use scale_time, only: &
290  dt => time_dtsec
291  use scale_rm_statistics, only: &
292  stat_total
293  implicit none
294 
295  integer, intent(in) :: itemid
296  real(RP), intent(in) :: var(:,:,:)
297 
298  real(RP) :: total
299  !---------------------------------------------------------------------------
300 
301  if( itemid <= 0 ) return
302 
303  call stat_total( total, var(:,:,:), monit_item(itemid) )
304 
305  if ( monit_flux(itemid) ) then
306  if ( monit_first(itemid) ) then
307  monit_var(itemid) = total * dt ! first put
308  monit_first(itemid) = .false.
309  else
310  monit_var(itemid) = monit_var(itemid) + total * dt ! integrate by last put
311  endif
312  else
313  if ( monitor_usedevation ) then
314  if ( monit_first(itemid) ) then
315  monit_var(itemid) = 0.0_rp
316  monit_var0(itemid) = total
317  monit_first(itemid) = .false.
318  else
319  monit_var(itemid) = total - monit_var0(itemid) ! overwrite by last put
320  endif
321  else
322  monit_var(itemid) = total ! overwrite by last put
323  endif
324  endif
325 
326  return
module Statistics
real(dp), public time_dtsec
time interval of model [sec]
Definition: scale_time.F90:36
module TIME
Definition: scale_time.F90:15

◆ monit_in_2d()

subroutine scale_monitor::monit_in_2d ( real(rp), dimension(:,:), intent(in)  var,
character(len=*), intent(in)  item,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  unit,
integer, intent(in)  ndim,
logical, intent(in)  isflux 
)

Wrapper routine of MONIT_reg+MONIT_put.

Parameters
[in]varvalue
[in]itemname of the item
[in]descdescription of the item
[in]unitunit of the item
[in]ndimdimension of the item
[in]isfluxneed to integrate values?

Definition at line 338 of file scale_monitor.F90.

References monit_reg().

338  implicit none
339 
340  real(RP), intent(in) :: var(:,:)
341  character(len=*), intent(in) :: item
342  character(len=*), intent(in) :: desc
343  character(len=*), intent(in) :: unit
344  integer, intent(in) :: ndim
345  logical, intent(in) :: isflux
346 
347  integer :: itemid
348  !---------------------------------------------------------------------------
349 
350  call monit_reg( itemid, item, desc, unit, ndim, isflux )
351  call monit_put( itemid, var(:,:) )
352 
353  return
Here is the call graph for this function:

◆ monit_write()

subroutine, public scale_monitor::monit_write ( character(len=*), intent(in)  memo)

Flush monitor buffer to formatted file.

Parameters
[in]memonote

Definition at line 386 of file scale_monitor.F90.

References scale_stdio::io_fid_log, scale_stdio::io_get_available_fid(), scale_stdio::io_l, scale_stdio::io_log_allnode, scale_stdio::io_make_idstr(), scale_process::prc_ismaster, scale_process::prc_mpistop(), scale_process::prc_myrank, scale_prof::prof_rapend(), scale_prof::prof_rapstart(), and scale_time::time_nowstep.

Referenced by mod_rm_driver::scalerm().

386  use scale_time, only: &
387  nowstep => time_nowstep
388  implicit none
389 
390  character(len=*), intent(in) :: memo
391 
392  logical, save :: firsttime = .true.
393 
394  integer :: n
395  !---------------------------------------------------------------------------
396 
397  if( monit_id_count == 0 ) return
398 
399  call prof_rapstart('FILE_O_ASCII', 2)
400 
401  if (firsttime) then
402  firsttime = .false.
403  call monit_writeheader
404  endif
405 
406  if ( monit_fid > 0 ) then
407 
408  if ( mod(nowstep-1,monitor_step_interval) == 0 ) then
409  if( io_l ) write(io_fid_log,*) '*** Output Monitor'
410 
411  write(monit_fid,'(A,i7,A,A4,A)',advance='no') 'STEP=',nowstep,' (',memo,')'
412  do n = 1, monit_id_count
413  write(monit_fid,'(A,ES15.8)',advance='no') ' ',monit_var(n)
414  enddo
415  write(monit_fid,*)
416  endif
417 
418  endif
419 
420  call prof_rapend ('FILE_O_ASCII', 2)
421 
422  return
integer, public time_nowstep
current step [number]
Definition: scale_time.F90:70
module TIME
Definition: scale_time.F90:15
Here is the call graph for this function:
Here is the caller graph for this function:

◆ monit_finalize()

subroutine, public scale_monitor::monit_finalize ( )

Close file.

Definition at line 491 of file scale_monitor.F90.

References scale_stdio::io_fid_log, scale_stdio::io_l, scale_stdio::io_make_idstr(), and scale_process::prc_myrank.

Referenced by mod_rm_driver::scalerm().

491  use scale_process, only: &
492  prc_myrank
493  implicit none
494 
495  character(len=H_LONG) :: fname
496  !---------------------------------------------------------------------------
497 
498  if ( monit_fid > 0 ) then
499  call io_make_idstr(fname,trim(monitor_out_basename),'pe',prc_myrank)
500 
501  if( io_l ) write(io_fid_log,*)
502  if( io_l ) write(io_fid_log,*) '*** Close ASCII file for monitor, name : ', trim(fname)
503 
504  close(monit_fid)
505  endif
506 
507  return
module PROCESS
integer, public prc_myrank
process num in local communicator
Here is the call graph for this function:
Here is the caller graph for this function: