24 #if defined(__pgi) || defined(__es2)
44 public :: historyputaxis
45 public :: historyputassociatedcoordinates
56 interface historyputaxis
59 end interface historyputaxis
61 interface historyputassociatedcoordinates
70 end interface historyputassociatedcoordinates
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
93 module procedure historyget1ddp
98 end interface historyget
101 character(len=File_HSHORT) :: name
102 character(len=File_HLONG) :: desc
103 character(len=File_HSHORT) :: units
104 character(len=File_HSHORT) :: dim
108 real(DP),
pointer :: var(:)
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)
120 real(DP),
pointer :: var(:)
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
147 logical,
private :: history_output_step0 = .false.
148 real(DP),
private :: history_output_start = 0.0_dp
149 logical,
private :: history_error_putmiss = .false.
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)
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(:)
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(:)
183 integer,
private,
parameter :: history_axis_limit = 100
184 integer,
private :: history_axis_count = 0;
185 type(axis) :: history_axis(history_axis_limit)
187 integer,
private,
parameter :: history_assoc_limit = 20
188 integer,
private :: history_assoc_count = 0;
189 type(assoc) :: history_assoc(history_assoc_limit)
191 character(LEN=LOG_LMSG),
private :: message
197 title, source, institution, & ! (in)
199 master, myrank, rankidx, &
200 time_start, time_interval, &
201 time_units, time_since, &
203 default_tinterval, default_tunit, default_taverage, &
206 namelist_filename, namelist_fid &
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
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' 243 namelist / param_history / &
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
258 character(len=File_HLONG) :: BASENAME
259 character(len=File_HSHORT) :: ITEM
260 real(DP) :: TINTERVAL
261 character(len=File_HSHORT) :: TUNIT
264 character(len=File_HSHORT) :: DATATYPE
266 namelist / histitem / &
285 call log(
'I',
'+++ Module[HISTORY]/Categ[IO]')
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
296 history_time_units =
'seconds' 298 if (
present(time_since) )
then 299 history_time_since = time_since
301 history_time_since =
'' 303 if (
present(default_basename) )
then 304 history_default_basename = default_basename
306 if (
present(default_tinterval) )
then 307 history_default_tinterval = default_tinterval
308 if (
present(default_tunit) )
then 309 history_default_tunit = default_tunit
312 if (
present(default_taverage) )
then 313 history_default_taverage = default_taverage
315 if (
present(default_zinterp) )
then 316 history_default_zinterp = default_zinterp
318 if (
present(default_datatype) )
then 319 history_default_datatype = default_datatype
322 if (
present(namelist_fid) )
then 323 fid_conf = namelist_fid
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)
330 call log(
'I',
'*** Brank namelist file was specified. Default used. ***')
334 call log(
'I',
'*** No namelist was specified. Default used. ***')
338 if ( fid_conf > 0 )
then 339 read(fid_conf, nml=param_history, iostat=ierr)
342 call log(
'I',
'*** Not found namelist. Default used.')
343 elseif( ierr > 0 )
then 344 call log(
'E',
'xxx Not appropriate names in namelist PARAM_HISTORY. Check!')
346 #if defined(__PGI) || defined(__ES2) 347 write(log_fid,nml=param_history)
349 write(message,nml=param_history)
350 call log(
'I',message)
356 if ( fid_conf > 0 )
then 358 do n = 1, history_req_limit
359 basename = history_default_basename
360 read(fid_conf, nml=histitem, iostat=ierr)
362 if( basename /=
"" ) history_req_nmax = history_req_nmax + 1
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.')
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) )
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) )
389 allocate( history_axis_written(history_req_nmax) )
391 if ( fid_conf > 0 ) rewind(fid_conf)
394 do n = 1, history_req_limit
396 basename = history_default_basename
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
404 if ( fid_conf > 0 )
then 405 read(fid_conf, nml=histitem,iostat=ierr)
409 if ( basename ==
"" ) cycle
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 )
417 history_req_tavg(ni) = taverage
418 history_req_zinterp(ni) = zinterp
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)
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)
431 if ( datatype ==
'REAL4' )
then 433 elseif( datatype ==
'REAL8' )
then 436 write(message,*)
'xxx Not appropriate DATATYPE. Check!', datatype
437 call log(
'E',message)
440 memsize = memsize + array_size *
file_preclist(history_req_dtype(ni))
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)
450 if ( (.not.
present(namelist_fid)) )
then 451 if ( fid_conf > 0 )
close(fid_conf)
454 history_master = master
455 history_myrank = myrank
457 allocate( history_rankidx(
size(rankidx)) )
458 history_rankidx(:) = rankidx(:)
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
493 character(len=File_HMID) :: tunits
495 logical :: fileexisted
496 integer :: nmax, reqid
498 integer :: ic, ie, is, lo
507 nmax = min( history_id_count, history_req_nmax )
509 if ( varname == history_item(n) )
then 511 zinterp = history_zinterp(n)
520 if ( history_time_since ==
'' )
then 521 tunits = history_time_units
523 tunits = trim(history_time_units)//
' since '//trim(history_time_since)
526 do n = 1, history_req_nmax
527 if ( varname == history_req_item(n) )
then 529 if( history_req_basename(reqid) ==
'' )
exit 530 history_id_count = history_id_count + 1
531 id = history_id_count
535 trim(history_req_basename(reqid)), &
538 history_institution, &
542 time_units = tunits )
544 if ( .not. fileexisted )
then 546 if (
present(options) )
then 550 lo = len_trim(options)
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))
558 options(ic+1:ie-1), options(ie+1:m-1) )
562 elseif( options(m:m) ==
':' )
then 564 elseif( options(m:m) ==
'=' )
then 571 do m = 1, history_axis_count
572 history_axis(m)%id = id
574 history_axis(m)%name, history_axis(m)%desc, &
575 history_axis(m)%units, history_axis(m)%dim, &
576 history_axis(m)%type, history_axis(m)%dim_size )
579 do m = 1, history_assoc_count
580 history_assoc(m)%id = id
582 history_assoc(m)%name, history_assoc(m)%desc, &
583 history_assoc(m)%units, &
584 history_assoc(m)%dims(1:history_assoc(m)%ndims), &
585 history_assoc(m)%type )
587 history_axis_written(id) = .false.
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)
597 history_varsum(:,id) = 0.d0
599 if ( history_output_step0 .and. now_step==1 )
then 600 history_tstrstep(id) = 1 - history_tintstep(id)
602 history_tstrstep(id) = 1
604 if ( history_output_start > 0.0_dp )
then 605 history_tstart(id) = history_startdaysec + history_output_start
607 history_tstart(id) = history_startdaysec
609 history_tlststep(id) = history_tstrstep(id)
610 history_tsumsec(id) = 0.d0
612 call fileaddvariable( history_vid(id), &
614 varname, desc, units, dims, &
615 history_req_dtype(reqid), &
616 history_tintsec(id), &
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" )
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)
645 zinterp = history_zinterp(id)
661 filewriteassociatedcoordinates
667 if ( history_req_nmax == 0 )
return 670 if ( history_axis_written(history_axis(1)%id) )
return 672 call fileenddef( history_fid(history_axis(1)%id) )
675 do m = 1, history_axis_count
676 call filewriteaxis( history_fid(history_axis(m)%id), &
677 history_axis(m)%name, &
678 history_axis(m)%var )
681 do m = 1, history_assoc_count
682 call filewriteassociatedcoordinates( history_fid(history_assoc(m)%id), &
683 history_assoc(m)%name, &
684 history_assoc(m)%var )
687 history_axis_written(history_axis(1)%id) = .true.
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
719 if (
present(dtype) )
then 720 if ( dtype ==
'REAL4' )
then 722 elseif( dtype ==
'REAL8' )
then 725 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
726 call log(
'E',message)
732 if ( history_axis_count < history_axis_limit )
then 733 history_axis_count = history_axis_count + 1
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)
742 allocate(history_axis(history_axis_count)%var(
size(var)))
743 history_axis(history_axis_count)%var = var
745 if (
present(down) )
then 746 history_axis(history_axis_count)%down = down
748 history_axis(history_axis_count)%down = .false.
751 write(message,*)
'xxx Number of axis exceeds the limit.' 752 call log(
'E',message)
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
781 if (
present(dtype) )
then 782 if ( dtype ==
'REAL4' )
then 784 elseif( dtype ==
'REAL8' )
then 787 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
788 call log(
'E',message)
794 if ( history_axis_count < history_axis_limit )
then 795 history_axis_count = history_axis_count + 1
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)
804 allocate(history_axis(history_axis_count)%var(
size(var)))
805 history_axis(history_axis_count)%var = var
807 if (
present(down) )
then 808 history_axis(history_axis_count)%down = down
810 history_axis(history_axis_count)%down = .false.
813 write(message,*)
'xxx Number of axis exceeds the limit.' 814 call log(
'E',message)
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
844 if (
present(dtype) )
then 845 if ( dtype ==
'REAL4' )
then 847 elseif( dtype ==
'REAL8' )
then 850 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
851 call log(
'E',message)
857 if ( history_assoc_count < history_assoc_limit )
then 858 history_assoc_count = history_assoc_count + 1
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 867 allocate(history_assoc(history_assoc_count)%var(
size(var)))
868 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
870 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 871 call log(
'E',message)
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
901 if (
present(dtype) )
then 902 if ( dtype ==
'REAL4' )
then 904 elseif( dtype ==
'REAL8' )
then 907 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
908 call log(
'E',message)
914 if ( history_assoc_count < history_assoc_limit )
then 915 history_assoc_count = history_assoc_count + 1
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 924 allocate(history_assoc(history_assoc_count)%var(
size(var)))
925 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
927 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 928 call log(
'E',message)
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
958 if (
present(dtype) )
then 959 if ( dtype ==
'REAL4' )
then 961 elseif( dtype ==
'REAL8' )
then 964 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
965 call log(
'E',message)
971 if ( history_assoc_count < history_assoc_limit )
then 972 history_assoc_count = history_assoc_count + 1
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 981 allocate(history_assoc(history_assoc_count)%var(
size(var)))
982 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
984 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 985 call log(
'E',message)
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
1015 if (
present(dtype) )
then 1016 if ( dtype ==
'REAL4' )
then 1018 elseif( dtype ==
'REAL8' )
then 1021 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
1022 call log(
'E',message)
1028 if ( history_assoc_count < history_assoc_limit )
then 1029 history_assoc_count = history_assoc_count + 1
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 1038 allocate(history_assoc(history_assoc_count)%var(
size(var)))
1039 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
1041 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 1042 call log(
'E',message)
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
1072 if (
present(dtype) )
then 1073 if ( dtype ==
'REAL4' )
then 1075 elseif( dtype ==
'REAL8' )
then 1078 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
1079 call log(
'E',message)
1085 if ( history_assoc_count < history_assoc_limit )
then 1086 history_assoc_count = history_assoc_count + 1
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 1095 allocate(history_assoc(history_assoc_count)%var(
size(var)))
1096 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
1098 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 1099 call log(
'E',message)
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
1129 if (
present(dtype) )
then 1130 if ( dtype ==
'REAL4' )
then 1132 elseif( dtype ==
'REAL8' )
then 1135 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
1136 call log(
'E',message)
1142 if ( history_assoc_count < history_assoc_limit )
then 1143 history_assoc_count = history_assoc_count + 1
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 1152 allocate(history_assoc(history_assoc_count)%var(
size(var)))
1153 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
1155 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 1156 call log(
'E',message)
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
1186 if (
present(dtype) )
then 1187 if ( dtype ==
'REAL4' )
then 1189 elseif( dtype ==
'REAL8' )
then 1192 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
1193 call log(
'E',message)
1199 if ( history_assoc_count < history_assoc_limit )
then 1200 history_assoc_count = history_assoc_count + 1
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 1209 allocate(history_assoc(history_assoc_count)%var(
size(var)))
1210 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
1212 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 1213 call log(
'E',message)
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
1243 if (
present(dtype) )
then 1244 if ( dtype ==
'REAL4' )
then 1246 elseif( dtype ==
'REAL8' )
then 1249 write(message,*)
'xxx Not appropriate dtype. Check!', dtype
1250 call log(
'E',message)
1256 if ( history_assoc_count < history_assoc_limit )
then 1257 history_assoc_count = history_assoc_count + 1
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 1266 allocate(history_assoc(history_assoc_count)%var(
size(var)))
1267 history_assoc(history_assoc_count)%var = reshape(var, (/
size(var)/))
1269 write(message,*)
'xxx Number of associate coordinates exceeds the limit.' 1270 call log(
'E',message)
1286 character(len=*),
intent(in) :: varname
1287 character(len=*),
intent(in) :: key
1288 character(len=*),
intent(in) :: val
1293 do n = 1, history_id_count
1310 integer,
intent(in) :: itemid
1311 integer,
intent(in) :: step_next
1312 logical,
intent(out) :: answer
1317 if ( history_tavg(itemid) )
then 1319 elseif( step_next == history_tstrstep(itemid) + history_tintstep(itemid) )
then 1328 subroutine historyput0dnamesp( &
1334 character(len=*),
intent(in) :: varname
1335 integer,
intent(in) :: step_next
1336 real(SP),
intent(in) :: var
1338 integer :: itemid, n
1343 do n = 1, history_id_count
1344 if ( varname == history_item(n) )
then 1350 call historyput0didsp(itemid, step_next, var)
1353 end subroutine historyput0dnamesp
1357 subroutine historyput0didsp( &
1363 integer,
intent(in) :: itemid
1364 integer,
intent(in) :: step_next
1365 real(SP),
intent(in) :: var
1373 if ( itemid < 0 )
return 1375 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1383 if ( history_tavg(itemid) )
then 1385 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var * dt
1388 history_varsum(idx,itemid) = var
1391 history_size(itemid) = idx
1392 history_tlststep(itemid) = step_next
1393 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1396 end subroutine historyput0didsp
1400 subroutine historyput0dnamedp( &
1406 character(len=*),
intent(in) :: varname
1407 integer,
intent(in) :: step_next
1408 real(DP),
intent(in) :: var
1410 integer :: itemid, n
1415 do n = 1, history_id_count
1416 if ( varname == history_item(n) )
then 1422 call historyput0diddp(itemid, step_next, var)
1425 end subroutine historyput0dnamedp
1429 subroutine historyput0diddp( &
1435 integer,
intent(in) :: itemid
1436 integer,
intent(in) :: step_next
1437 real(DP),
intent(in) :: var
1445 if ( itemid < 0 )
return 1447 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1455 if ( history_tavg(itemid) )
then 1457 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var * dt
1460 history_varsum(idx,itemid) = var
1463 history_size(itemid) = idx
1464 history_tlststep(itemid) = step_next
1465 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1468 end subroutine historyput0diddp
1472 subroutine historyput1dnamesp( &
1478 character(len=*),
intent(in) :: varname
1479 integer,
intent(in) :: step_next
1480 real(SP),
intent(in) :: var(:)
1482 integer :: itemid, n
1487 do n = 1, history_id_count
1488 if ( varname == history_item(n) )
then 1494 call historyput1didsp(itemid, step_next, var)
1497 end subroutine historyput1dnamesp
1501 subroutine historyput1didsp( &
1507 integer,
intent(in) :: itemid
1508 integer,
intent(in) :: step_next
1509 real(SP),
intent(in) :: var(:)
1519 if ( itemid < 0 )
return 1522 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1530 if ( history_tavg(itemid) )
then 1533 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i) * dt
1538 history_varsum(idx,itemid) = var(i)
1542 history_size(itemid) = idx
1543 history_tlststep(itemid) = step_next
1544 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1547 end subroutine historyput1didsp
1551 subroutine historyput1dnamedp( &
1557 character(len=*),
intent(in) :: varname
1558 integer,
intent(in) :: step_next
1559 real(DP),
intent(in) :: var(:)
1561 integer :: itemid, n
1566 do n = 1, history_id_count
1567 if ( varname == history_item(n) )
then 1573 call historyput1diddp(itemid, step_next, var)
1576 end subroutine historyput1dnamedp
1580 subroutine historyput1diddp( &
1586 integer,
intent(in) :: itemid
1587 integer,
intent(in) :: step_next
1588 real(DP),
intent(in) :: var(:)
1598 if ( itemid < 0 )
return 1601 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1609 if ( history_tavg(itemid) )
then 1612 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i) * dt
1617 history_varsum(idx,itemid) = var(i)
1621 history_size(itemid) = idx
1622 history_tlststep(itemid) = step_next
1623 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1626 end subroutine historyput1diddp
1630 subroutine historyput2dnamesp( &
1636 character(len=*),
intent(in) :: varname
1637 integer,
intent(in) :: step_next
1638 real(SP),
intent(in) :: var(:,:)
1640 integer :: itemid, n
1645 do n = 1, history_id_count
1646 if ( varname == history_item(n) )
then 1652 call historyput2didsp(itemid, step_next, var)
1655 end subroutine historyput2dnamesp
1659 subroutine historyput2didsp( &
1665 integer,
intent(in) :: itemid
1666 integer,
intent(in) :: step_next
1667 real(SP),
intent(in) :: var(:,:)
1677 if ( itemid < 0 )
return 1680 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1688 if ( history_tavg(itemid) )
then 1692 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j) * dt
1699 history_varsum(idx,itemid) = var(i,j)
1704 history_size(itemid) = idx
1705 history_tlststep(itemid) = step_next
1706 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1709 end subroutine historyput2didsp
1713 subroutine historyput2dnamedp( &
1719 character(len=*),
intent(in) :: varname
1720 integer,
intent(in) :: step_next
1721 real(DP),
intent(in) :: var(:,:)
1723 integer :: itemid, n
1728 do n = 1, history_id_count
1729 if ( varname == history_item(n) )
then 1735 call historyput2diddp(itemid, step_next, var)
1738 end subroutine historyput2dnamedp
1742 subroutine historyput2diddp( &
1748 integer,
intent(in) :: itemid
1749 integer,
intent(in) :: step_next
1750 real(DP),
intent(in) :: var(:,:)
1760 if ( itemid < 0 )
return 1763 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1771 if ( history_tavg(itemid) )
then 1775 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j) * dt
1782 history_varsum(idx,itemid) = var(i,j)
1787 history_size(itemid) = idx
1788 history_tlststep(itemid) = step_next
1789 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1792 end subroutine historyput2diddp
1796 subroutine historyput3dnamesp( &
1802 character(len=*),
intent(in) :: varname
1803 integer,
intent(in) :: step_next
1804 real(SP),
intent(in) :: var(:,:,:)
1806 integer :: itemid, n
1811 do n = 1, history_id_count
1812 if ( varname == history_item(n) )
then 1818 call historyput3didsp(itemid, step_next, var)
1821 end subroutine historyput3dnamesp
1825 subroutine historyput3didsp( &
1831 integer,
intent(in) :: itemid
1832 integer,
intent(in) :: step_next
1833 real(SP),
intent(in) :: var(:,:,:)
1843 if ( itemid < 0 )
return 1846 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1854 if ( history_tavg(itemid) )
then 1858 idx = (k*ijk(2)+j)*ijk(1)+i
1859 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j,k) * dt
1867 idx = (k*ijk(2)+j)*ijk(1)+i
1868 history_varsum(idx,itemid) = var(i,j,k)
1874 history_size(itemid) = idx
1875 history_tlststep(itemid) = step_next
1876 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1879 end subroutine historyput3didsp
1883 subroutine historyput3dnamedp( &
1889 character(len=*),
intent(in) :: varname
1890 integer,
intent(in) :: step_next
1891 real(DP),
intent(in) :: var(:,:,:)
1893 integer :: itemid, n
1898 do n = 1, history_id_count
1899 if ( varname == history_item(n) )
then 1905 call historyput3diddp(itemid, step_next, var)
1908 end subroutine historyput3dnamedp
1912 subroutine historyput3diddp( &
1918 integer,
intent(in) :: itemid
1919 integer,
intent(in) :: step_next
1920 real(DP),
intent(in) :: var(:,:,:)
1930 if ( itemid < 0 )
return 1933 dt = ( step_next - history_tlststep(itemid) ) * history_dtsec
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)
1941 if ( history_tavg(itemid) )
then 1945 idx = (k*ijk(2)+j)*ijk(1)+i
1946 history_varsum(idx,itemid) = history_varsum(idx,itemid) + var(i,j,k) * dt
1954 idx = (k*ijk(2)+j)*ijk(1)+i
1955 history_varsum(idx,itemid) = var(i,j,k)
1961 history_size(itemid) = idx
1962 history_tlststep(itemid) = step_next
1963 history_tsumsec(itemid) = history_tsumsec(itemid) + dt
1966 end subroutine historyput3diddp
1979 integer,
intent(in) :: itemid
1980 integer,
intent(in) :: step_now
1983 real(DP) :: time_str, time_end
1984 real(DP) :: sec_str, sec_end
1986 real(DP),
save :: sec_end_last = -1.0_dp
1987 logical,
save :: firsttime = .true.
1990 if( history_id_count == 0 )
return 1992 if ( step_now < history_tstrstep(itemid) + history_tintstep(itemid) )
then 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)
2002 call log(
'I',message)
2006 isize = history_size(itemid)
2008 if ( history_tavg(itemid) )
then 2009 history_varsum(1:isize,itemid) = history_varsum(1:isize,itemid) / history_tsumsec(itemid)
2012 if ( firsttime )
then 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
2021 call calendarsec2ymdhms( time_str, sec_str, history_time_units )
2022 call calendarsec2ymdhms( time_end, sec_end, history_time_units )
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)
2030 call filewrite( history_fid(itemid), &
2031 history_vid(itemid), &
2032 history_varsum(1:isize,itemid), &
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)
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
2047 sec_end_last = sec_end
2058 integer,
intent(in) :: step_now
2067 do n = 1, history_id_count
2076 subroutine historyget1ddp( &
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
2095 call fileread( var, &
2104 end subroutine historyget1ddp
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
2127 call fileread( var, &
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
2159 call fileread( var, &
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
2191 call fileread( var, &
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
2223 call fileread( var, &
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
2255 call fileread( var, &
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)
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)
2289 write(message,*)
'============================================================================' 2290 call log(
'I',message)
2305 do n = 1, history_id_count
subroutine historyput2dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine historyget3ddp(var, basename, varname, step, allow_missing, single)
subroutine historyput1dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine historyput2dassociatedcoordinatessp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
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)
subroutine historyget1dsp(var, basename, varname, step, allow_missing, single)
subroutine historyput4dassociatedcoordinatessp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
integer, parameter, public dp
subroutine historyput1dassociatedcoordinatessp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
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)
subroutine historyget2ddp(var, basename, varname, step, allow_missing, single)
subroutine, public historyoutputlist
subroutine historyput3dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
integer, parameter, public sp
subroutine historyput4dassociatedcoordinatesdp(name, desc, units, dims, var, dtype)
interface HistoryPutAssociatedCoordinates
subroutine, public historywriteall(step_now)
subroutine historyputaxisdp(name, desc, units, dim, var, dtype, down)
subroutine historyget2dsp(var, basename, varname, step, allow_missing, single)
subroutine, public historyquery(itemid, step_next, answer)
subroutine, public historysettattr(varname, key, val)
subroutine historyputaxissp(name, desc, units, dim, var, dtype, down)