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

module Gtool_History More...

Functions/Subroutines

subroutine, public historyinit (title, source, institution, array_size, master, myrank, rankidx, time_start, time_interval, time_units, time_since, default_basename, default_tinterval, default_tunit, default_taverage, default_zinterp, default_datatype, namelist_filename, namelist_fid)
 
subroutine, public historyaddvariable (varname, dims, desc, units, now_step, id, zinterp, existed, options)
 
subroutine, public historywriteaxes
 
subroutine historyputaxissp (name, desc, units, dim, var, dtype, down)
 
subroutine historyputaxisdp (name, desc, units, dim, var, dtype, down)
 
subroutine historyput1dassociatedcoordinatessp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine historyput1dassociatedcoordinatesdp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine historyput2dassociatedcoordinatessp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine historyput2dassociatedcoordinatesdp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine historyput3dassociatedcoordinatessp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine historyput3dassociatedcoordinatesdp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine historyput4dassociatedcoordinatessp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine historyput4dassociatedcoordinatesdp (name, desc, units, dims, var, dtype)
 interface HistoryPutAssociatedCoordinates More...
 
subroutine, public historysettattr (varname, key, val)
 
subroutine, public historyquery (itemid, step_next, answer)
 
subroutine, public historywrite (itemid, step_now)
 
subroutine, public historywriteall (step_now)
 
subroutine historyget1dsp (var, basename, varname, step, allow_missing, single)
 
subroutine historyget2ddp (var, basename, varname, step, allow_missing, single)
 
subroutine historyget2dsp (var, basename, varname, step, allow_missing, single)
 
subroutine historyget3ddp (var, basename, varname, step, allow_missing, single)
 
subroutine historyget3dsp (var, basename, varname, step, allow_missing, single)
 
subroutine, public historyoutputlist
 
subroutine, public historyfinalize
 

Detailed Description

module Gtool_History

Description
module library for history output
Author
Team SCALE
History
  • 2012-06-11 (S.Nishizawa) [new] imported from SCALE-LES

Function/Subroutine Documentation

◆ historyinit()

subroutine, public gtool_history::historyinit ( character(len=*), intent(in)  title,
character(len=*), intent(in)  source,
character(len=*), intent(in)  institution,
integer, intent(in)  array_size,
integer, intent(in)  master,
integer, intent(in)  myrank,
integer, dimension(:), intent(in)  rankidx,
real(dp), intent(in)  time_start,
real(dp), intent(in)  time_interval,
character(len=*), intent(in), optional  time_units,
character(len=*), intent(in), optional  time_since,
character(len=*), intent(in), optional  default_basename,
real(dp), intent(in), optional  default_tinterval,
character(len=*), intent(in), optional  default_tunit,
logical, intent(in), optional  default_taverage,
logical, intent(in), optional  default_zinterp,
character(len=*), intent(in), optional  default_datatype,
character(len=*), intent(in), optional  namelist_filename,
integer, intent(in), optional  namelist_fid 
)

Definition at line 208 of file gtool_history.f90.

References gtool_file_h::file_preclist, gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

Referenced by scale_history::hist_setup().

