SCALE-RM
gtool_history.f90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
13 !-------------------------------------------------------------------------------
14 ! Warning: This file was generated from gtool_history.f90.erb.
15 ! Do not edit this file.
16 !-------------------------------------------------------------------------------
18  !-----------------------------------------------------------------------------
19  !
20  !++ Used modules
21  !
22  use dc_log, only: &
23  log, &
24 #if defined(__pgi) || defined(__es2)
25  log_fid, &
26 #endif
27  log_lmsg
28  use dc_types, only: &
29  sp, &
30  dp
31  use gtool_file_h, only: &
32  file_hlong, &
33  file_hshort, &
34  file_hmid
35  !-----------------------------------------------------------------------------
36  implicit none
37  private
38  !-----------------------------------------------------------------------------
39  !
40  !++ Public procedures
41  !
42  public :: historyinit
43  public :: historyaddvariable
44  public :: historyputaxis
45  public :: historyputassociatedcoordinates
46  public :: historywriteaxes
47  public :: historysettattr
48  public :: historyquery
49  public :: historyput
50  public :: historywrite
51  public :: historywriteall
52  public :: historyget
53  public :: historyoutputlist
54  public :: historyfinalize
55 
56  interface historyputaxis
57  module procedure historyputaxissp
58  module procedure historyputaxisdp
59  end interface historyputaxis
60 
61  interface historyputassociatedcoordinates
70  end interface historyputassociatedcoordinates
71 
72  interface historyput
73  module procedure historyput0dnamesp
74  module procedure historyput0didsp
75  module procedure historyput0dnamedp
76  module procedure historyput0diddp
77  module procedure historyput1dnamesp
78  module procedure historyput1didsp
79  module procedure historyput1dnamedp
80  module procedure historyput1diddp
81  module procedure historyput2dnamesp
82  module procedure historyput2didsp
83  module procedure historyput2dnamedp
84  module procedure historyput2diddp
85  module procedure historyput3dnamesp
86  module procedure historyput3didsp
87  module procedure historyput3dnamedp
88  module procedure historyput3diddp
89  end interface historyput
90 
91  interface historyget
92  module procedure historyget1dsp
93  module procedure historyget1ddp
94  module procedure historyget2dsp
95  module procedure historyget2ddp
96  module procedure historyget3dsp
97  module procedure historyget3ddp
98  end interface historyget
99 
100  type axis
101  character(len=File_HSHORT) :: name
102  character(len=File_HLONG) :: desc
103  character(len=File_HSHORT) :: units
104  character(len=File_HSHORT) :: dim
105  integer :: type
106  integer :: dim_size
107  integer :: id
108  real(DP), pointer :: var(:)
109  logical :: down
110  end type axis
111 
112  type assoc
113  character(len=File_HSHORT) :: name
114  character(len=File_HLONG) :: desc
115  character(len=File_HSHORT) :: units
116  character(len=File_HSHORT) :: dims(4)
117  integer :: ndims
118  integer :: type
119  integer :: id
120  real(DP), pointer :: var(:)
121  end type assoc
122 
123  !-----------------------------------------------------------------------------
124  !
125  !++ included parameters
126  !
127  !-----------------------------------------------------------------------------
128  !
129  !++ Public parameters & variables
130  !
131  !-----------------------------------------------------------------------------
132  !
133  !++ Private procedures
134  !
135  !-----------------------------------------------------------------------------
136  !
137  !++ Private parameters & variables
138  !
139  character(len=File_HMID), private :: history_title
140  character(len=File_HMID), private :: history_source
141  character(len=File_HMID), private :: history_institution
142  character(len=File_HMID), private :: history_time_units
143  character(len=File_HMID), private :: history_time_since
144  real(DP), private :: history_dtsec
145  real(DP), private :: history_startdaysec
146 
147  logical, private :: history_output_step0 = .false.
148  real(DP), private :: history_output_start = 0.0_dp
149  logical, private :: history_error_putmiss = .false.
150 
151  integer, private, parameter :: history_req_limit = 1000
152  character(len=File_HLONG), private :: history_req_basename(history_req_limit)
153  character(len=File_HSHORT), private :: history_req_item (history_req_limit)
154  real(DP), private :: history_req_tintsec (history_req_limit)
155  integer, private :: history_req_tintstep(history_req_limit)
156  logical, private :: history_req_tavg (history_req_limit)
157  logical, private :: history_req_zinterp (history_req_limit)
158  integer, private :: history_req_dtype (history_req_limit)
159 
160  integer, private :: history_req_nmax = 0
161  integer, private :: history_id_count = 0
162  character(len=File_HSHORT), private, allocatable :: history_item (:)
163  integer, private, allocatable :: history_fid (:)
164  integer, private, allocatable :: history_vid (:)
165  real(DP), private, allocatable :: history_tintsec (:)
166  integer, private, allocatable :: history_tintstep(:)
167  logical, private, allocatable :: history_tavg (:)
168  logical, private, allocatable :: history_zinterp (:)
169  real(DP), private, allocatable :: history_varsum (:,:)
170  integer, private, allocatable :: history_size (:)
171  real(DP), private, allocatable :: history_tstart (:)
172  integer, private, allocatable :: history_tstrstep(:)
173  integer, private, allocatable :: history_tlststep(:)
174  real(DP), private, allocatable :: history_tsumsec (:)
175  logical, private, allocatable :: history_axis_written(:)
176 
177 
178  real(DP), private, parameter :: eps = 1.d-10
179  integer, private :: history_master
180  integer, private :: history_myrank
181  integer, private, allocatable :: history_rankidx(:)
182 
183  integer, private, parameter :: history_axis_limit = 100
184  integer, private :: history_axis_count = 0;
185  type(axis) :: history_axis(history_axis_limit)
186 
187  integer, private, parameter :: history_assoc_limit = 20
188  integer, private :: history_assoc_count = 0;
189  type(assoc) :: history_assoc(history_assoc_limit)
190 
191  character(LEN=LOG_LMSG), private :: message
192 
193  !-----------------------------------------------------------------------------
194 contains
195  !-----------------------------------------------------------------------------
196  subroutine historyinit( &
197  title, source, institution, & ! (in)
198  array_size, & ! (in)
199  master, myrank, rankidx, & ! (in)
200  time_start, time_interval, & ! (in)
201  time_units, time_since, & ! (in)
202  default_basename, & ! (in) optional
203  default_tinterval, default_tunit, default_taverage, & ! (in) optional
204  default_zinterp, & ! (in) optional
205  default_datatype, & ! (in) optional
206  namelist_filename, namelist_fid & ! (in) optional
207  )
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
461  end subroutine historyinit
462 
463  !-----------------------------------------------------------------------------
464  subroutine historyaddvariable( &
465  varname, &
466  dims, &
467  desc, &
468  units, &
469  now_step, &
470  id, &
471  zinterp, &
472  existed, &
473  options )
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
654  end subroutine historyaddvariable
655 
656  !-----------------------------------------------------------------------------
657  subroutine historywriteaxes
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
690  end subroutine historywriteaxes
691 
692  !-----------------------------------------------------------------------------
693  ! interface HistoryPutAxis
694  !-----------------------------------------------------------------------------
695  subroutine historyputaxissp( &
696  name, & ! (in)
697  desc, & ! (in)
698  units, & ! (in)
699  dim, & ! (in)
700  var, & ! (in)
701  dtype, & ! (in) optional
702  down ) ! (in) optional
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
756  end subroutine historyputaxissp
757  subroutine historyputaxisdp( &
758  name, & ! (in)
759  desc, & ! (in)
760  units, & ! (in)
761  dim, & ! (in)
762  var, & ! (in)
763  dtype, & ! (in) optional
764  down ) ! (in) optional
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
818  end subroutine historyputaxisdp
819 
820  !-----------------------------------------------------------------------------
823  name, & ! (in)
824  desc, & ! (in)
825  units, & ! (in)
826  dims, & ! (in)
827  var, & ! (in)
828  dtype ) ! (in) optional
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
876 
877  !-----------------------------------------------------------------------------
880  name, & ! (in)
881  desc, & ! (in)
882  units, & ! (in)
883  dims, & ! (in)
884  var, & ! (in)
885  dtype ) ! (in) optional
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
933 
934  !-----------------------------------------------------------------------------
937  name, & ! (in)
938  desc, & ! (in)
939  units, & ! (in)
940  dims, & ! (in)
941  var, & ! (in)
942  dtype ) ! (in) optional
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
990 
991  !-----------------------------------------------------------------------------
994  name, & ! (in)
995  desc, & ! (in)
996  units, & ! (in)
997  dims, & ! (in)
998  var, & ! (in)
999  dtype ) ! (in) optional
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
1047 
1048  !-----------------------------------------------------------------------------
1051  name, & ! (in)
1052  desc, & ! (in)
1053  units, & ! (in)
1054  dims, & ! (in)
1055  var, & ! (in)
1056  dtype ) ! (in) optional
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
1104 
1105  !-----------------------------------------------------------------------------
1108  name, & ! (in)
1109  desc, & ! (in)
1110  units, & ! (in)
1111  dims, & ! (in)
1112  var, & ! (in)
1113  dtype ) ! (in) optional
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
1161 
1162  !-----------------------------------------------------------------------------
1165  name, & ! (in)
1166  desc, & ! (in)
1167  units, & ! (in)
1168  dims, & ! (in)
1169  var, & ! (in)
1170  dtype ) ! (in) optional
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
1218 
1219  !-----------------------------------------------------------------------------
1222  name, & ! (in)
1223  desc, & ! (in)
1224  units, & ! (in)
1225  dims, & ! (in)
1226  var, & ! (in)
1227  dtype ) ! (in) optional
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
1275 
1276  !-----------------------------------------------------------------------------
1277  ! HistorySetTAttr
1278  subroutine historysettattr( &
1279  varname, &
1280  key, &
1281  val )
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 
1300  end subroutine historysettattr
1301 
1302  !-----------------------------------------------------------------------------
1303  ! HistoryQuery
1304  subroutine historyquery( &
1305  itemid, &
1306  step_next, &
1307  answer )
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
1324  end subroutine historyquery
1325 
1326  !-----------------------------------------------------------------------------
1327  ! interface HistoryPut(by NAME)
1328  subroutine historyput0dnamesp( &
1329  varname, &
1330  step_next, &
1331  var )
1332  implicit none
1333 
1334  character(len=*), intent(in) :: varname
1335  integer, intent(in) :: step_next
1336  real(SP), intent(in) :: var
1337 
1338  integer :: itemid, n
1339  !---------------------------------------------------------------------------
1340 
1341  ! search item id
1342  itemid = -1
1343  do n = 1, history_id_count
1344  if ( varname == history_item(n) ) then
1345  itemid = n
1346  exit
1347  endif
1348  enddo
1349 
1350  call historyput0didsp(itemid, step_next, var)
1351 
1352  return
1353  end subroutine historyput0dnamesp
1354 
1355  !-----------------------------------------------------------------------------
1356  ! interface HistoryPut(by ID)
1357  subroutine historyput0didsp( &
1358  itemid, &
1359  step_next, &
1360  var )
1361  implicit none
1362 
1363  integer, intent(in) :: itemid
1364  integer, intent(in) :: step_next
1365  real(SP), intent(in) :: var
1366 
1367  real(DP) :: dt
1368  integer :: idx
1369 
1370  intrinsic shape
1371  !---------------------------------------------------------------------------
1372 
1373  if ( itemid < 0 ) return
1374 
1375  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1376 
1377  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1378  write(message,*) 'xxx History variable was put two times before output!: ', &
1379  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1380  call log('E',message)
1381  endif
1382 
1383  if ( history_tavg(itemid) ) then
1384  idx = 1
1385  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var * dt
1386  else
1387  idx = 1
1388  history_varsum(idx,itemid) = var
1389  endif
1390 
1391  history_size(itemid) = idx
1392  history_tlststep(itemid) = step_next
1393  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1394 
1395  return
1396  end subroutine historyput0didsp
1397 
1398  !-----------------------------------------------------------------------------
1399  ! interface HistoryPut(by NAME)
1400  subroutine historyput0dnamedp( &
1401  varname, &
1402  step_next, &
1403  var )
1404  implicit none
1405 
1406  character(len=*), intent(in) :: varname
1407  integer, intent(in) :: step_next
1408  real(DP), intent(in) :: var
1409 
1410  integer :: itemid, n
1411  !---------------------------------------------------------------------------
1412 
1413  ! search item id
1414  itemid = -1
1415  do n = 1, history_id_count
1416  if ( varname == history_item(n) ) then
1417  itemid = n
1418  exit
1419  endif
1420  enddo
1421 
1422  call historyput0diddp(itemid, step_next, var)
1423 
1424  return
1425  end subroutine historyput0dnamedp
1426 
1427  !-----------------------------------------------------------------------------
1428  ! interface HistoryPut(by ID)
1429  subroutine historyput0diddp( &
1430  itemid, &
1431  step_next, &
1432  var )
1433  implicit none
1434 
1435  integer, intent(in) :: itemid
1436  integer, intent(in) :: step_next
1437  real(DP), intent(in) :: var
1438 
1439  real(DP) :: dt
1440  integer :: idx
1441 
1442  intrinsic shape
1443  !---------------------------------------------------------------------------
1444 
1445  if ( itemid < 0 ) return
1446 
1447  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1448 
1449  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1450  write(message,*) 'xxx History variable was put two times before output!: ', &
1451  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1452  call log('E',message)
1453  endif
1454 
1455  if ( history_tavg(itemid) ) then
1456  idx = 1
1457  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var * dt
1458  else
1459  idx = 1
1460  history_varsum(idx,itemid) = var
1461  endif
1462 
1463  history_size(itemid) = idx
1464  history_tlststep(itemid) = step_next
1465  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1466 
1467  return
1468  end subroutine historyput0diddp
1469 
1470  !-----------------------------------------------------------------------------
1471  ! interface HistoryPut(by NAME)
1472  subroutine historyput1dnamesp( &
1473  varname, &
1474  step_next, &
1475  var )
1476  implicit none
1477 
1478  character(len=*), intent(in) :: varname
1479  integer, intent(in) :: step_next
1480  real(SP), intent(in) :: var(:)
1481 
1482  integer :: itemid, n
1483  !---------------------------------------------------------------------------
1484 
1485  ! search item id
1486  itemid = -1
1487  do n = 1, history_id_count
1488  if ( varname == history_item(n) ) then
1489  itemid = n
1490  exit
1491  endif
1492  enddo
1493 
1494  call historyput1didsp(itemid, step_next, var)
1495 
1496  return
1497  end subroutine historyput1dnamesp
1498 
1499  !-----------------------------------------------------------------------------
1500  ! interface HistoryPut(by ID)
1501  subroutine historyput1didsp( &
1502  itemid, &
1503  step_next, &
1504  var )
1505  implicit none
1506 
1507  integer, intent(in) :: itemid
1508  integer, intent(in) :: step_next
1509  real(SP), intent(in) :: var(:)
1510 
1511  real(DP) :: dt
1512  integer :: idx
1513  integer :: ijk(1)
1514  integer :: i
1515 
1516  intrinsic shape
1517  !---------------------------------------------------------------------------
1518 
1519  if ( itemid < 0 ) return
1520 
1521  ijk = shape(var)
1522  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1523 
1524  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1525  write(message,*) 'xxx History variable was put two times before output!: ', &
1526  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1527  call log('E',message)
1528  endif
1529 
1530  if ( history_tavg(itemid) ) then
1531  do i = 1, ijk(1)
1532  idx = i
1533  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i) * dt
1534  enddo
1535  else
1536  do i = 1, ijk(1)
1537  idx = i
1538  history_varsum(idx,itemid) = var(i)
1539  enddo
1540  endif
1541 
1542  history_size(itemid) = idx
1543  history_tlststep(itemid) = step_next
1544  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1545 
1546  return
1547  end subroutine historyput1didsp
1548 
1549  !-----------------------------------------------------------------------------
1550  ! interface HistoryPut(by NAME)
1551  subroutine historyput1dnamedp( &
1552  varname, &
1553  step_next, &
1554  var )
1555  implicit none
1556 
1557  character(len=*), intent(in) :: varname
1558  integer, intent(in) :: step_next
1559  real(DP), intent(in) :: var(:)
1560 
1561  integer :: itemid, n
1562  !---------------------------------------------------------------------------
1563 
1564  ! search item id
1565  itemid = -1
1566  do n = 1, history_id_count
1567  if ( varname == history_item(n) ) then
1568  itemid = n
1569  exit
1570  endif
1571  enddo
1572 
1573  call historyput1diddp(itemid, step_next, var)
1574 
1575  return
1576  end subroutine historyput1dnamedp
1577 
1578  !-----------------------------------------------------------------------------
1579  ! interface HistoryPut(by ID)
1580  subroutine historyput1diddp( &
1581  itemid, &
1582  step_next, &
1583  var )
1584  implicit none
1585 
1586  integer, intent(in) :: itemid
1587  integer, intent(in) :: step_next
1588  real(DP), intent(in) :: var(:)
1589 
1590  real(DP) :: dt
1591  integer :: idx
1592  integer :: ijk(1)
1593  integer :: i
1594 
1595  intrinsic shape
1596  !---------------------------------------------------------------------------
1597 
1598  if ( itemid < 0 ) return
1599 
1600  ijk = shape(var)
1601  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1602 
1603  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1604  write(message,*) 'xxx History variable was put two times before output!: ', &
1605  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1606  call log('E',message)
1607  endif
1608 
1609  if ( history_tavg(itemid) ) then
1610  do i = 1, ijk(1)
1611  idx = i
1612  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i) * dt
1613  enddo
1614  else
1615  do i = 1, ijk(1)
1616  idx = i
1617  history_varsum(idx,itemid) = var(i)
1618  enddo
1619  endif
1620 
1621  history_size(itemid) = idx
1622  history_tlststep(itemid) = step_next
1623  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1624 
1625  return
1626  end subroutine historyput1diddp
1627 
1628  !-----------------------------------------------------------------------------
1629  ! interface HistoryPut(by NAME)
1630  subroutine historyput2dnamesp( &
1631  varname, &
1632  step_next, &
1633  var )
1634  implicit none
1635 
1636  character(len=*), intent(in) :: varname
1637  integer, intent(in) :: step_next
1638  real(SP), intent(in) :: var(:,:)
1639 
1640  integer :: itemid, n
1641  !---------------------------------------------------------------------------
1642 
1643  ! search item id
1644  itemid = -1
1645  do n = 1, history_id_count
1646  if ( varname == history_item(n) ) then
1647  itemid = n
1648  exit
1649  endif
1650  enddo
1651 
1652  call historyput2didsp(itemid, step_next, var)
1653 
1654  return
1655  end subroutine historyput2dnamesp
1656 
1657  !-----------------------------------------------------------------------------
1658  ! interface HistoryPut(by ID)
1659  subroutine historyput2didsp( &
1660  itemid, &
1661  step_next, &
1662  var )
1663  implicit none
1664 
1665  integer, intent(in) :: itemid
1666  integer, intent(in) :: step_next
1667  real(SP), intent(in) :: var(:,:)
1668 
1669  real(DP) :: dt
1670  integer :: idx
1671  integer :: ijk(2)
1672  integer :: i, j
1673 
1674  intrinsic shape
1675  !---------------------------------------------------------------------------
1676 
1677  if ( itemid < 0 ) return
1678 
1679  ijk = shape(var)
1680  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1681 
1682  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1683  write(message,*) 'xxx History variable was put two times before output!: ', &
1684  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1685  call log('E',message)
1686  endif
1687 
1688  if ( history_tavg(itemid) ) then
1689  do j = 1, ijk(2)
1690  do i = 1, ijk(1)
1691  idx = j*ijk(i)+i
1692  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j) * dt
1693  enddo
1694  enddo
1695  else
1696  do j = 1, ijk(2)
1697  do i = 1, ijk(1)
1698  idx = j*ijk(i)+i
1699  history_varsum(idx,itemid) = var(i,j)
1700  enddo
1701  enddo
1702  endif
1703 
1704  history_size(itemid) = idx
1705  history_tlststep(itemid) = step_next
1706  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1707 
1708  return
1709  end subroutine historyput2didsp
1710 
1711  !-----------------------------------------------------------------------------
1712  ! interface HistoryPut(by NAME)
1713  subroutine historyput2dnamedp( &
1714  varname, &
1715  step_next, &
1716  var )
1717  implicit none
1718 
1719  character(len=*), intent(in) :: varname
1720  integer, intent(in) :: step_next
1721  real(DP), intent(in) :: var(:,:)
1722 
1723  integer :: itemid, n
1724  !---------------------------------------------------------------------------
1725 
1726  ! search item id
1727  itemid = -1
1728  do n = 1, history_id_count
1729  if ( varname == history_item(n) ) then
1730  itemid = n
1731  exit
1732  endif
1733  enddo
1734 
1735  call historyput2diddp(itemid, step_next, var)
1736 
1737  return
1738  end subroutine historyput2dnamedp
1739 
1740  !-----------------------------------------------------------------------------
1741  ! interface HistoryPut(by ID)
1742  subroutine historyput2diddp( &
1743  itemid, &
1744  step_next, &
1745  var )
1746  implicit none
1747 
1748  integer, intent(in) :: itemid
1749  integer, intent(in) :: step_next
1750  real(DP), intent(in) :: var(:,:)
1751 
1752  real(DP) :: dt
1753  integer :: idx
1754  integer :: ijk(2)
1755  integer :: i, j
1756 
1757  intrinsic shape
1758  !---------------------------------------------------------------------------
1759 
1760  if ( itemid < 0 ) return
1761 
1762  ijk = shape(var)
1763  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1764 
1765  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1766  write(message,*) 'xxx History variable was put two times before output!: ', &
1767  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1768  call log('E',message)
1769  endif
1770 
1771  if ( history_tavg(itemid) ) then
1772  do j = 1, ijk(2)
1773  do i = 1, ijk(1)
1774  idx = j*ijk(i)+i
1775  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j) * dt
1776  enddo
1777  enddo
1778  else
1779  do j = 1, ijk(2)
1780  do i = 1, ijk(1)
1781  idx = j*ijk(i)+i
1782  history_varsum(idx,itemid) = var(i,j)
1783  enddo
1784  enddo
1785  endif
1786 
1787  history_size(itemid) = idx
1788  history_tlststep(itemid) = step_next
1789  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1790 
1791  return
1792  end subroutine historyput2diddp
1793 
1794  !-----------------------------------------------------------------------------
1795  ! interface HistoryPut(by NAME)
1796  subroutine historyput3dnamesp( &
1797  varname, &
1798  step_next, &
1799  var )
1800  implicit none
1801 
1802  character(len=*), intent(in) :: varname
1803  integer, intent(in) :: step_next
1804  real(SP), intent(in) :: var(:,:,:)
1805 
1806  integer :: itemid, n
1807  !---------------------------------------------------------------------------
1808 
1809  ! search item id
1810  itemid = -1
1811  do n = 1, history_id_count
1812  if ( varname == history_item(n) ) then
1813  itemid = n
1814  exit
1815  endif
1816  enddo
1817 
1818  call historyput3didsp(itemid, step_next, var)
1819 
1820  return
1821  end subroutine historyput3dnamesp
1822 
1823  !-----------------------------------------------------------------------------
1824  ! interface HistoryPut(by ID)
1825  subroutine historyput3didsp( &
1826  itemid, &
1827  step_next, &
1828  var )
1829  implicit none
1830 
1831  integer, intent(in) :: itemid
1832  integer, intent(in) :: step_next
1833  real(SP), intent(in) :: var(:,:,:)
1834 
1835  real(DP) :: dt
1836  integer :: idx
1837  integer :: ijk(3)
1838  integer :: i, j, k
1839 
1840  intrinsic shape
1841  !---------------------------------------------------------------------------
1842 
1843  if ( itemid < 0 ) return
1844 
1845  ijk = shape(var)
1846  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1847 
1848  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1849  write(message,*) 'xxx History variable was put two times before output!: ', &
1850  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1851  call log('E',message)
1852  endif
1853 
1854  if ( history_tavg(itemid) ) then
1855  do k = 1, ijk(3)
1856  do j = 1, ijk(2)
1857  do i = 1, ijk(1)
1858  idx = (k*ijk(2)+j)*ijk(1)+i
1859  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j,k) * dt
1860  enddo
1861  enddo
1862  enddo
1863  else
1864  do k = 1, ijk(3)
1865  do j = 1, ijk(2)
1866  do i = 1, ijk(1)
1867  idx = (k*ijk(2)+j)*ijk(1)+i
1868  history_varsum(idx,itemid) = var(i,j,k)
1869  enddo
1870  enddo
1871  enddo
1872  endif
1873 
1874  history_size(itemid) = idx
1875  history_tlststep(itemid) = step_next
1876  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1877 
1878  return
1879  end subroutine historyput3didsp
1880 
1881  !-----------------------------------------------------------------------------
1882  ! interface HistoryPut(by NAME)
1883  subroutine historyput3dnamedp( &
1884  varname, &
1885  step_next, &
1886  var )
1887  implicit none
1888 
1889  character(len=*), intent(in) :: varname
1890  integer, intent(in) :: step_next
1891  real(DP), intent(in) :: var(:,:,:)
1892 
1893  integer :: itemid, n
1894  !---------------------------------------------------------------------------
1895 
1896  ! search item id
1897  itemid = -1
1898  do n = 1, history_id_count
1899  if ( varname == history_item(n) ) then
1900  itemid = n
1901  exit
1902  endif
1903  enddo
1904 
1905  call historyput3diddp(itemid, step_next, var)
1906 
1907  return
1908  end subroutine historyput3dnamedp
1909 
1910  !-----------------------------------------------------------------------------
1911  ! interface HistoryPut(by ID)
1912  subroutine historyput3diddp( &
1913  itemid, &
1914  step_next, &
1915  var )
1916  implicit none
1917 
1918  integer, intent(in) :: itemid
1919  integer, intent(in) :: step_next
1920  real(DP), intent(in) :: var(:,:,:)
1921 
1922  real(DP) :: dt
1923  integer :: idx
1924  integer :: ijk(3)
1925  integer :: i, j, k
1926 
1927  intrinsic shape
1928  !---------------------------------------------------------------------------
1929 
1930  if ( itemid < 0 ) return
1931 
1932  ijk = shape(var)
1933  dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
1934 
1935  if ( dt < eps .AND. ( .NOT. history_tavg(itemid) ) ) then
1936  write(message,*) 'xxx History variable was put two times before output!: ', &
1937  trim(history_item(itemid)), step_next, history_tlststep(itemid)
1938  call log('E',message)
1939  endif
1940 
1941  if ( history_tavg(itemid) ) then
1942  do k = 1, ijk(3)
1943  do j = 1, ijk(2)
1944  do i = 1, ijk(1)
1945  idx = (k*ijk(2)+j)*ijk(1)+i
1946  history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j,k) * dt
1947  enddo
1948  enddo
1949  enddo
1950  else
1951  do k = 1, ijk(3)
1952  do j = 1, ijk(2)
1953  do i = 1, ijk(1)
1954  idx = (k*ijk(2)+j)*ijk(1)+i
1955  history_varsum(idx,itemid) = var(i,j,k)
1956  enddo
1957  enddo
1958  enddo
1959  endif
1960 
1961  history_size(itemid) = idx
1962  history_tlststep(itemid) = step_next
1963  history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1964 
1965  return
1966  end subroutine historyput3diddp
1967 
1968  !-----------------------------------------------------------------------------
1969  ! HistoryWrite
1970  subroutine historywrite( &
1971  itemid, &
1972  step_now )
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
2050  end subroutine historywrite
2051 
2052  !-----------------------------------------------------------------------------
2053  ! HistoryWritaAll
2054  subroutine historywriteall( &
2055  step_now )
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
2072  end subroutine historywriteall
2073 
2074  !-----------------------------------------------------------------------------
2075  ! interface HistoryGet
2076  subroutine historyget1ddp( &
2077  var, &
2078  basename, &
2079  varname, &
2080  step, &
2081  allow_missing, &
2082  single )
2083  use gtool_file, only: &
2084  fileread
2085  implicit none
2086 
2087  real(DP), intent(out) :: var(:)
2088  character(len=*), intent(in) :: basename
2089  character(len=*), intent(in) :: varname
2090  integer, intent(in) :: step
2091  logical, intent(in), optional :: allow_missing
2092  logical, intent(in), optional :: single
2093  !---------------------------------------------------------------------------
2094 
2095  call fileread( var, & ! [OUT]
2096  basename, & ! [IN]
2097  varname, & ! [IN]
2098  step, & ! [IN]
2099  history_myrank, & ! [IN]
2100  allow_missing, & ! [IN]
2101  single ) ! [IN]
2102 
2103  return
2104  end subroutine historyget1ddp
2105 
2106  !-----------------------------------------------------------------------------
2107  ! interface HistoryGet
2108  subroutine historyget1dsp( &
2109  var, &
2110  basename, &
2111  varname, &
2112  step, &
2113  allow_missing, &
2114  single )
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
2136  end subroutine historyget1dsp
2137 
2138  !-----------------------------------------------------------------------------
2139  ! interface HistoryGet
2140  subroutine historyget2ddp( &
2141  var, &
2142  basename, &
2143  varname, &
2144  step, &
2145  allow_missing, &
2146  single )
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
2168  end subroutine historyget2ddp
2169 
2170  !-----------------------------------------------------------------------------
2171  ! interface HistoryGet
2172  subroutine historyget2dsp( &
2173  var, &
2174  basename, &
2175  varname, &
2176  step, &
2177  allow_missing, &
2178  single )
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
2200  end subroutine historyget2dsp
2201 
2202  !-----------------------------------------------------------------------------
2203  ! interface HistoryGet
2204  subroutine historyget3ddp( &
2205  var, &
2206  basename, &
2207  varname, &
2208  step, &
2209  allow_missing, &
2210  single )
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
2232  end subroutine historyget3ddp
2233 
2234  !-----------------------------------------------------------------------------
2235  ! interface HistoryGet
2236  subroutine historyget3dsp( &
2237  var, &
2238  basename, &
2239  varname, &
2240  step, &
2241  allow_missing, &
2242  single )
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
2264  end subroutine historyget3dsp
2265 
2266  !-----------------------------------------------------------------------------
2267  subroutine historyoutputlist
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
2294  end subroutine historyoutputlist
2295 
2296  !-----------------------------------------------------------------------------
2297  subroutine historyfinalize
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
2310  end subroutine historyfinalize
2311 
2312 end module gtool_history
2313 !-------------------------------------------------------------------------------
2314 
2315 
2316 
2317 !--
2318 ! vi:set readonly sw=4 ts=8
2319 !
2320 !Local Variables:
2321 !mode: f90
2322 !buffer-read-only:t
2323 !End:
2324 !
2325 !++
subroutine historyput2dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
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 historyget3ddp(var, basename, varname, step, allow_missing, single)
subroutine historyput1dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
module TIME
Definition: dc_calendar.f90:17
module DC_Log
Definition: dc_log.f90:14
integer, parameter, public file_hlong
subroutine historyput2dassociatedcoordinatessp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine, public fileenddef(fid)
integer, parameter, public file_hmid
subroutine historyput3dassociatedcoordinatessp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine historyget3dsp(var, basename, varname, step, allow_missing, single)
subroutine, public historywriteaxes
subroutine, public historywrite(itemid, step_now)
module Gtool_History
subroutine historyget1dsp(var, basename, varname, step, allow_missing, single)
subroutine, public fileclose(fid)
subroutine historyput4dassociatedcoordinatessp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine, public filedefassociatedcoordinates(fid, name, desc, units, dim_names, dtype)
Definition: gtool_file.f90:869
integer, parameter, public dp
Definition: dc_types.f90:27
subroutine historyput1dassociatedcoordinatessp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine, public filesettattr(fid, vname, key, val)
subroutine, public filesetoption(fid, filetype, key, val)
Definition: gtool_file.f90:453
subroutine, public historyfinalize
subroutine, public historyaddvariable(varname, dims, desc, units, now_step, id, zinterp, existed, options)
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 log(type, message)
Definition: dc_log.f90:133
subroutine historyget2ddp(var, basename, varname, step, allow_missing, single)
integer, dimension(0:3), parameter, public file_preclist
subroutine, public historyoutputlist
subroutine historyput3dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
integer, parameter, public sp
Definition: dc_types.f90:30
subroutine historyput4dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine, public historywriteall(step_now)
integer, parameter, public file_real4
subroutine historyputaxisdp(name, desc, units, dim, var, dtype, down)
module FILE I/O HEADER
integer, parameter, public file_hshort
subroutine historyget2dsp(var, basename, varname, step, allow_missing, single)
subroutine, public historyquery(itemid, step_next, answer)
integer, parameter, public file_real8
subroutine, public historysettattr(varname, key, val)
subroutine, public filedefaxis(fid, name, desc, units, dim_name, dtype, dim_size)
Definition: gtool_file.f90:564
subroutine historyputaxissp(name, desc, units, dim, var, dtype, down)