hstnmlinfoadd.f90
Go to the documentation of this file.
1 != 変数の出力情報の追加
2 != Add output information of a variable
3 !
4 ! Authors:: Yasuhiro MORIKAWA
5 ! Version:: $Id: hstnmlinfoadd.f90,v 1.2 2009-10-10 10:59:01 morikawa Exp $
6 ! Tag Name:: $Name: $
7 ! Copyright:: Copyright (C) GFD Dennou Club, 2007-2009. All rights reserved.
8 ! License:: See COPYRIGHT[link:../../../COPYRIGHT]
9 !
10  recursive subroutine hstnmlinfoadd( gthstnml, &
11  & name, file, &
12  & interval_value, interval_unit, &
13  & precision, &
14  & time_average, average, &
15  & fileprefix, &
16  & origin_value, origin_unit, &
17  & terminus_value, terminus_unit, &
18  & slice_start, slice_end, slice_stride, &
19  & space_average, &
20  & newfile_intvalue, newfile_intunit, &
21  & err )
22  !
23  ! 変数の出力情報を加えます.
24  !
25  ! デフォルト値を設定するには, *name* を与えないか, または
26  ! *name* に空白を与えてください.
27  ! デフォルト値を与える場合, *file* に与えられる情報は無視されます.
28  ! *fileprefix* はデフォルト値に与える場合のみ有効です.
29  !
30  ! *name* に変数名が指定され, その際に *file* が与えられない,
31  ! または空白が与えられる場合, *file* には
32  ! "<i><*name* に与えられた文字></i>.nc" が指定されます.
33  !
34  ! なお, 与えられた *gthstnml* が HstNmlInfoCreate によって初期設定
35  ! されていない場合, プログラムはエラーを発生させます.
36  !
37  ! Add output information of a variable.
38  !
39  ! In order to set default values, specify blank to *name* or
40  ! do not specify *name*.
41  ! When default values are specified, *file* is ignored.
42  ! *fileprefix* is valid only when default values are specified.
43  !
44  ! When a variable identifier is specified to *name* and
45  ! *file* is not specified or blanks are specified to *file*,
46  ! "<i><string given to *name*></i>.nc" is specified to *file*.
47  !
48  ! If *gthstnml* is not initialized by "HstNmlInfoCreate" yet,
49  ! error is occurred.
50  !
55  use dc_trace, only: beginsub, endsub, dbgmessage
58  use dc_types, only: dp, string, token, stdout
59  use dc_date_types, only: dc_difftime
60  use dc_date, only: dcdifftimecreate, operator(>), operator(<)
61  use dc_message, only: messagenotify
64  use netcdf, only: nf90_max_dims
65  implicit none
66  type(gthst_nmlinfo), intent(inout):: gthstnml
67  character(*), intent(in), optional:: name
68  ! 変数名.
69  !
70  ! 先頭の空白は無視されます.
71  !
72  ! "Data1,Data2" のようにカンマで区切って複数
73  ! の変数を指定することも可能です.
74  !--
75  ! ただし,
76  ! その際には, *file* 引数で与えられる情報は
77  ! 無視されます. その他の情報はそれぞれの
78  ! 変数の情報として設定されます.
79  !++
80  !
81  ! Variable identifier.
82  !
83  ! Blanks at the head of the name are ignored.
84  !
85  ! Multiple variables can be specified
86  ! as "Data1,Data2" too. Delimiter is comma.
87  !--
88  ! In this case, *file* is ignored, and
89  ! other information is set to each variable.
90  !++
91  !
92  character(*), intent(in), optional:: file
93  ! ヒストリデータのファイル名.
94  ! History data filenames
95  real(DP), intent(in), optional:: interval_value
96  ! ヒストリデータの出力間隔の数値.
97  ! 負の値を与えると, 出力を抑止します.
98  !
99  ! Numerical value for interval of history data output.
100  ! Negative values suppresses output.
101  character(*), intent(in), optional:: interval_unit
102  ! ヒストリデータの出力間隔の単位.
103  ! Unit for interval of history data output
104  character(*), intent(in), optional:: precision
105  ! ヒストリデータの精度.
106  ! Precision of history data
107  logical, intent(in), optional:: time_average
108  ! 出力データの時間平均化フラグ.
109  ! Flag for time average of output data.
110  logical, intent(in), optional:: average
111  ! time_average の旧版.
112  ! Old version of "time_average"
113  character(*), intent(in), optional:: fileprefix
114  ! ヒストリデータのファイル名の接頭詞.
115  ! Prefixes of history data filenames
116  real(DP), intent(in), optional:: origin_value
117  ! 出力開始時刻.
118  ! Start time of output.
119  character(*), intent(in), optional:: origin_unit
120  ! 出力開始時刻の単位.
121  ! Unit of start time of output.
122  real(DP), intent(in), optional:: terminus_value
123  ! 出力終了時刻.
124  ! End time of output.
125  character(*), intent(in), optional:: terminus_unit
126  ! 出力終了時刻の単位.
127  ! Unit of end time of output.
128  integer, intent(in), optional:: slice_start(:)
129  ! 空間方向の開始点.
130  ! Start points of spaces.
131  integer, intent(in), optional:: slice_end(:)
132  ! 空間方向の終了点.
133  ! End points of spaces.
134  integer, intent(in), optional:: slice_stride(:)
135  ! 空間方向の刻み幅.
136  ! Strides of spaces.
137  logical, intent(in), optional:: space_average(:)
138  ! 平均化のフラグ.
139  ! Flag of average.
140  integer, intent(in), optional:: newfile_intvalue
141  ! ファイル分割時間間隔.
142  ! Interval of time of separation of a file.
143  character(*), intent(in), optional:: newfile_intunit
144  ! ファイル分割時間間隔の単位.
145  ! Unit of interval of time of separation of a file.
146  logical, intent(out), optional:: err
147  ! 例外処理用フラグ.
148  ! デフォルトでは, この手続き内でエラーが
149  ! 生じた場合, プログラムは強制終了します.
150  ! 引数 *err* が与えられる場合,
151  ! プログラムは強制終了せず, 代わりに
152  ! *err* に .true. が代入されます.
153  !
154  ! Exception handling flag.
155  ! By default, when error occur in
156  ! this procedure, the program aborts.
157  ! If this *err* argument is given,
158  ! .true. is substituted to *err* and
159  ! the program does not abort.
160 
161  !-----------------------------------
162  ! 作業変数
163  ! Work variables
164  type(gthst_nmlinfo_entry), pointer:: hptr =>null()
165  type(gthst_nmlinfo_entry), pointer:: hptr_last =>null()
166  type(dc_difftime):: interval_time, newfileint_time
167  character(TOKEN), pointer:: varnames_array(:) =>null()
168  integer:: i, vnmax, ary_size
169  integer:: stat
170  character(STRING):: cause_c
171  character(*), parameter:: subname = 'HstNmlInfoAdd'
172  continue
173  call beginsub( subname, &
174  & fmt = '@name=%a @file=%a @interval_value=%r @interval_unit=%a @precision=%a @time_average=%y @fileprefix=%a', &
175  & d = (/ present_select(.true., -1.0_dp, interval_value) /), &
176  & l = (/ present_and_true(time_average) /), &
177  & ca = stoa( present_select(.true., '<no>', name), &
178  & present_select(.true., '<no>', file), &
179  & present_select(.true., '<no>', interval_unit), &
180  & present_select(.true., '<no>', precision), &
181  & present_select(.true., '<no>', fileprefix) ) &
182  & )
183 
184  stat = dc_noerr
185  cause_c = ''
186 
187  !-----------------------------------------------------------------
188  ! 初期設定のチェック
189  ! Check initialization
190  !-----------------------------------------------------------------
191  if ( .not. gthstnml % initialized ) then
192  stat = dc_enotinit
193  cause_c = 'GTHST_NMLINFO'
194  goto 999
195  end if
196 
197  if ( .not. gthstnml % define_mode ) then
198  stat = hst_enotindefine
199  cause_c = 'Add'
200  goto 999
201  end if
202 
203  !-----------------------------------------------------------------
204  ! 複数の変数を設定する場合
205  ! Configure multiple variables
206  !-----------------------------------------------------------------
207  if ( present_and_not_empty(name) ) then
208  if ( index(name, name_delimiter) > 0 ) then
209  call dbgmessage( 'multiple entries (%c) will be created', c1 = trim(name) )
210 !!$ if ( present(file) ) call DbgMessage( 'argument @file=%c is ignored', c1 = trim(file) )
211 
212  call split( str = name, sep = name_delimiter, & ! (in)
213  & carray = varnames_array ) ! (out)
214  vnmax = size( varnames_array )
215 
216  do i = 1, vnmax
217  call hstnmlinfoadd( &
218  & gthstnml = gthstnml, & ! (inout)
219  & name = varnames_array(i), & ! (in)
220  & file = file, & ! (in)
221  & interval_value = interval_value, & ! (in)
222  & interval_unit = interval_unit, & ! (in)
223  & precision = precision, & ! (in)
224  & time_average = time_average, & ! (in)
225  & average = average, & ! (in)
226  & origin_value = origin_value, & ! (in)
227  & origin_unit = origin_unit, & ! (in)
228  & terminus_value = terminus_value, & ! (in)
229  & terminus_unit = terminus_unit, & ! (in)
230  & slice_start = slice_start, & ! (in)
231  & slice_end = slice_end, & ! (in)
232  & slice_stride = slice_stride, & ! (in)
233  & space_average = space_average, & ! (in)
234  & newfile_intvalue = newfile_intvalue, & ! (in)
235  & newfile_intunit = newfile_intunit, & ! (in)
236  & err = err ) ! (out)
237  if ( present_and_true( err ) ) then
238  deallocate( varnames_array )
239  stat = usr_errno
240  goto 999
241  end if
242  end do
243  deallocate( varnames_array )
244  goto 999
245  end if
246  end if
247 
248  !-----------------------------------------------------------------
249  ! *gthstnml* へ情報を追加.
250  ! Add information to *gthstnml*
251  !-----------------------------------------------------------------
252  if ( .not. present_and_not_empty(name) ) then
253  if ( present(interval_value) ) gthstnml % gthstnml_list % interval_value = interval_value
254  if ( present(interval_unit) ) gthstnml % gthstnml_list % interval_unit = interval_unit
255  if ( present(precision) ) gthstnml % gthstnml_list % precision = precision
256  if ( present(average) ) gthstnml % gthstnml_list % time_average = average
257  if ( present(time_average) ) gthstnml % gthstnml_list % time_average = time_average
258  if ( present(fileprefix) ) gthstnml % gthstnml_list % fileprefix = fileprefix
259 
260  if ( present(origin_value ) ) gthstnml % gthstnml_list % origin_value = origin_value
261  if ( present(origin_unit ) ) gthstnml % gthstnml_list % origin_unit = origin_unit
262  if ( present(terminus_value ) ) gthstnml % gthstnml_list % terminus_value = terminus_value
263  if ( present(terminus_unit ) ) gthstnml % gthstnml_list % terminus_unit = terminus_unit
264  if ( present(slice_start ) ) then
265  ary_size = size(slice_start)
266  gthstnml % gthstnml_list % slice_start(1:ary_size) = slice_start
267  end if
268  if ( present(slice_end ) ) then
269  ary_size = size(slice_end)
270  gthstnml % gthstnml_list % slice_end(1:ary_size) = slice_end
271  end if
272  if ( present(slice_stride ) ) then
273  ary_size = size(slice_stride)
274  gthstnml % gthstnml_list % slice_stride(1:ary_size) = slice_stride
275  end if
276  if ( present(space_average ) ) then
277  ary_size = size(space_average)
278  gthstnml % gthstnml_list % space_average(1:ary_size) = space_average
279  end if
280  if ( present(newfile_intvalue) ) gthstnml % gthstnml_list % newfile_intvalue = newfile_intvalue
281  if ( present(newfile_intunit ) ) gthstnml % gthstnml_list % newfile_intunit = newfile_intunit
282 
283 
284  hptr => gthstnml % gthstnml_list
285 
286  else
287  hptr => gthstnml % gthstnml_list
288  call listsearch( gthstnml_list = hptr, & ! (inout)
289  & name = name ) ! (in)
290  if ( .not. associated(hptr) ) then
291  call dbgmessage( 'new entry (%c) is created', c1 = trim( adjustl( name ) ) )
292 
293  hptr_last => gthstnml % gthstnml_list
294  call listlast( gthstnml_list = hptr_last ) ! (inout)
295  allocate( hptr )
296 
297  nullify( hptr % next )
298 
299  hptr % interval_value => gthstnml % gthstnml_list % interval_value
300  hptr % interval_unit => gthstnml % gthstnml_list % interval_unit
301  hptr % precision => gthstnml % gthstnml_list % precision
302  hptr % time_average => gthstnml % gthstnml_list % time_average
303  hptr % fileprefix => gthstnml % gthstnml_list % fileprefix
304 
305  hptr % origin_value => gthstnml % gthstnml_list % origin_value
306  hptr % origin_unit => gthstnml % gthstnml_list % origin_unit
307  hptr % terminus_value => gthstnml % gthstnml_list % terminus_value
308  hptr % terminus_unit => gthstnml % gthstnml_list % terminus_unit
309  hptr % slice_start => gthstnml % gthstnml_list % slice_start
310  hptr % slice_end => gthstnml % gthstnml_list % slice_end
311  hptr % slice_stride => gthstnml % gthstnml_list % slice_stride
312  hptr % space_average => gthstnml % gthstnml_list % space_average
313  hptr % newfile_intvalue => gthstnml % gthstnml_list % newfile_intvalue
314  hptr % newfile_intunit => gthstnml % gthstnml_list % newfile_intunit
315 
316  hptr_last % next => hptr
317  else
318  call dbgmessage( 'entry (%c) is overwritten', c1 = trim( adjustl( name ) ) )
319  end if
320 
321  hptr % name = adjustl( name )
322  if ( present_and_not_empty(file) ) then
323  hptr % file = file
324  nullify( hptr % fileprefix )
325  allocate( hptr % fileprefix )
326  hptr % fileprefix = ''
327  else
328  hptr % file = trim( adjustl(name) ) // '.nc'
329  end if
330 
331  if ( present(interval_value) ) then
332  nullify( hptr % interval_value )
333  allocate( hptr % interval_value )
334  hptr % interval_value = interval_value
335  end if
336  if ( present(interval_unit) ) then
337  nullify( hptr % interval_unit )
338  allocate( hptr % interval_unit )
339  hptr % interval_unit = interval_unit
340  end if
341  if ( present(precision) ) then
342  nullify( hptr % precision )
343  allocate( hptr % precision )
344  hptr % precision = precision
345  end if
346  if ( present(average) ) then
347  nullify( hptr % time_average )
348  allocate( hptr % time_average )
349  hptr % time_average = average
350  end if
351  if ( present(time_average) ) then
352  nullify( hptr % time_average )
353  allocate( hptr % time_average )
354  hptr % time_average = time_average
355  end if
356 
357  if ( present(origin_value) ) then
358  nullify( hptr % origin_value )
359  allocate( hptr % origin_value )
360  hptr % origin_value = origin_value
361  end if
362  if ( present(origin_unit) ) then
363  nullify( hptr % origin_unit )
364  allocate( hptr % origin_unit )
365  hptr % origin_unit = origin_unit
366  end if
367  if ( present(terminus_value) ) then
368  nullify( hptr % terminus_value )
369  allocate( hptr % terminus_value )
370  hptr % terminus_value = terminus_value
371  end if
372  if ( present(terminus_unit) ) then
373  nullify( hptr % terminus_unit )
374  allocate( hptr % terminus_unit )
375  hptr % terminus_unit = terminus_unit
376  end if
377  if ( present(slice_start) ) then
378  ary_size = size( slice_start )
379  nullify( hptr % slice_start )
380  allocate( hptr % slice_start(1:nf90_max_dims) )
381  hptr % slice_start = 1
382  hptr % slice_start(1:ary_size) = slice_start
383  end if
384  if ( present(slice_end) ) then
385  ary_size = size( slice_end )
386  nullify( hptr % slice_end )
387  allocate( hptr % slice_end(1:nf90_max_dims) )
388  hptr % slice_end = -1
389  hptr % slice_end(1:ary_size) = slice_end
390  end if
391  if ( present(slice_stride) ) then
392  ary_size = size( slice_stride )
393  nullify( hptr % slice_stride )
394  allocate( hptr % slice_stride(1:nf90_max_dims) )
395  hptr % slice_stride = 1
396  hptr % slice_stride(1:ary_size) = slice_stride
397  end if
398  if ( present(space_average) ) then
399  ary_size = size( space_average )
400  nullify( hptr % space_average )
401  allocate( hptr % space_average(1:nf90_max_dims) )
402  hptr % space_average = .false.
403  hptr % space_average(1:ary_size) = space_average
404  end if
405  if ( present(newfile_intvalue) ) then
406  nullify( hptr % newfile_intvalue )
407  allocate( hptr % newfile_intvalue )
408  hptr % newfile_intvalue = newfile_intvalue
409  end if
410  if ( present(newfile_intunit) ) then
411  nullify( hptr % newfile_intunit )
412  allocate( hptr % newfile_intunit )
413  hptr % newfile_intunit = newfile_intunit
414  end if
415 
416  end if
417 
418  !---------------------------------------------------------------
419  ! 時間の単位のチェック
420  ! Check unit of time
421  !---------------------------------------------------------------
422  call dcdifftimecreate( &
423  & diff = interval_time, & ! (out)
424  & value = hptr % interval_value, & ! (in)
425  & unit = hptr % interval_unit, & ! (in)
426  & err = err ) ! (out)
427  if ( present_and_true( err ) ) then
428  call hstnmlinfodelete( &
429  & gthstnml = gthstnml, & ! (inout)
430  & name = name ) ! (in)
431  stat = usr_errno
432  goto 999
433  end if
434 
435  !---------------------------------------------------------------
436  ! ファイル分割時間間隔のチェック
437  ! Check interval of time of separation of a file
438  !---------------------------------------------------------------
439  call dcdifftimecreate( &
440  & diff = newfileint_time, & ! (out)
441  & value = real( hptr % newfile_intvalue ), & ! (in)
442  & unit = hptr % newfile_intunit, & ! (in)
443  & err = err ) ! (out)
444  if ( present_and_true( err ) ) then
445  call hstnmlinfodelete( &
446  & gthstnml = gthstnml, & ! (inout)
447  & name = name ) ! (in)
448  stat = usr_errno
449  goto 999
450  end if
451 
452  if ( ( hptr % newfile_intvalue > 0 ) &
453  & .and. .not. ( newfileint_time > interval_time ) ) then
454  call messagenotify( 'W', subname, &
455  & 'newfile_int=%d [%c] must be greater than interval=%r [%c]', &
456  & i = (/ hptr % newfile_intvalue /), &
457  & r = (/ hptr % interval_value /), &
458  & c1 = trim( hptr % newfile_intunit ), &
459  & c2 = trim( hptr % interval_unit ) )
460 
461  call hstnmlinfodelete( &
462  & gthstnml = gthstnml, & ! (inout)
463  & name = name ) ! (in)
464  stat = hst_ebadnewfileint
465  cause_c = cprintf( '%d [%c]', &
466  & i = (/ hptr % newfile_intvalue /), c1 = trim( hptr % newfile_intunit ) )
467  goto 999
468  end if
469 
470  nullify( hptr )
471 
472  !-----------------------------------------------------------------
473  ! 終了処理, 例外処理
474  ! Termination and Exception handling
475  !-----------------------------------------------------------------
476 999 continue
477  call storeerror( stat, subname, err, cause_c )
478  call endsub( subname )
479  end subroutine hstnmlinfoadd
integer, parameter, public dc_earglack
Definition: dc_error.f90:569
integer, parameter, public usr_errno
Definition: dc_error.f90:604
integer, parameter, public hst_enotindefine
Definition: dc_error.f90:581
integer, parameter, public dc_enotinit
Definition: dc_error.f90:557
integer, parameter, public token
単語やキーワードを保持する文字型変数の種別型パラメタ
Definition: dc_types.f90:109
logical function, public present_and_true(arg)
Definition: dc_present.f90:80
character(1), parameter, public name_delimiter
subroutine, public storeerror(number, where, err, cause_c, cause_i)
Definition: dc_error.f90:830
integer, parameter, public dc_noerr
Definition: dc_error.f90:509
character(string) function, public joinchar(carray, expr)
Definition: dc_string.f90:861
recursive subroutine hstnmlinfoadd(gthstnml, name, file, interval_value, interval_unit, precision, time_average, average, fileprefix, origin_value, origin_unit, terminus_value, terminus_unit, slice_start, slice_end, slice_stride, space_average, newfile_intvalue, newfile_intunit, err)
integer, parameter, public hst_ebadnewfileint
Definition: dc_error.f90:593
integer, parameter, public dp
倍精度実数型変数
Definition: dc_types.f90:83
subroutine, public dbgmessage(fmt, i, r, d, L, n, c1, c2, c3, ca)
Definition: dc_trace.f90:509
logical function, public present_and_not_empty(arg)
Definition: dc_present.f90:276
subroutine, public beginsub(name, fmt, i, r, d, L, n, c1, c2, c3, ca, version)
Definition: dc_trace.f90:351
integer, parameter, public stdout
標準出力の装置番号
Definition: dc_types.f90:98
文字型変数の操作.
Definition: dc_string.f90:24
種別型パラメタを提供します。
Definition: dc_types.f90:49
subroutine, public endsub(name, fmt, i, r, d, L, n, c1, c2, c3, ca)
Definition: dc_trace.f90:446
integer, parameter, public string
文字列を保持する 文字型変数の種別型パラメタ
Definition: dc_types.f90:118