208  use dc_calendar, only: &
209  calendarymdhms2sec
210  use gtool_file_h, only: &
211  file_real4, &
212  file_real8, &
214  implicit none
215 
216  character(len=*), intent(in) :: title
217  character(len=*), intent(in) :: source
218  character(len=*), intent(in) :: institution
219  integer, intent(in) :: array_size
220  integer, intent(in) :: master
221  integer, intent(in) :: myrank
222  integer, intent(in) :: rankidx(:)
223  real(DP), intent(in) :: time_start
224  real(DP), intent(in) :: time_interval
225  character(len=*), intent(in), optional :: time_units
226  character(len=*), intent(in), optional :: time_since
227  character(len=*), intent(in), optional :: default_basename
228  real(DP), intent(in), optional :: default_tinterval
229  character(len=*), intent(in), optional :: default_tunit
230  logical, intent(in), optional :: default_taverage
231  logical, intent(in), optional :: default_zinterp
232  character(len=*), intent(in), optional :: default_datatype
233  character(len=*), intent(in), optional :: namelist_filename
234  integer , intent(in), optional :: namelist_fid
235 
236  character(len=File_HLONG) :: history_default_basename = ''
237  real(DP) :: history_default_tinterval = 1.0_dp
238  character(len=File_HSHORT) :: history_default_tunit = 'sec'
239  logical :: history_default_taverage = .false.
240  logical :: history_default_zinterp = .false.
241  character(len=File_HSHORT) :: history_default_datatype = 'REAL4'
242 
243  namelist / param_history / &
244  history_title, &
245  history_source, &
246  history_institution, &
247  history_time_units, &
248  history_default_basename, &
249  history_default_tinterval, &
250  history_default_tunit, &
251  history_default_taverage, &
252  history_default_zinterp, &
253  history_default_datatype, &
254  history_output_step0, &
255  history_output_start, &
256  history_error_putmiss
257 
258  character(len=File_HLONG) :: basename
259  character(len=File_HSHORT) :: item
260  real(DP) :: tinterval
261  character(len=File_HSHORT) :: tunit
262  logical :: taverage
263  logical :: zinterp
264  character(len=File_HSHORT) :: datatype
265 
266  namelist / histitem / &
267  basename, &
268  item, &
269  tinterval, &
270  tunit, &
271  taverage, &
272  zinterp, &
273  datatype
274 
275  integer :: fid_conf
276 
277  integer :: ierr
278  integer :: n, ni
279  integer :: memsize
280 
281  intrinsic size
282  !---------------------------------------------------------------------------
283 
284  call log('I','')
285  call log('I','+++ Module[HISTORY]/Categ[IO]')
286 
287  !--- read namelist
288  history_title = title
289  history_source = source
290  history_institution = institution
291  history_startdaysec = time_start
292  history_dtsec = time_interval
293  if ( present(time_units) ) then
294  history_time_units = time_units
295  else
296  history_time_units = 'seconds'
297  endif
298  if ( present(time_since) ) then
299  history_time_since = time_since
300  else
301  history_time_since = ''
302  endif
303  if ( present(default_basename) ) then
304  history_default_basename = default_basename
305  endif
306  if ( present(default_tinterval) ) then
307  history_default_tinterval = default_tinterval
308  if ( present(default_tunit) ) then
309  history_default_tunit = default_tunit
310  endif
311  endif
312  if ( present(default_taverage) ) then
313  history_default_taverage = default_taverage
314  endif
315  if ( present(default_zinterp) ) then
316  history_default_zinterp = default_zinterp
317  endif
318  if ( present(default_datatype) ) then
319  history_default_datatype = default_datatype
320  endif
321 
322  if ( present(namelist_fid) ) then
323  fid_conf = namelist_fid
324  rewind(fid_conf)
325  elseif( present(namelist_filename) ) then
326  if ( namelist_filename /= '' ) then
327  open( fid_conf, file = trim(namelist_filename), &
328  form = 'formatted', status = 'old', iostat = ierr)
329  else
330  call log('I','*** Brank namelist file was specified. Default used. ***')
331  fid_conf = -1
332  endif
333  else
334  call log('I','*** No namelist was specified. Default used. ***')
335  fid_conf = -1
336  endif
337 
338  if ( fid_conf > 0 ) then
339  read(fid_conf, nml=param_history, iostat=ierr)
340 
341  if ( ierr < 0 ) then !--- missing
342  call log('I','*** Not found namelist. Default used.')
343  elseif( ierr > 0 ) then !--- fatal error
344  call log('E', 'xxx Not appropriate names in namelist PARAM_HISTORY. Check!')
345  endif
346 #if defined(__PGI) || defined(__ES2)
347  write(log_fid,nml=param_history)
348 #else
349  write(message,nml=param_history)
350  call log('I',message)
351 #endif
352  endif
353 
354  ! listup history request
355  history_req_nmax = 0
356  if ( fid_conf > 0 ) then
357  rewind( fid_conf )
358  do n = 1, history_req_limit
359  basename = history_default_basename
360  read(fid_conf, nml=histitem, iostat=ierr)
361  if( ierr /= 0 ) exit
362  if( basename /= "" ) history_req_nmax = history_req_nmax + 1
363  enddo
364  endif
365 
366  if ( history_req_nmax > history_req_limit ) then
367  write(message,*) '*** request of history file is exceed! n >', history_req_limit
368  call log('I',message)
369  elseif( history_req_nmax == 0 ) then
370  call log('I','*** No history file specified.')
371  return
372  endif
373 
374  allocate( history_item(history_req_nmax) ); history_item(:) = ''
375  allocate( history_fid(history_req_nmax) )
376  allocate( history_vid(history_req_nmax) )
377  allocate( history_tintsec(history_req_nmax) )
378  allocate( history_tintstep(history_req_nmax) )
379  allocate( history_tavg(history_req_nmax) )
380  allocate( history_zinterp(history_req_nmax) )
381 
382  allocate( history_varsum(array_size,history_req_nmax) )
383  allocate( history_size(history_req_nmax) )
384  allocate( history_tstart(history_req_nmax) )
385  allocate( history_tstrstep(history_req_nmax) )
386  allocate( history_tlststep(history_req_nmax) )
387  allocate( history_tsumsec(history_req_nmax) )
388 
389  allocate( history_axis_written(history_req_nmax) )
390 
391  if ( fid_conf > 0 ) rewind(fid_conf)
392  memsize = 0
393  ni = 0
394  do n = 1, history_req_limit
395  ! set default
396  basename = history_default_basename
397  item = 'unknown'
398  tinterval = history_default_tinterval
399  tunit = history_default_tunit
400  taverage = history_default_taverage
401  zinterp = history_default_zinterp
402  datatype = history_default_datatype
403 
404  if ( fid_conf > 0 ) then
405  read(fid_conf, nml=histitem,iostat=ierr)
406  if( ierr /= 0 ) exit
407  endif
408 
409  if ( basename == "" ) cycle
410  ni = ni + 1
411 
412  history_req_item(ni) = item
413  history_req_basename(ni) = basename
414  call calendarymdhms2sec( history_req_tintsec(ni), tinterval, tunit )
415  history_req_tintstep(ni) = int( history_req_tintsec(ni) / history_dtsec )
416 
417  history_req_tavg(ni) = taverage
418  history_req_zinterp(ni) = zinterp
419 
420  if ( history_req_tintsec(ni) <= 0.d0 ) then
421  write(message,*) 'xxx Not appropriate time interval. Check!', item, tinterval
422  call log('E',message)
423  endif
424 
425  if ( abs(history_req_tintsec(ni)-real(History_req_tintstep(ni),kind=dp)*history_dtsec) > eps ) then
426  write(message,*) 'xxx time interval must be a multiple of delta t ', &
427  history_req_tintsec(ni), real(History_req_tintstep(ni),kind=dp)*history_dtsec
428  call log('E',message)
429  endif
430 
431  if ( datatype == 'REAL4' ) then
432  history_req_dtype(n) = file_real4
433  elseif( datatype == 'REAL8' ) then
434  history_req_dtype(n) = file_real8
435  else
436  write(message,*) 'xxx Not appropriate DATATYPE. Check!', datatype
437  call log('E',message)
438  endif
439 
440  memsize = memsize + array_size * file_preclist(history_req_dtype(ni))
441  enddo
442 
443  write(message,*) '*** Number of requested history item : ', history_req_nmax
444  call log('I',message)
445  write(message,*) '*** Output default data type : ', history_default_datatype
446  call log('I',message)
447  write(message,*) '*** Memory usage for history data buffer [Mbyte] : ', memsize/1024/1024
448  call log('I',message)
449 
450  if ( (.not. present(namelist_fid)) ) then
451  if ( fid_conf > 0 ) close(fid_conf)
452  endif
453 
454  history_master = master
455  history_myrank = myrank
456 
457  allocate( history_rankidx(size(rankidx)) )
458  history_rankidx(:) = rankidx(:)
459 
460  return
module TIME
Definition: dc_calendar.f90:17
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, dimension(0:3), parameter, public file_preclist
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:
Here is the caller graph for this function:

◆ historyaddvariable()

subroutine, public gtool_history::historyaddvariable ( character(len=*), intent(in)  varname,
character(len=*), dimension(:), intent(in)  dims,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
integer, intent(in)  now_step,
integer, intent(out)  id,
logical, intent(out)  zinterp,
logical, intent(out)  existed,
character(len=*), intent(in), optional  options 
)

Definition at line 474 of file gtool_history.f90.

References gtool_file::filecreate(), gtool_file::filedefassociatedcoordinates(), gtool_file::filedefaxis(), gtool_file::filesetoption(), gtool_file::filesettattr(), and dc_log::log().

Referenced by scale_history::hist_reg().

474  use gtool_file, only: &
475  filecreate, &
476  filesetoption, &
477  fileaddvariable, &
478  filesettattr, &
479  filedefaxis, &
481  implicit none
482 
483  character(len=*), intent(in) :: varname
484  character(len=*), intent(in) :: dims(:)
485  character(len=*), intent(in) :: desc
486  character(len=*), intent(in) :: units
487  integer, intent(in) :: now_step
488  integer, intent(out) :: id
489  logical, intent(out) :: zinterp
490  logical, intent(out) :: existed
491  character(len=*), intent(in), optional :: options ! 'filetype1:key1=val1&filetype2:key2=val2&...'
492 
493  character(len=File_HMID) :: tunits
494 
495  logical :: fileexisted
496  integer :: nmax, reqid
497  integer :: n, m
498  integer :: ic, ie, is, lo
499 
500  intrinsic size
501  !---------------------------------------------------------------------------
502 
503  existed = .false.
504 
505  !--- search existing item
506  id = -1
507  nmax = min( history_id_count, history_req_nmax )
508  do n = 1, nmax
509  if ( varname == history_item(n) ) then ! match existing item
510  id = n
511  zinterp = history_zinterp(n)
512  existed = .true.
513  return
514  endif
515  enddo
516 
517  if ( id < 0 ) then ! request-register matching check
518 
519  ! new file registration
520  if ( history_time_since == '' ) then
521  tunits = history_time_units
522  else
523  tunits = trim(history_time_units)//' since '//trim(history_time_since)
524  endif
525 
526  do n = 1, history_req_nmax
527  if ( varname == history_req_item(n) ) then
528  reqid = n
529  if( history_req_basename(reqid) == '' ) exit
530  history_id_count = history_id_count + 1
531  id = history_id_count
532 
533  call filecreate( history_fid(id), & ! (out)
534  fileexisted, & ! (out)
535  trim(history_req_basename(reqid)), & ! (in)
536  history_title, & ! (in)
537  history_source, & ! (in)
538  history_institution, & ! (in)
539  history_master, & ! (in)
540  history_myrank, & ! (in)
541  history_rankidx, & ! (in)
542  time_units = tunits ) ! (in)
543 
544  if ( .not. fileexisted ) then
545 
546  if ( present(options) ) then
547  ic = -1 ! index of ':'
548  ie = -1 ! index of '='
549  is = 1 ! start index
550  lo = len_trim(options)
551  do m = 1, lo+1
552  if ( m == lo+1 .or. options(m:m) == '&' ) then
553  if ( ic == -1 .or. ie == -1 ) then
554  call log('E', 'xxx option is invalid: ' // trim(options))
555  endif
556  call filesetoption(history_fid(id), & ! (in)
557  options(is:ic-1), & ! (in)
558  options(ic+1:ie-1), options(ie+1:m-1) ) ! (in)
559  ic = -1
560  ie = -1
561  is = m + 1
562  elseif( options(m:m) == ':' ) then
563  ic = m
564  elseif( options(m:m) == '=' ) then
565  ie = m
566  endif
567  enddo
568  endif
569 
570  ! define registered history variables in file
571  do m = 1, history_axis_count
572  history_axis(m)%id = id
573  call filedefaxis( history_fid(id), & ! (in)
574  history_axis(m)%name, history_axis(m)%desc, & ! (in)
575  history_axis(m)%units, history_axis(m)%dim, & ! (in)
576  history_axis(m)%type, history_axis(m)%dim_size ) ! (in)
577  enddo
578 
579  do m = 1, history_assoc_count
580  history_assoc(m)%id = id
581  call filedefassociatedcoordinates( history_fid(id), & ! (in)
582  history_assoc(m)%name, history_assoc(m)%desc, & ! (in)
583  history_assoc(m)%units, & ! (in)
584  history_assoc(m)%dims(1:history_assoc(m)%ndims), & ! (in)
585  history_assoc(m)%type ) ! (in)
586  enddo
587  history_axis_written(id) = .false.
588 
589  endif
590 
591  history_item(id) = varname
592  history_tintsec(id) = history_req_tintsec(reqid)
593  history_tintstep(id) = history_req_tintstep(reqid)
594  history_tavg(id) = history_req_tavg(reqid)
595  history_zinterp(id) = history_req_zinterp(reqid)
596 
597  history_varsum(:,id) = 0.d0
598 
599  if ( history_output_step0 .and. now_step==1 ) then
600  history_tstrstep(id) = 1 - history_tintstep(id)
601  else
602  history_tstrstep(id) = 1
603  endif
604  if ( history_output_start > 0.0_dp ) then
605  history_tstart(id) = history_startdaysec + history_output_start
606  else
607  history_tstart(id) = history_startdaysec
608  endif
609  history_tlststep(id) = history_tstrstep(id)
610  history_tsumsec(id) = 0.d0
611 
612  call fileaddvariable( history_vid(id), & ! (out)
613  history_fid(id), & ! (in)
614  varname, desc, units, dims, & ! (in)
615  history_req_dtype(reqid), & ! (in)
616  history_tintsec(id), & ! (in)
617  history_tavg(id) ) ! (in)
618 
619  if ( .not. fileexisted ) then
620  do m = 1, history_axis_count
621  if ( history_axis(m)%down ) then
622  call filesettattr( history_fid(id), history_axis(m)%name, "positive", "down" )
623  endif
624  enddo
625  endif
626 
627  write(message,*) '*** [HIST] Item registration No.= ', id
628  call log('I',message)
629  write(message,*) '] Name : ', trim(history_item(id))
630  call log('I',message)
631  write(message,*) '] Description : ', trim(desc)
632  call log('I',message)
633  write(message,*) '] Unit : ', trim(units)
634  call log('I',message)
635  write(message,*) '] Interval [sec] : ', history_tintsec(id)
636  call log('I',message)
637  write(message,*) '] Interval [step] : ', history_tintstep(id)
638  call log('I',message)
639  write(message,*) '] Time Average? : ', history_tavg(id)
640  call log('I',message)
641  write(message,*) '] z* -> z conversion? : ', history_zinterp(id)
642  call log('I',message)
643  call log('I','')
644 
645  zinterp = history_zinterp(id)
646 
647  exit
648  endif
649  enddo
650 
651  endif
652 
653  return
subroutine, public filecreate(fid, existed, basename, title, source, institution, master, myrank, rankidx, single, time_units, append)
Definition: gtool_file.f90:181
module GTOOL_FILE
Definition: gtool_file.f90:17
subroutine, public filedefassociatedcoordinates(fid, name, desc, units, dim_names, dtype)
Definition: gtool_file.f90:869
subroutine, public filesettattr(fid, vname, key, val)
subroutine, public filesetoption(fid, filetype, key, val)
Definition: gtool_file.f90:453
subroutine, public log(type, message)
Definition: dc_log.f90:133
subroutine, public filedefaxis(fid, name, desc, units, dim_name, dtype, dim_size)
Definition: gtool_file.f90:564
Here is the call graph for this function:
Here is the caller graph for this function:

◆ historywriteaxes()

subroutine, public gtool_history::historywriteaxes ( )

Definition at line 658 of file gtool_history.f90.

References gtool_file::fileenddef().

Referenced by historywriteall().

658  use gtool_file, only: &
659  fileenddef, &
660  filewriteaxis, &
661  filewriteassociatedcoordinates
662  implicit none
663 
664  integer :: m
665  !---------------------------------------------------------------------------
666 
667  if ( history_req_nmax == 0 ) return
668 
669  ! Assume all history axes are written into the same file
670  if ( history_axis_written(history_axis(1)%id) ) return
671 
672  call fileenddef( history_fid(history_axis(1)%id) )
673 
674  ! write registered history variables to file
675  do m = 1, history_axis_count
676  call filewriteaxis( history_fid(history_axis(m)%id), & ! (in)
677  history_axis(m)%name, & ! (in)
678  history_axis(m)%var ) ! (in)
679  enddo
680 
681  do m = 1, history_assoc_count
682  call filewriteassociatedcoordinates( history_fid(history_assoc(m)%id), & ! (in)
683  history_assoc(m)%name, & ! (in)
684  history_assoc(m)%var ) ! (in)
685  enddo
686 
687  history_axis_written(history_axis(1)%id) = .true.
688 
689  return
module GTOOL_FILE
Definition: gtool_file.f90:17
subroutine, public fileenddef(fid)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ historyputaxissp()

subroutine gtool_history::historyputaxissp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), intent(in)  dim,
real(sp), dimension(:), intent(in)  var,
character(len=*), intent(in), optional  dtype,
logical, intent(in), optional  down 
)

Definition at line 703 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

703  use gtool_file_h, only: &
704  file_real4, &
705  file_real8
706  implicit none
707 
708  character(len=*), intent(in) :: name
709  character(len=*), intent(in) :: desc
710  character(len=*), intent(in) :: units
711  character(len=*), intent(in) :: dim
712  real(SP), intent(in) :: var(:)
713  character(len=*), intent(in), optional :: dtype
714  logical, intent(in), optional :: down
715 
716  integer :: type
717  !---------------------------------------------------------------------------
718 
719  if ( present(dtype) ) then
720  if ( dtype == 'REAL4' ) then
721  type = file_real4
722  elseif( dtype == 'REAL8' ) then
723  type = file_real8
724  else
725  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
726  call log('E',message)
727  endif
728  else
729  type = file_real4
730  endif
731 
732  if ( history_axis_count < history_axis_limit ) then
733  history_axis_count = history_axis_count + 1
734 
735  history_axis(history_axis_count)%name = name
736  history_axis(history_axis_count)%desc = desc
737  history_axis(history_axis_count)%units = units
738  history_axis(history_axis_count)%dim = dim
739  history_axis(history_axis_count)%type = type
740  history_axis(history_axis_count)%dim_size = size(var)
741 
742  allocate(history_axis(history_axis_count)%var(size(var)))
743  history_axis(history_axis_count)%var = var
744 
745  if ( present(down) ) then
746  history_axis(history_axis_count)%down = down
747  else
748  history_axis(history_axis_count)%down = .false.
749  endif
750  else
751  write(message,*) 'xxx Number of axis exceeds the limit.'
752  call log('E',message)
753  endif
754 
755  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyputaxisdp()

subroutine gtool_history::historyputaxisdp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), intent(in)  dim,
real(dp), dimension(:), intent(in)  var,
character(len=*), intent(in), optional  dtype,
logical, intent(in), optional  down 
)

Definition at line 765 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

765  use gtool_file_h, only: &
766  file_real4, &
767  file_real8
768  implicit none
769 
770  character(len=*), intent(in) :: name
771  character(len=*), intent(in) :: desc
772  character(len=*), intent(in) :: units
773  character(len=*), intent(in) :: dim
774  real(DP), intent(in) :: var(:)
775  character(len=*), intent(in), optional :: dtype
776  logical, intent(in), optional :: down
777 
778  integer :: type
779  !---------------------------------------------------------------------------
780 
781  if ( present(dtype) ) then
782  if ( dtype == 'REAL4' ) then
783  type = file_real4
784  elseif( dtype == 'REAL8' ) then
785  type = file_real8
786  else
787  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
788  call log('E',message)
789  endif
790  else
791  type = file_real8
792  endif
793 
794  if ( history_axis_count < history_axis_limit ) then
795  history_axis_count = history_axis_count + 1
796 
797  history_axis(history_axis_count)%name = name
798  history_axis(history_axis_count)%desc = desc
799  history_axis(history_axis_count)%units = units
800  history_axis(history_axis_count)%dim = dim
801  history_axis(history_axis_count)%type = type
802  history_axis(history_axis_count)%dim_size = size(var)
803 
804  allocate(history_axis(history_axis_count)%var(size(var)))
805  history_axis(history_axis_count)%var = var
806 
807  if ( present(down) ) then
808  history_axis(history_axis_count)%down = down
809  else
810  history_axis(history_axis_count)%down = .false.
811  endif
812  else
813  write(message,*) 'xxx Number of axis exceeds the limit.'
814  call log('E',message)
815  endif
816 
817  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput1dassociatedcoordinatessp()

subroutine gtool_history::historyput1dassociatedcoordinatessp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(sp), dimension (:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 829 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

829  use gtool_file_h, only: &
830  file_real4, &
831  file_real8
832  implicit none
833 
834  character(len=*), intent(in) :: name
835  character(len=*), intent(in) :: desc
836  character(len=*), intent(in) :: units
837  character(len=*), intent(in) :: dims(:)
838  real(SP), intent(in) :: var (:)
839  character(len=*), intent(in), optional :: dtype
840 
841  integer :: type
842  !---------------------------------------------------------------------------
843 
844  if ( present(dtype) ) then
845  if ( dtype == 'REAL4' ) then
846  type = file_real4
847  elseif( dtype == 'REAL8' ) then
848  type = file_real8
849  else
850  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
851  call log('E',message)
852  endif
853  else
854  type = file_real4
855  endif
856 
857  if ( history_assoc_count < history_assoc_limit ) then
858  history_assoc_count = history_assoc_count + 1
859 
860  history_assoc(history_assoc_count)%name = name
861  history_assoc(history_assoc_count)%desc = desc
862  history_assoc(history_assoc_count)%units = units
863  history_assoc(history_assoc_count)%dims(1:1) = dims
864  history_assoc(history_assoc_count)%ndims = 1
865  history_assoc(history_assoc_count)%type = type
866 
867  allocate(history_assoc(history_assoc_count)%var(size(var)))
868  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
869  else
870  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
871  call log('E',message)
872  endif
873 
874  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput1dassociatedcoordinatesdp()

subroutine gtool_history::historyput1dassociatedcoordinatesdp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(dp), dimension (:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 886 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

886  use gtool_file_h, only: &
887  file_real4, &
888  file_real8
889  implicit none
890 
891  character(len=*), intent(in) :: name
892  character(len=*), intent(in) :: desc
893  character(len=*), intent(in) :: units
894  character(len=*), intent(in) :: dims(:)
895  real(DP), intent(in) :: var (:)
896  character(len=*), intent(in), optional :: dtype
897 
898  integer :: type
899  !---------------------------------------------------------------------------
900 
901  if ( present(dtype) ) then
902  if ( dtype == 'REAL4' ) then
903  type = file_real4
904  elseif( dtype == 'REAL8' ) then
905  type = file_real8
906  else
907  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
908  call log('E',message)
909  endif
910  else
911  type = file_real8
912  endif
913 
914  if ( history_assoc_count < history_assoc_limit ) then
915  history_assoc_count = history_assoc_count + 1
916 
917  history_assoc(history_assoc_count)%name = name
918  history_assoc(history_assoc_count)%desc = desc
919  history_assoc(history_assoc_count)%units = units
920  history_assoc(history_assoc_count)%dims(1:1) = dims
921  history_assoc(history_assoc_count)%ndims = 1
922  history_assoc(history_assoc_count)%type = type
923 
924  allocate(history_assoc(history_assoc_count)%var(size(var)))
925  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
926  else
927  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
928  call log('E',message)
929  endif
930 
931  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput2dassociatedcoordinatessp()

subroutine gtool_history::historyput2dassociatedcoordinatessp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(sp), dimension (:,:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 943 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

943  use gtool_file_h, only: &
944  file_real4, &
945  file_real8
946  implicit none
947 
948  character(len=*), intent(in) :: name
949  character(len=*), intent(in) :: desc
950  character(len=*), intent(in) :: units
951  character(len=*), intent(in) :: dims(:)
952  real(SP), intent(in) :: var (:,:)
953  character(len=*), intent(in), optional :: dtype
954 
955  integer :: type
956  !---------------------------------------------------------------------------
957 
958  if ( present(dtype) ) then
959  if ( dtype == 'REAL4' ) then
960  type = file_real4
961  elseif( dtype == 'REAL8' ) then
962  type = file_real8
963  else
964  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
965  call log('E',message)
966  endif
967  else
968  type = file_real4
969  endif
970 
971  if ( history_assoc_count < history_assoc_limit ) then
972  history_assoc_count = history_assoc_count + 1
973 
974  history_assoc(history_assoc_count)%name = name
975  history_assoc(history_assoc_count)%desc = desc
976  history_assoc(history_assoc_count)%units = units
977  history_assoc(history_assoc_count)%dims(1:2) = dims
978  history_assoc(history_assoc_count)%ndims = 2
979  history_assoc(history_assoc_count)%type = type
980 
981  allocate(history_assoc(history_assoc_count)%var(size(var)))
982  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
983  else
984  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
985  call log('E',message)
986  endif
987 
988  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput2dassociatedcoordinatesdp()

subroutine gtool_history::historyput2dassociatedcoordinatesdp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(dp), dimension (:,:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 1000 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

1000  use gtool_file_h, only: &
1001  file_real4, &
1002  file_real8
1003  implicit none
1004 
1005  character(len=*), intent(in) :: name
1006  character(len=*), intent(in) :: desc
1007  character(len=*), intent(in) :: units
1008  character(len=*), intent(in) :: dims(:)
1009  real(DP), intent(in) :: var (:,:)
1010  character(len=*), intent(in), optional :: dtype
1011 
1012  integer :: type
1013  !---------------------------------------------------------------------------
1014 
1015  if ( present(dtype) ) then
1016  if ( dtype == 'REAL4' ) then
1017  type = file_real4
1018  elseif( dtype == 'REAL8' ) then
1019  type = file_real8
1020  else
1021  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
1022  call log('E',message)
1023  endif
1024  else
1025  type = file_real8
1026  endif
1027 
1028  if ( history_assoc_count < history_assoc_limit ) then
1029  history_assoc_count = history_assoc_count + 1
1030 
1031  history_assoc(history_assoc_count)%name = name
1032  history_assoc(history_assoc_count)%desc = desc
1033  history_assoc(history_assoc_count)%units = units
1034  history_assoc(history_assoc_count)%dims(1:2) = dims
1035  history_assoc(history_assoc_count)%ndims = 2
1036  history_assoc(history_assoc_count)%type = type
1037 
1038  allocate(history_assoc(history_assoc_count)%var(size(var)))
1039  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
1040  else
1041  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
1042  call log('E',message)
1043  endif
1044 
1045  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput3dassociatedcoordinatessp()

subroutine gtool_history::historyput3dassociatedcoordinatessp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(sp), dimension (:,:,:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 1057 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

1057  use gtool_file_h, only: &
1058  file_real4, &
1059  file_real8
1060  implicit none
1061 
1062  character(len=*), intent(in) :: name
1063  character(len=*), intent(in) :: desc
1064  character(len=*), intent(in) :: units
1065  character(len=*), intent(in) :: dims(:)
1066  real(SP), intent(in) :: var (:,:,:)
1067  character(len=*), intent(in), optional :: dtype
1068 
1069  integer :: type
1070  !---------------------------------------------------------------------------
1071 
1072  if ( present(dtype) ) then
1073  if ( dtype == 'REAL4' ) then
1074  type = file_real4
1075  elseif( dtype == 'REAL8' ) then
1076  type = file_real8
1077  else
1078  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
1079  call log('E',message)
1080  endif
1081  else
1082  type = file_real4
1083  endif
1084 
1085  if ( history_assoc_count < history_assoc_limit ) then
1086  history_assoc_count = history_assoc_count + 1
1087 
1088  history_assoc(history_assoc_count)%name = name
1089  history_assoc(history_assoc_count)%desc = desc
1090  history_assoc(history_assoc_count)%units = units
1091  history_assoc(history_assoc_count)%dims(1:3) = dims
1092  history_assoc(history_assoc_count)%ndims = 3
1093  history_assoc(history_assoc_count)%type = type
1094 
1095  allocate(history_assoc(history_assoc_count)%var(size(var)))
1096  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
1097  else
1098  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
1099  call log('E',message)
1100  endif
1101 
1102  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput3dassociatedcoordinatesdp()

subroutine gtool_history::historyput3dassociatedcoordinatesdp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(dp), dimension (:,:,:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 1114 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

1114  use gtool_file_h, only: &
1115  file_real4, &
1116  file_real8
1117  implicit none
1118 
1119  character(len=*), intent(in) :: name
1120  character(len=*), intent(in) :: desc
1121  character(len=*), intent(in) :: units
1122  character(len=*), intent(in) :: dims(:)
1123  real(DP), intent(in) :: var (:,:,:)
1124  character(len=*), intent(in), optional :: dtype
1125 
1126  integer :: type
1127  !---------------------------------------------------------------------------
1128 
1129  if ( present(dtype) ) then
1130  if ( dtype == 'REAL4' ) then
1131  type = file_real4
1132  elseif( dtype == 'REAL8' ) then
1133  type = file_real8
1134  else
1135  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
1136  call log('E',message)
1137  endif
1138  else
1139  type = file_real8
1140  endif
1141 
1142  if ( history_assoc_count < history_assoc_limit ) then
1143  history_assoc_count = history_assoc_count + 1
1144 
1145  history_assoc(history_assoc_count)%name = name
1146  history_assoc(history_assoc_count)%desc = desc
1147  history_assoc(history_assoc_count)%units = units
1148  history_assoc(history_assoc_count)%dims(1:3) = dims
1149  history_assoc(history_assoc_count)%ndims = 3
1150  history_assoc(history_assoc_count)%type = type
1151 
1152  allocate(history_assoc(history_assoc_count)%var(size(var)))
1153  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
1154  else
1155  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
1156  call log('E',message)
1157  endif
1158 
1159  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput4dassociatedcoordinatessp()

subroutine gtool_history::historyput4dassociatedcoordinatessp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(sp), dimension (:,:,:,:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 1171 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

1171  use gtool_file_h, only: &
1172  file_real4, &
1173  file_real8
1174  implicit none
1175 
1176  character(len=*), intent(in) :: name
1177  character(len=*), intent(in) :: desc
1178  character(len=*), intent(in) :: units
1179  character(len=*), intent(in) :: dims(:)
1180  real(SP), intent(in) :: var (:,:,:,:)
1181  character(len=*), intent(in), optional :: dtype
1182 
1183  integer :: type
1184  !---------------------------------------------------------------------------
1185 
1186  if ( present(dtype) ) then
1187  if ( dtype == 'REAL4' ) then
1188  type = file_real4
1189  elseif( dtype == 'REAL8' ) then
1190  type = file_real8
1191  else
1192  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
1193  call log('E',message)
1194  endif
1195  else
1196  type = file_real4
1197  endif
1198 
1199  if ( history_assoc_count < history_assoc_limit ) then
1200  history_assoc_count = history_assoc_count + 1
1201 
1202  history_assoc(history_assoc_count)%name = name
1203  history_assoc(history_assoc_count)%desc = desc
1204  history_assoc(history_assoc_count)%units = units
1205  history_assoc(history_assoc_count)%dims(1:4) = dims
1206  history_assoc(history_assoc_count)%ndims = 4
1207  history_assoc(history_assoc_count)%type = type
1208 
1209  allocate(history_assoc(history_assoc_count)%var(size(var)))
1210  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
1211  else
1212  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
1213  call log('E',message)
1214  endif
1215 
1216  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historyput4dassociatedcoordinatesdp()

subroutine gtool_history::historyput4dassociatedcoordinatesdp ( character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dims,
real(dp), dimension (:,:,:,:), intent(in)  var,
character(len=*), intent(in), optional  dtype 
)

interface HistoryPutAssociatedCoordinates

Definition at line 1228 of file gtool_history.f90.

References gtool_file_h::file_real4, gtool_file_h::file_real8, and dc_log::log().

1228  use gtool_file_h, only: &
1229  file_real4, &
1230  file_real8
1231  implicit none
1232 
1233  character(len=*), intent(in) :: name
1234  character(len=*), intent(in) :: desc
1235  character(len=*), intent(in) :: units
1236  character(len=*), intent(in) :: dims(:)
1237  real(DP), intent(in) :: var (:,:,:,:)
1238  character(len=*), intent(in), optional :: dtype
1239 
1240  integer :: type
1241  !---------------------------------------------------------------------------
1242 
1243  if ( present(dtype) ) then
1244  if ( dtype == 'REAL4' ) then
1245  type = file_real4
1246  elseif( dtype == 'REAL8' ) then
1247  type = file_real8
1248  else
1249  write(message,*) 'xxx Not appropriate dtype. Check!', dtype
1250  call log('E',message)
1251  endif
1252  else
1253  type = file_real8
1254  endif
1255 
1256  if ( history_assoc_count < history_assoc_limit ) then
1257  history_assoc_count = history_assoc_count + 1
1258 
1259  history_assoc(history_assoc_count)%name = name
1260  history_assoc(history_assoc_count)%desc = desc
1261  history_assoc(history_assoc_count)%units = units
1262  history_assoc(history_assoc_count)%dims(1:4) = dims
1263  history_assoc(history_assoc_count)%ndims = 4
1264  history_assoc(history_assoc_count)%type = type
1265 
1266  allocate(history_assoc(history_assoc_count)%var(size(var)))
1267  history_assoc(history_assoc_count)%var = reshape(var, (/size(var)/))
1268  else
1269  write(message,*) 'xxx Number of associate coordinates exceeds the limit.'
1270  call log('E',message)
1271  endif
1272 
1273  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
integer, parameter, public file_real4
module FILE I/O HEADER
integer, parameter, public file_real8
Here is the call graph for this function:

◆ historysettattr()

subroutine, public gtool_history::historysettattr ( character(len=*), intent(in)  varname,
character(len=*), intent(in)  key,
character(len=*), intent(in)  val 
)

Definition at line 1282 of file gtool_history.f90.

References gtool_file::filesettattr().

1282  use gtool_file, only: &
1283  filesettattr
1284  implicit none
1285 
1286  character(len=*), intent(in) :: varname
1287  character(len=*), intent(in) :: key
1288  character(len=*), intent(in) :: val
1289 
1290  integer :: n
1291  !---------------------------------------------------------------------------
1292 
1293  do n = 1, history_id_count
1294  call filesettattr( history_fid(n), & ! (in)
1295  varname, & ! (in)
1296  key, & ! (in)
1297  val ) ! (in)
1298  enddo
1299 
module GTOOL_FILE
Definition: gtool_file.f90:17
subroutine, public filesettattr(fid, vname, key, val)
Here is the call graph for this function:

◆ historyquery()

subroutine, public gtool_history::historyquery ( integer, intent(in)  itemid,
integer, intent(in)  step_next,
logical, intent(out)  answer 
)

Definition at line 1308 of file gtool_history.f90.

References dc_log::log().

Referenced by scale_history::hist_query().

1308  implicit none
1309 
1310  integer, intent(in) :: itemid
1311  integer, intent(in) :: step_next
1312  logical, intent(out) :: answer
1313  !---------------------------------------------------------------------------
1314 
1315  answer = .false.
1316 
1317  if ( history_tavg(itemid) ) then
1318  answer = .true.
1319  elseif( step_next == history_tstrstep(itemid) + history_tintstep(itemid) ) then
1320  answer = .true.
1321  endif
1322 
1323  return
Here is the call graph for this function:
Here is the caller graph for this function:

◆ historywrite()

subroutine, public gtool_history::historywrite ( integer, intent(in)  itemid,
integer, intent(in)  step_now 
)

Definition at line 1973 of file gtool_history.f90.

References historyoutputlist(), and dc_log::log().

Referenced by historywriteall().

1973  use dc_calendar, only: &
1974  calendarsec2ymdhms
1975  use gtool_file, only: &
1976  filewrite
1977  implicit none
1978 
1979  integer, intent(in) :: itemid
1980  integer, intent(in) :: step_now
1981 
1982  integer :: isize
1983  real(DP) :: time_str, time_end
1984  real(DP) :: sec_str, sec_end
1985 
1986  real(DP), save :: sec_end_last = -1.0_dp
1987  logical, save :: firsttime = .true.
1988  !---------------------------------------------------------------------------
1989 
1990  if( history_id_count == 0 ) return
1991 
1992  if ( step_now < history_tstrstep(itemid) + history_tintstep(itemid) ) then
1993  return
1994  endif
1995 
1996  if ( history_tlststep(itemid) == history_tstrstep(itemid) ) then
1997  write(message,*) 'xxx History variable was never put after the last output!: ', &
1998  trim(history_item(itemid))
1999  if ( history_error_putmiss ) then
2000  call log('E',message)
2001  else
2002  call log('I',message)
2003  endif
2004  endif
2005 
2006  isize = history_size(itemid)
2007 
2008  if ( history_tavg(itemid) ) then
2009  history_varsum(1:isize,itemid) = history_varsum(1:isize,itemid) / history_tsumsec(itemid)
2010  endif
2011 
2012  if ( firsttime ) then
2013  firsttime = .false.
2014  call historyoutputlist
2015  endif
2016 
2017  sec_str = history_startdaysec + real(History_tstrstep(itemid)-1,kind=DP) * history_dtsec
2018  sec_end = history_startdaysec + real(step_now-1 ,kind=DP) * history_dtsec
2019 
2020  ! convert time units
2021  call calendarsec2ymdhms( time_str, sec_str, history_time_units )
2022  call calendarsec2ymdhms( time_end, sec_end, history_time_units )
2023 
2024  if ( sec_end .ge. history_tstart(itemid) ) then
2025  if ( sec_end_last < sec_end ) then
2026  write(message,'(A)') '*** Output History'
2027  call log('I',message)
2028  endif
2029 
2030  call filewrite( history_fid(itemid), & ! file id
2031  history_vid(itemid), & ! variable id
2032  history_varsum(1:isize,itemid), & ! data
2033  time_str, & ! start time
2034  time_end ) ! end time
2035  else
2036  if ( sec_end_last < sec_end ) then
2037  write(message,'(A,2F15.3)') '*** Output History: Suppressed ', sec_end, history_tstart(itemid)
2038  call log('I',message)
2039  endif
2040  endif
2041 
2042  history_varsum(:,itemid) = 0.0_dp
2043  history_tstrstep(itemid) = step_now
2044  history_tlststep(itemid) = step_now
2045  history_tsumsec(itemid) = 0.0_dp
2046 
2047  sec_end_last = sec_end
2048 
2049  return
module GTOOL_FILE
Definition: gtool_file.f90:17
module TIME
Definition: dc_calendar.f90:17
subroutine, public log(type, message)
Definition: dc_log.f90:133
Here is the call graph for this function:
Here is the caller graph for this function:

◆ historywriteall()

subroutine, public gtool_history::historywriteall ( integer, intent(in)  step_now)

Definition at line 2056 of file gtool_history.f90.

References historywrite(), and historywriteaxes().

Referenced by scale_history::hist_write().

2056  implicit none
2057 
2058  integer, intent(in) :: step_now
2059 
2060  integer :: n
2061  !---------------------------------------------------------------------------
2062 
2063  ! Write registered axis variables to history file
2064  ! This subroutine must be called after all HIST_reg calls are completed
2065  call historywriteaxes
2066 
2067  do n = 1, history_id_count
2068  call historywrite( n, step_now )
2069  enddo
2070 
2071  return
Here is the call graph for this function:
Here is the caller graph for this function:

◆ historyget1dsp()

subroutine gtool_history::historyget1dsp ( real(sp), dimension(:), intent(out)  var,
character(len=*), intent(in)  basename,
character(len=*), intent(in)  varname,
integer, intent(in)  step,
logical, intent(in), optional  allow_missing,
logical, intent(in), optional  single 
)

Definition at line 2115 of file gtool_history.f90.

2115  use gtool_file, only: &
2116  fileread
2117  implicit none
2118 
2119  real(SP), intent(out) :: var(:)
2120  character(len=*), intent(in) :: basename
2121  character(len=*), intent(in) :: varname
2122  integer, intent(in) :: step
2123  logical, intent(in), optional :: allow_missing
2124  logical, intent(in), optional :: single
2125  !---------------------------------------------------------------------------
2126 
2127  call fileread( var, & ! [OUT]
2128  basename, & ! [IN]
2129  varname, & ! [IN]
2130  step, & ! [IN]
2131  history_myrank, & ! [IN]
2132  allow_missing, & ! [IN]
2133  single ) ! [IN]
2134 
2135  return
module GTOOL_FILE
Definition: gtool_file.f90:17

◆ historyget2ddp()

subroutine gtool_history::historyget2ddp ( real(dp), dimension(:,:), intent(out)  var,
character(len=*), intent(in)  basename,
character(len=*), intent(in)  varname,
integer, intent(in)  step,
logical, intent(in), optional  allow_missing,
logical, intent(in), optional  single 
)

Definition at line 2147 of file gtool_history.f90.

2147  use gtool_file, only: &
2148  fileread
2149  implicit none
2150 
2151  real(DP), intent(out) :: var(:,:)
2152  character(len=*), intent(in) :: basename
2153  character(len=*), intent(in) :: varname
2154  integer, intent(in) :: step
2155  logical, intent(in), optional :: allow_missing
2156  logical, intent(in), optional :: single
2157  !---------------------------------------------------------------------------
2158 
2159  call fileread( var, & ! [OUT]
2160  basename, & ! [IN]
2161  varname, & ! [IN]
2162  step, & ! [IN]
2163  history_myrank, & ! [IN]
2164  allow_missing, & ! [IN]
2165  single ) ! [IN]
2166 
2167  return
module GTOOL_FILE
Definition: gtool_file.f90:17

◆ historyget2dsp()

subroutine gtool_history::historyget2dsp ( real(sp), dimension(:,:), intent(out)  var,
character(len=*), intent(in)  basename,
character(len=*), intent(in)  varname,
integer, intent(in)  step,
logical, intent(in), optional  allow_missing,
logical, intent(in), optional  single 
)

Definition at line 2179 of file gtool_history.f90.

2179  use gtool_file, only: &
2180  fileread
2181  implicit none
2182 
2183  real(SP), intent(out) :: var(:,:)
2184  character(len=*), intent(in) :: basename
2185  character(len=*), intent(in) :: varname
2186  integer, intent(in) :: step
2187  logical, intent(in), optional :: allow_missing
2188  logical, intent(in), optional :: single
2189  !---------------------------------------------------------------------------
2190 
2191  call fileread( var, & ! [OUT]
2192  basename, & ! [IN]
2193  varname, & ! [IN]
2194  step, & ! [IN]
2195  history_myrank, & ! [IN]
2196  allow_missing, & ! [IN]
2197  single ) ! [IN]
2198 
2199  return
module GTOOL_FILE
Definition: gtool_file.f90:17

◆ historyget3ddp()

subroutine gtool_history::historyget3ddp ( real(dp), dimension(:,:,:), intent(out)  var,
character(len=*), intent(in)  basename,
character(len=*), intent(in)  varname,
integer, intent(in)  step,
logical, intent(in), optional  allow_missing,
logical, intent(in), optional  single 
)

Definition at line 2211 of file gtool_history.f90.

2211  use gtool_file, only: &
2212  fileread
2213  implicit none
2214 
2215  real(DP), intent(out) :: var(:,:,:)
2216  character(len=*), intent(in) :: basename
2217  character(len=*), intent(in) :: varname
2218  integer, intent(in) :: step
2219  logical, intent(in), optional :: allow_missing
2220  logical, intent(in), optional :: single
2221  !---------------------------------------------------------------------------
2222 
2223  call fileread( var, & ! [OUT]
2224  basename, & ! [IN]
2225  varname, & ! [IN]
2226  step, & ! [IN]
2227  history_myrank, & ! [IN]
2228  allow_missing, & ! [IN]
2229  single ) ! [IN]
2230 
2231  return
module GTOOL_FILE
Definition: gtool_file.f90:17

◆ historyget3dsp()

subroutine gtool_history::historyget3dsp ( real(sp), dimension(:,:,:), intent(out)  var,
character(len=*), intent(in)  basename,
character(len=*), intent(in)  varname,
integer, intent(in)  step,
logical, intent(in), optional  allow_missing,
logical, intent(in), optional  single 
)

Definition at line 2243 of file gtool_history.f90.

2243  use gtool_file, only: &
2244  fileread
2245  implicit none
2246 
2247  real(SP), intent(out) :: var(:,:,:)
2248  character(len=*), intent(in) :: basename
2249  character(len=*), intent(in) :: varname
2250  integer, intent(in) :: step
2251  logical, intent(in), optional :: allow_missing
2252  logical, intent(in), optional :: single
2253  !---------------------------------------------------------------------------
2254 
2255  call fileread( var, & ! [OUT]
2256  basename, & ! [IN]
2257  varname, & ! [IN]
2258  step, & ! [IN]
2259  history_myrank, & ! [IN]
2260  allow_missing, & ! [IN]
2261  single ) ! [IN]
2262 
2263  return
module GTOOL_FILE
Definition: gtool_file.f90:17

◆ historyoutputlist()

subroutine, public gtool_history::historyoutputlist ( )

Definition at line 2268 of file gtool_history.f90.

References dc_log::log().

Referenced by historywrite().

2268  implicit none
2269 
2270  integer :: n
2271  !---------------------------------------------------------------------------
2272 
2273  call log('I','')
2274  write(message,*) '*** [HIST] Output item list '
2275  call log('I',message)
2276  write(message,*) '*** Number of history item :', history_req_nmax
2277  call log('I',message)
2278  write(message,*) 'NAME :size :interval[sec]: [step]:timeavg?:zinterp?'
2279  call log('I',message)
2280  write(message,*) '============================================================================'
2281  call log('I',message)
2282 
2283  do n = 1, history_id_count
2284  write(message,'(1x,A,1x,I8,1x,f13.3,1x,I8,1x,L8,1x,L8)') &
2285  history_item(n), history_size(n), history_tintsec(n), history_tintstep(n), history_tavg(n), history_zinterp(n)
2286  call log('I',message)
2287  enddo
2288 
2289  write(message,*) '============================================================================'
2290  call log('I',message)
2291  call log('I','')
2292 
2293  return
subroutine, public log(type, message)
Definition: dc_log.f90:133
Here is the call graph for this function:
Here is the caller graph for this function:

◆ historyfinalize()

subroutine, public gtool_history::historyfinalize ( )

Definition at line 2298 of file gtool_history.f90.

References gtool_file::fileclose().

2298  use gtool_file, only: &
2299  fileclose
2300  implicit none
2301 
2302  integer :: n
2303  !---------------------------------------------------------------------------
2304 
2305  do n = 1, history_id_count
2306  call fileclose( history_fid(n) )
2307  enddo
2308 
2309  return
module GTOOL_FILE
Definition: gtool_file.f90:17
subroutine, public fileclose(fid)
Here is the call graph for this function: