dc_present Module Reference

Data Types

interface  present_and_eq
 
interface  present_and_ne
 
interface  present_select
 

Functions/Subroutines

logical function, public present_and_true (arg)
 
logical function, public present_and_false (arg)
 
logical function, public present_and_zero (arg)
 
logical function, public present_and_nonzero (arg)
 
logical function present_and_eq_integer (arg, val)
 
logical function present_and_eq_real (arg, val)
 
logical function present_and_eq_double (arg, val)
 
logical function present_and_ne_integer (arg, val)
 
logical function present_and_ne_real (arg, val)
 
logical function present_and_ne_double (arg, val)
 
logical function, public present_and_not_empty (arg)
 
character(string) function present_select_char (invalid, default, c0, c1, c2, c3, c4, c5, c6, c7, c8, c9)
 
integer function present_select_int (invalid, default, d0, d1, d2, d3, d4, d5, d6, d7, d8, d9)
 
real function present_select_real (invalid, default, r0, r1, r2, r3, r4, r5, r6, r7, r8, r9)
 
real(dp) function present_select_double (invalid, default, f0, f1, f2, f3, f4, f5, f6, f7, f8, f9)
 
character(string) function present_select_char_auto (invalid, default, c0, c1, c2, c3, c4, c5, c6, c7, c8, c9)
 
integer function present_select_int_auto (invalid, default, d0, d1, d2, d3, d4, d5, d6, d7, d8, d9)
 
real function present_select_real_auto (invalid, default, r0, r1, r2, r3, r4, r5, r6, r7, r8, r9)
 
real(dp) function present_select_double_auto (invalid, default, f0, f1, f2, f3, f4, f5, f6, f7, f8, f9)
 

Function/Subroutine Documentation

◆ present_and_eq_double()

logical function dc_present::present_and_eq_double ( real(dp), intent(in), optional  arg,
real(dp), intent(in)  val 
)
private

Definition at line 196 of file dc_present.f90.

196  !
197  ! arg が省略されておらず、且つ val と等しい場合、
198  ! <tt>.true.</tt> が返ります。
199  !
200  logical :: result
201  real(DP),intent(in),optional :: arg
202  real(DP),intent(in) :: val
203  continue
204  if(present(arg)) then
205  if(arg==val) then
206  result=.true.
207  else
208  result=.false.
209  endif
210  else
211  result=.false.
212  endif

◆ present_and_eq_integer()

logical function dc_present::present_and_eq_integer ( integer, intent(in), optional  arg,
integer, intent(in)  val 
)
private

Definition at line 156 of file dc_present.f90.

156  !
157  ! arg が省略されておらず、且つ val と等しい場合、
158  ! <tt>.true.</tt> が返ります。
159  !
160  logical :: result
161  integer,intent(in),optional :: arg
162  integer,intent(in) :: val
163  continue
164  if(present(arg)) then
165  if(arg==val) then
166  result=.true.
167  else
168  result=.false.
169  endif
170  else
171  result=.false.
172  endif

◆ present_and_eq_real()

logical function dc_present::present_and_eq_real ( real, intent(in), optional  arg,
real, intent(in)  val 
)
private

Definition at line 176 of file dc_present.f90.

176  !
177  ! arg が省略されておらず、且つ val と等しい場合、
178  ! <tt>.true.</tt> が返ります。
179  !
180  logical :: result
181  real,intent(in),optional :: arg
182  real,intent(in) :: val
183  continue
184  if(present(arg)) then
185  if(arg==val) then
186  result=.true.
187  else
188  result=.false.
189  endif
190  else
191  result=.false.
192  endif

◆ present_and_false()

logical function, public dc_present::present_and_false ( logical, intent(in), optional  arg)

Definition at line 99 of file dc_present.f90.

Referenced by gtvarcopyattrall(), historycopyvariable1(), historycreate1(), historycreate2(), historyputcharex(), historyputdoubleex(), historyputintex(), and historyputrealex().

99  !
100  ! arg が省略されておらず、且つ <tt>.false.</tt> の場合、
101  ! <tt>.true.</tt> が返ります。
102  !
103  logical :: result
104  logical,intent(in),optional :: arg
105  continue
106  if(present(arg)) then
107  if(arg) then
108  result=.false.
109  else
110  result=.true.
111  endif
112  else
113  result=.false.
114  endif
Here is the caller graph for this function:

◆ present_and_ne_double()

logical function dc_present::present_and_ne_double ( real(dp), intent(in), optional  arg,
real(dp), intent(in)  val 
)
private

Definition at line 256 of file dc_present.f90.

256  !
257  ! arg が省略されておらず、且つ val と等しくない場合、
258  ! <tt>.true.</tt> が返ります。
259  !
260  logical :: result
261  real(DP),intent(in),optional :: arg
262  real(DP),intent(in) :: val
263  continue
264  if(present(arg)) then
265  if(arg/=val) then
266  result=.true.
267  else
268  result=.false.
269  endif
270  else
271  result=.false.
272  endif

◆ present_and_ne_integer()

logical function dc_present::present_and_ne_integer ( integer, intent(in), optional  arg,
integer, intent(in)  val 
)
private

Definition at line 216 of file dc_present.f90.

216  !
217  ! arg が省略されておらず、且つ val と等しくない場合、
218  ! <tt>.true.</tt> が返ります。
219  !
220  logical :: result
221  integer,intent(in),optional :: arg
222  integer,intent(in) :: val
223  continue
224  if(present(arg)) then
225  if(arg/=val) then
226  result=.true.
227  else
228  result=.false.
229  endif
230  else
231  result=.false.
232  endif

◆ present_and_ne_real()

logical function dc_present::present_and_ne_real ( real, intent(in), optional  arg,
real, intent(in)  val 
)
private

Definition at line 236 of file dc_present.f90.

236  !
237  ! arg が省略されておらず、且つ val と等しくない場合、
238  ! <tt>.true.</tt> が返ります。
239  !
240  logical :: result
241  real,intent(in),optional :: arg
242  real,intent(in) :: val
243  continue
244  if(present(arg)) then
245  if(arg/=val) then
246  result=.true.
247  else
248  result=.false.
249  endif
250  else
251  result=.false.
252  endif

◆ present_and_nonzero()

logical function, public dc_present::present_and_nonzero ( integer, intent(in), optional  arg)

Definition at line 137 of file dc_present.f90.

137  !
138  ! arg が省略されておらず、且つ 0 ではない場合、
139  ! <tt>.true.</tt> が返ります。
140  !
141  logical :: result
142  integer,intent(in),optional :: arg
143  continue
144  if(present(arg)) then
145  if(arg==0) then
146  result=.false.
147  else
148  result=.true.
149  endif
150  else
151  result=.false.
152  endif

◆ present_and_not_empty()

logical function, public dc_present::present_and_not_empty ( character(len=*), intent(in), optional  arg)

Definition at line 276 of file dc_present.f90.

Referenced by dc_iounit::fileopen(), historyautocreate1(), historyautocreate2(), historyautocreate3(), historycreate1(), historycreate2(), historygetdouble0(), historygetdouble1(), historygetdouble2(), historygetdouble3(), historygetdouble4(), historygetdouble5(), historygetdouble6(), historygetdouble7(), historygetint0(), historygetint1(), historygetint2(), historygetint3(), historygetint4(), historygetint5(), historygetint6(), historygetint7(), historygetreal0(), historygetreal1(), historygetreal2(), historygetreal3(), historygetreal4(), historygetreal5(), historygetreal6(), historygetreal7(), historyputcharex(), historyputdoubleex(), historyputintex(), historyputrealex(), hstnmlinfoadd(), hstnmlinfoallnamevalid(), hstnmlinfoallvarinicheck(), hstnmlinfocreate(), hstnmlinfodelete(), hstnmlinfoinquire(), hstnmlinfooutputstep(), hstnmlinfooutputvalid(), hstnmlinfosetvalidname(), and lookup_growable_url().

276  !
277  ! arg が省略されておらず、且つ空文字ではない場合、
278  ! <tt>.true.</tt> が返ります。
279  !
280  logical :: result
281  character(len=*),intent(in),optional :: arg
282  continue
283  if(present(arg)) then
284  if(arg=="") then
285  result=.false.
286  else
287  result=.true.
288  endif
289  else
290  result=.false.
291  endif
Here is the caller graph for this function:

◆ present_and_true()

logical function, public dc_present::present_and_true ( logical, intent(in), optional  arg)

Definition at line 80 of file dc_present.f90.

Referenced by dc_args::dcargsget0(), dc_args::dcargshelp0(), dc_args::dcargsstrict0(), dcdatetimetocharcal(), gtvarcopyattrall(), gtvaropen(), gtvaropenbydimord(), historyaddvariable1(), historyautocreate1(), historyautocreate2(), historyautocreate3(), historyclose(), historycreate1(), historycreate2(), historycreate3(), historygetdouble0(), historygetdouble0pointer(), historygetdouble0pointertimed(), historygetdouble0pointertimei(), historygetdouble0pointertimer(), historygetdouble0timed(), historygetdouble0timei(), historygetdouble0timer(), historygetdouble1(), historygetdouble1pointer(), historygetdouble1pointertimed(), historygetdouble1pointertimei(), historygetdouble1pointertimer(), historygetdouble1timed(), historygetdouble1timei(), historygetdouble1timer(), historygetdouble2(), historygetdouble2pointer(), historygetdouble2pointertimed(), historygetdouble2pointertimei(), historygetdouble2pointertimer(), historygetdouble2timed(), historygetdouble2timei(), historygetdouble2timer(), historygetdouble3(), historygetdouble3pointer(), historygetdouble3pointertimed(), historygetdouble3pointertimei(), historygetdouble3pointertimer(), historygetdouble3timed(), historygetdouble3timei(), historygetdouble3timer(), historygetdouble4(), historygetdouble4pointer(), historygetdouble4pointertimed(), historygetdouble4pointertimei(), historygetdouble4pointertimer(), historygetdouble4timed(), historygetdouble4timei(), historygetdouble4timer(), historygetdouble5(), historygetdouble5pointer(), historygetdouble5pointertimed(), historygetdouble5pointertimei(), historygetdouble5pointertimer(), historygetdouble5timed(), historygetdouble5timei(), historygetdouble5timer(), historygetdouble6(), historygetdouble6pointer(), historygetdouble6pointertimed(), historygetdouble6pointertimei(), historygetdouble6pointertimer(), historygetdouble6timed(), historygetdouble6timei(), historygetdouble6timer(), historygetdouble7(), historygetdouble7pointer(), historygetdouble7pointertimed(), historygetdouble7pointertimei(), historygetdouble7pointertimer(), historygetdouble7timed(), historygetdouble7timei(), historygetdouble7timer(), historygetint0(), historygetint0pointer(), historygetint0pointertimed(), historygetint0pointertimei(), historygetint0pointertimer(), historygetint0timed(), historygetint0timei(), historygetint0timer(), historygetint1(), historygetint1pointer(), historygetint1pointertimed(), historygetint1pointertimei(), historygetint1pointertimer(), historygetint1timed(), historygetint1timei(), historygetint1timer(), historygetint2(), historygetint2pointer(), historygetint2pointertimed(), historygetint2pointertimei(), historygetint2pointertimer(), historygetint2timed(), historygetint2timei(), historygetint2timer(), historygetint3(), historygetint3pointer(), historygetint3pointertimed(), historygetint3pointertimei(), historygetint3pointertimer(), historygetint3timed(), historygetint3timei(), historygetint3timer(), historygetint4(), historygetint4pointer(), historygetint4pointertimed(), historygetint4pointertimei(), historygetint4pointertimer(), historygetint4timed(), historygetint4timei(), historygetint4timer(), historygetint5(), historygetint5pointer(), historygetint5pointertimed(), historygetint5pointertimei(), historygetint5pointertimer(), historygetint5timed(), historygetint5timei(), historygetint5timer(), historygetint6(), historygetint6pointer(), historygetint6pointertimed(), historygetint6pointertimei(), historygetint6pointertimer(), historygetint6timed(), historygetint6timei(), historygetint6timer(), historygetint7(), historygetint7pointer(), historygetint7pointertimed(), historygetint7pointertimei(), historygetint7pointertimer(), historygetint7timed(), historygetint7timei(), historygetint7timer(), historygetreal0(), historygetreal0pointer(), historygetreal0pointertimed(), historygetreal0pointertimei(), historygetreal0pointertimer(), historygetreal0timed(), historygetreal0timei(), historygetreal0timer(), historygetreal1(), historygetreal1pointer(), historygetreal1pointertimed(), historygetreal1pointertimei(), historygetreal1pointertimer(), historygetreal1timed(), historygetreal1timei(), historygetreal1timer(), historygetreal2(), historygetreal2pointer(), historygetreal2pointertimed(), historygetreal2pointertimei(), historygetreal2pointertimer(), historygetreal2timed(), historygetreal2timei(), historygetreal2timer(), historygetreal3(), historygetreal3pointer(), historygetreal3pointertimed(), historygetreal3pointertimei(), historygetreal3pointertimer(), historygetreal3timed(), historygetreal3timei(), historygetreal3timer(), historygetreal4(), historygetreal4pointer(), historygetreal4pointertimed(), historygetreal4pointertimei(), historygetreal4pointertimer(), historygetreal4timed(), historygetreal4timei(), historygetreal4timer(), historygetreal5(), historygetreal5pointer(), historygetreal5pointertimed(), historygetreal5pointertimei(), historygetreal5pointertimer(), historygetreal5timed(), historygetreal5timei(), historygetreal5timer(), historygetreal6(), historygetreal6pointer(), historygetreal6pointertimed(), historygetreal6pointertimei(), historygetreal6pointertimer(), historygetreal6timed(), historygetreal6timei(), historygetreal6timer(), historygetreal7(), historygetreal7pointer(), historygetreal7pointertimed(), historygetreal7pointertimei(), historygetreal7pointertimer(), historygetreal7timed(), historygetreal7timei(), historygetreal7timer(), historygettattrchar0(), historygettattrdouble0(), historygettattrdouble1(), historygettattrint0(), historygettattrint1(), historygettattrreal0(), historygettattrreal1(), historyputcharex(), historyputdoubleex(), historyputintex(), historyputrealex(), hstnmlinfoadd(), hstnmlinfoallnamevalid(), hstnmlinfoallvarinicheck(), hstnmlinfocreate(), hstnmlinfodelete(), hstnmlinfoinquire(), hstnmlinfooutputstep(), hstnmlinfooutputvalid(), hstnmlinfosetvalidname(), lookup_growable_url(), putlinedouble1(), putlinedouble2(), putlinedouble3(), putlinedouble4(), putlinedouble5(), putlinedouble6(), putlinedouble7(), putlineint1(), putlineint2(), putlineint3(), putlineint4(), putlineint5(), putlineint6(), putlineint7(), putlinereal1(), putlinereal2(), putlinereal3(), putlinereal4(), putlinereal5(), putlinereal6(), and putlinereal7().

80  !
81  ! arg が省略されておらず、且つ <tt>.true.</tt> の場合、
82  ! <tt>.true.</tt> が返ります。
83  !
84  logical :: result
85  logical,intent(in),optional :: arg
86  continue
87  if(present(arg)) then
88  if(arg) then
89  result=.true.
90  else
91  result=.false.
92  endif
93  else
94  result=.false.
95  endif

◆ present_and_zero()

logical function, public dc_present::present_and_zero ( integer, intent(in), optional  arg)

Definition at line 118 of file dc_present.f90.

118  !
119  ! arg が省略されておらず、且つ 0 の場合、
120  ! <tt>.true.</tt> が返ります。
121  !
122  logical :: result
123  integer,intent(in),optional :: arg
124  continue
125  if(present(arg)) then
126  if(arg==0) then
127  result=.true.
128  else
129  result=.false.
130  endif
131  else
132  result=.false.
133  endif

◆ present_select_char()

character(string) function dc_present::present_select_char ( character(*), intent(in)  invalid,
character(*), intent(in)  default,
character(*), intent(in), optional  c0,
character(*), intent(in), optional  c1,
character(*), intent(in), optional  c2,
character(*), intent(in), optional  c3,
character(*), intent(in), optional  c4,
character(*), intent(in), optional  c5,
character(*), intent(in), optional  c6,
character(*), intent(in), optional  c7,
character(*), intent(in), optional  c8,
character(*), intent(in), optional  c9 
)
private

Definition at line 308 of file dc_present.f90.

308  !
309  ! 省略可能な引数 c0 〜 c9 のうち、
310  ! 省略されておらず、且つ invalid と等しくないものを 1 つ返します。
311  ! 優先順位が最も高いものは c0 で、
312  ! 最も低いのは c9 です。
313  ! c0 〜 c9 の全てが省略されているか
314  ! もしくは invalid と同様な場合は default が返ります。
315  !
316  implicit none
317  character(*) ,intent(in) :: invalid
318  character(*) ,intent(in) :: default
319  character(*) ,intent(in),optional :: c0
320  character(*) ,intent(in),optional :: c1
321  character(*) ,intent(in),optional :: c2
322  character(*) ,intent(in),optional :: c3
323  character(*) ,intent(in),optional :: c4
324  character(*) ,intent(in),optional :: c5
325  character(*) ,intent(in),optional :: c6
326  character(*) ,intent(in),optional :: c7
327  character(*) ,intent(in),optional :: c8
328  character(*) ,intent(in),optional :: c9
329  character(STRING) :: result
330 
331  !=== Variables for internal work
332  logical :: specified
333  character(*), parameter:: subname = 'present_select_Char'
334  continue
335 
336 !!$ call BeginSub(subname, 'invalid=%c default=%c', &
337 !!$ & c1=trim(invalid), c2=trim(default) )
338  specified = .false.
339 
340  if ( present(c0) ) then
341  if ( len(trim(c0)) > len(trim(invalid)) ) then
342  result = c0
343  specified = .true.
344  else
345  if ( trim(c0) /= invalid(:len(trim(c0))) ) then
346  result = c0
347  specified = .true.
348  endif
349  end if
350  end if
351 
352  if ( present(c1) .and. .not. specified) then
353  if ( len(trim(c1)) > len(trim(invalid)) ) then
354  result = c1
355  specified = .true.
356  else
357  if ( trim(c1) /= invalid(:len(trim(c1))) ) then
358  result = c1
359  specified = .true.
360  endif
361  end if
362  end if
363  if ( present(c2) .and. .not. specified) then
364  if ( len(trim(c2)) > len(trim(invalid)) ) then
365  result = c2
366  specified = .true.
367  else
368  if ( trim(c2) /= invalid(:len(trim(c2))) ) then
369  result = c2
370  specified = .true.
371  endif
372  end if
373  end if
374  if ( present(c3) .and. .not. specified) then
375  if ( len(trim(c3)) > len(trim(invalid)) ) then
376  result = c3
377  specified = .true.
378  else
379  if ( trim(c3) /= invalid(:len(trim(c3))) ) then
380  result = c3
381  specified = .true.
382  endif
383  end if
384  end if
385  if ( present(c4) .and. .not. specified) then
386  if ( len(trim(c4)) > len(trim(invalid)) ) then
387  result = c4
388  specified = .true.
389  else
390  if ( trim(c4) /= invalid(:len(trim(c4))) ) then
391  result = c4
392  specified = .true.
393  endif
394  end if
395  end if
396  if ( present(c5) .and. .not. specified) then
397  if ( len(trim(c5)) > len(trim(invalid)) ) then
398  result = c5
399  specified = .true.
400  else
401  if ( trim(c5) /= invalid(:len(trim(c5))) ) then
402  result = c5
403  specified = .true.
404  endif
405  end if
406  end if
407  if ( present(c6) .and. .not. specified) then
408  if ( len(trim(c6)) > len(trim(invalid)) ) then
409  result = c6
410  specified = .true.
411  else
412  if ( trim(c6) /= invalid(:len(trim(c6))) ) then
413  result = c6
414  specified = .true.
415  endif
416  end if
417  end if
418  if ( present(c7) .and. .not. specified) then
419  if ( len(trim(c7)) > len(trim(invalid)) ) then
420  result = c7
421  specified = .true.
422  else
423  if ( trim(c7) /= invalid(:len(trim(c7))) ) then
424  result = c7
425  specified = .true.
426  endif
427  end if
428  end if
429  if ( present(c8) .and. .not. specified) then
430  if ( len(trim(c8)) > len(trim(invalid)) ) then
431  result = c8
432  specified = .true.
433  else
434  if ( trim(c8) /= invalid(:len(trim(c8))) ) then
435  result = c8
436  specified = .true.
437  endif
438  end if
439  end if
440  if ( present(c9) .and. .not. specified) then
441  if ( len(trim(c9)) > len(trim(invalid)) ) then
442  result = c9
443  specified = .true.
444  else
445  if ( trim(c9) /= invalid(:len(trim(c9))) ) then
446  result = c9
447  specified = .true.
448  endif
449  end if
450  end if
451 
452  if (.not. specified) then
453  result = default
454  end if
455 
456 !!$ call EndSub(subname, "result=%c", c1=trim(result))
457 
type(gt_history), target, save, public default

◆ present_select_char_auto()

character(string) function dc_present::present_select_char_auto ( logical, intent(in)  invalid,
character(*), intent(in)  default,
character(*), intent(in), optional  c0,
character(*), intent(in), optional  c1,
character(*), intent(in), optional  c2,
character(*), intent(in), optional  c3,
character(*), intent(in), optional  c4,
character(*), intent(in), optional  c5,
character(*), intent(in), optional  c6,
character(*), intent(in), optional  c7,
character(*), intent(in), optional  c8,
character(*), intent(in), optional  c9 
)
private

Definition at line 828 of file dc_present.f90.

828  !
829  ! invalid に <tt>.false.</tt> を与えた場合、省略可能な引数
830  ! c0 〜 c9 のうち、
831  ! 省略されておらず且つ優先順位が最も高いものを
832  ! 1 つ返します。優先順位が最も高いのは c0 で、
833  ! 最も低いのは c9 です。
834  !
835  ! invarlid が .true. の場合は、
836  ! 空文字 (空白のみの場合も空文字と扱う) は省略されている
837  ! のと同様に扱われ、優先順位に関わらず無視されます。
838  ! 与えられた引数の全てが空文字の場合は default が返ります。
839  !
840  implicit none
841  logical ,intent(in) :: invalid
842  character(*) ,intent(in) :: default
843  character(*) ,intent(in),optional :: c0
844  character(*) ,intent(in),optional :: c1
845  character(*) ,intent(in),optional :: c2
846  character(*) ,intent(in),optional :: c3
847  character(*) ,intent(in),optional :: c4
848  character(*) ,intent(in),optional :: c5
849  character(*) ,intent(in),optional :: c6
850  character(*) ,intent(in),optional :: c7
851  character(*) ,intent(in),optional :: c8
852  character(*) ,intent(in),optional :: c9
853  character(STRING) :: result
854 
855  !=== Variables for internal work
856  logical :: specified
857  character(*), parameter:: subname = "present_select_Char_auto"
858  continue
859 
860 !!$ call BeginSub(subname, 'invalid=%y default=%c', &
861 !!$ & l=(/invalid/), c1=trim(default) )
862  specified = .false.
863 
864  if ( present(c0) ) then
865  if ( trim(c0) /= '' ) then
866  result = c0
867  specified = .true.
868  endif
869  end if
870 
871  if ( present(c1) .and. .not. specified ) then
872  if ( trim(c1) /= '' ) then
873  result = c1
874  specified = .true.
875  endif
876  end if
877  if ( present(c2) .and. .not. specified ) then
878  if ( trim(c2) /= '' ) then
879  result = c2
880  specified = .true.
881  endif
882  end if
883  if ( present(c3) .and. .not. specified ) then
884  if ( trim(c3) /= '' ) then
885  result = c3
886  specified = .true.
887  endif
888  end if
889  if ( present(c4) .and. .not. specified ) then
890  if ( trim(c4) /= '' ) then
891  result = c4
892  specified = .true.
893  endif
894  end if
895  if ( present(c5) .and. .not. specified ) then
896  if ( trim(c5) /= '' ) then
897  result = c5
898  specified = .true.
899  endif
900  end if
901  if ( present(c6) .and. .not. specified ) then
902  if ( trim(c6) /= '' ) then
903  result = c6
904  specified = .true.
905  endif
906  end if
907  if ( present(c7) .and. .not. specified ) then
908  if ( trim(c7) /= '' ) then
909  result = c7
910  specified = .true.
911  endif
912  end if
913  if ( present(c8) .and. .not. specified ) then
914  if ( trim(c8) /= '' ) then
915  result = c8
916  specified = .true.
917  endif
918  end if
919  if ( present(c9) .and. .not. specified ) then
920  if ( trim(c9) /= '' ) then
921  result = c9
922  specified = .true.
923  endif
924  end if
925 
926  if (.not. specified) then
927  result = default
928  end if
929 
930 !!$ call EndSub(subname, "result=%c", c1=trim(result))
931 
type(gt_history), target, save, public default

◆ present_select_double()

real(dp) function dc_present::present_select_double ( real(dp), intent(in)  invalid,
real(dp), intent(in)  default,
real(dp), intent(in), optional  f0,
real(dp), intent(in), optional  f1,
real(dp), intent(in), optional  f2,
real(dp), intent(in), optional  f3,
real(dp), intent(in), optional  f4,
real(dp), intent(in), optional  f5,
real(dp), intent(in), optional  f6,
real(dp), intent(in), optional  f7,
real(dp), intent(in), optional  f8,
real(dp), intent(in), optional  f9 
)
private

Definition at line 710 of file dc_present.f90.

710  !
711  ! 省略可能な引数 f0 〜 f9 のうち、
712  ! 省略されておらず、且つ invalid と等しくないものを 1 つ返します。
713  ! 優先順位が最も高いものは f0 で、
714  ! 最も低いのは f9 です。
715  ! f0 〜 f9 の全てが省略されているか
716  ! もしくは invalid と同様な場合は default が返ります。
717  !
718  implicit none
719  real(DP) ,intent(in) :: invalid
720  real(DP) ,intent(in) :: default
721  real(DP) ,intent(in),optional :: f0
722  real(DP) ,intent(in),optional :: f1
723  real(DP) ,intent(in),optional :: f2
724  real(DP) ,intent(in),optional :: f3
725  real(DP) ,intent(in),optional :: f4
726  real(DP) ,intent(in),optional :: f5
727  real(DP) ,intent(in),optional :: f6
728  real(DP) ,intent(in),optional :: f7
729  real(DP) ,intent(in),optional :: f8
730  real(DP) ,intent(in),optional :: f9
731  real(DP) :: result
732 
733  !=== Variables for internal work
734  logical :: specified
735  character(*), parameter:: subname = 'present_select_Double'
736  continue
737 
738 !!$ call BeginSub(subname, &
739 !!$ & 'invalid=%f default=%f', &
740 !!$ & d=(/invalid, default/))
741  specified = .false.
742 
743  if ( present(f0) ) then
744  if ( f0 /= invalid ) then
745  result = f0
746  specified = .true.
747  endif
748  end if
749 
750  if ( present(f1) .and. .not. specified ) then
751  if ( f1 /= invalid ) then
752  result = f1
753  specified = .true.
754  endif
755  end if
756  if ( present(f2) .and. .not. specified ) then
757  if ( f2 /= invalid ) then
758  result = f2
759  specified = .true.
760  endif
761  end if
762  if ( present(f3) .and. .not. specified ) then
763  if ( f3 /= invalid ) then
764  result = f3
765  specified = .true.
766  endif
767  end if
768  if ( present(f4) .and. .not. specified ) then
769  if ( f4 /= invalid ) then
770  result = f4
771  specified = .true.
772  endif
773  end if
774  if ( present(f5) .and. .not. specified ) then
775  if ( f5 /= invalid ) then
776  result = f5
777  specified = .true.
778  endif
779  end if
780  if ( present(f6) .and. .not. specified ) then
781  if ( f6 /= invalid ) then
782  result = f6
783  specified = .true.
784  endif
785  end if
786  if ( present(f7) .and. .not. specified ) then
787  if ( f7 /= invalid ) then
788  result = f7
789  specified = .true.
790  endif
791  end if
792  if ( present(f8) .and. .not. specified ) then
793  if ( f8 /= invalid ) then
794  result = f8
795  specified = .true.
796  endif
797  end if
798  if ( present(f9) .and. .not. specified ) then
799  if ( f9 /= invalid ) then
800  result = f9
801  specified = .true.
802  endif
803  end if
804 
805  if (.not. specified) then
806  result = default
807  end if
808 
809 !!$ call EndSub(subname, "result=%f", &
810 !!$ & d=(/result/))
811 
type(gt_history), target, save, public default

◆ present_select_double_auto()

real(dp) function dc_present::present_select_double_auto ( logical, intent(in)  invalid,
real(dp), intent(in)  default,
real(dp), intent(in), optional  f0,
real(dp), intent(in), optional  f1,
real(dp), intent(in), optional  f2,
real(dp), intent(in), optional  f3,
real(dp), intent(in), optional  f4,
real(dp), intent(in), optional  f5,
real(dp), intent(in), optional  f6,
real(dp), intent(in), optional  f7,
real(dp), intent(in), optional  f8,
real(dp), intent(in), optional  f9 
)
private

Definition at line 1252 of file dc_present.f90.

1252  !
1253  ! invalid に <tt>.false.</tt> を与えた場合、省略可能な引数
1254  ! f0 〜 f9 のうち、
1255  ! 省略されておらず且つ優先順位が最も高いものを
1256  ! 1 つ返します。優先順位が最も高いのは f0 で、
1257  ! 最も低いのは f9 です。
1258  !
1259  ! invarlid が .true. の場合は、
1260  ! 0 は省略されている
1261  ! のと同様に扱われ、優先順位に関わらず無視されます。
1262  ! 与えられた引数の全てが 0 の場合は default が返ります。
1263  !
1264  implicit none
1265  logical ,intent(in) :: invalid
1266  real(DP) ,intent(in) :: default
1267  real(DP) ,intent(in),optional :: f0
1268  real(DP) ,intent(in),optional :: f1
1269  real(DP) ,intent(in),optional :: f2
1270  real(DP) ,intent(in),optional :: f3
1271  real(DP) ,intent(in),optional :: f4
1272  real(DP) ,intent(in),optional :: f5
1273  real(DP) ,intent(in),optional :: f6
1274  real(DP) ,intent(in),optional :: f7
1275  real(DP) ,intent(in),optional :: f8
1276  real(DP) ,intent(in),optional :: f9
1277  real(DP) :: result
1278 
1279  !=== Variables for internal work
1280  logical :: specified
1281  character(*), parameter:: subname = "present_select_Double_auto"
1282  continue
1283 
1284 !!$ call BeginSub(subname, &
1285 !!$ & 'invalid=%y default=%f', &
1286 !!$ & l=(/invalid/), d=(/default/))
1287  specified = .false.
1288 
1289  if ( present(f0) ) then
1290  if ( .not. invalid ) then
1291  result = f0
1292  specified = .true.
1293  elseif ( f0 /= 0.0_dp ) then
1294  result = f0
1295  specified = .true.
1296  endif
1297  end if
1298 
1299  if ( present(f1) .and. .not. specified ) then
1300  if ( .not. invalid ) then
1301  result = f1
1302  specified = .true.
1303  elseif ( f1 /= 0.0_dp ) then
1304  result = f1
1305  specified = .true.
1306  endif
1307  end if
1308  if ( present(f2) .and. .not. specified ) then
1309  if ( .not. invalid ) then
1310  result = f2
1311  specified = .true.
1312  elseif ( f2 /= 0.0_dp ) then
1313  result = f2
1314  specified = .true.
1315  endif
1316  end if
1317  if ( present(f3) .and. .not. specified ) then
1318  if ( .not. invalid ) then
1319  result = f3
1320  specified = .true.
1321  elseif ( f3 /= 0.0_dp ) then
1322  result = f3
1323  specified = .true.
1324  endif
1325  end if
1326  if ( present(f4) .and. .not. specified ) then
1327  if ( .not. invalid ) then
1328  result = f4
1329  specified = .true.
1330  elseif ( f4 /= 0.0_dp ) then
1331  result = f4
1332  specified = .true.
1333  endif
1334  end if
1335  if ( present(f5) .and. .not. specified ) then
1336  if ( .not. invalid ) then
1337  result = f5
1338  specified = .true.
1339  elseif ( f5 /= 0.0_dp ) then
1340  result = f5
1341  specified = .true.
1342  endif
1343  end if
1344  if ( present(f6) .and. .not. specified ) then
1345  if ( .not. invalid ) then
1346  result = f6
1347  specified = .true.
1348  elseif ( f6 /= 0.0_dp ) then
1349  result = f6
1350  specified = .true.
1351  endif
1352  end if
1353  if ( present(f7) .and. .not. specified ) then
1354  if ( .not. invalid ) then
1355  result = f7
1356  specified = .true.
1357  elseif ( f7 /= 0.0_dp ) then
1358  result = f7
1359  specified = .true.
1360  endif
1361  end if
1362  if ( present(f8) .and. .not. specified ) then
1363  if ( .not. invalid ) then
1364  result = f8
1365  specified = .true.
1366  elseif ( f8 /= 0.0_dp ) then
1367  result = f8
1368  specified = .true.
1369  endif
1370  end if
1371  if ( present(f9) .and. .not. specified ) then
1372  if ( .not. invalid ) then
1373  result = f9
1374  specified = .true.
1375  elseif ( f9 /= 0.0_dp ) then
1376  result = f9
1377  specified = .true.
1378  endif
1379  end if
1380 
1381  if (.not. specified) then
1382  result = default
1383  end if
1384 
1385 !!$ call EndSub(subname, "result=%f", &
1386 !!$ & d=(/result/))
1387 
type(gt_history), target, save, public default

◆ present_select_int()

integer function dc_present::present_select_int ( integer, intent(in)  invalid,
integer, intent(in)  default,
integer, intent(in), optional  d0,
integer, intent(in), optional  d1,
integer, intent(in), optional  d2,
integer, intent(in), optional  d3,
integer, intent(in), optional  d4,
integer, intent(in), optional  d5,
integer, intent(in), optional  d6,
integer, intent(in), optional  d7,
integer, intent(in), optional  d8,
integer, intent(in), optional  d9 
)
private

Definition at line 474 of file dc_present.f90.

474  !
475  ! 省略可能な引数 d0 〜 d9 のうち、
476  ! 省略されておらず、且つ invalid と等しくないものを 1 つ返します。
477  ! 優先順位が最も高いものは d0 で、
478  ! 最も低いのは d9 です。
479  ! d0 〜 d9 の全てが省略されているか
480  ! もしくは invalid と同様な場合は default が返ります。
481  !
482  implicit none
483  integer ,intent(in) :: invalid
484  integer ,intent(in) :: default
485  integer ,intent(in),optional :: d0
486  integer ,intent(in),optional :: d1
487  integer ,intent(in),optional :: d2
488  integer ,intent(in),optional :: d3
489  integer ,intent(in),optional :: d4
490  integer ,intent(in),optional :: d5
491  integer ,intent(in),optional :: d6
492  integer ,intent(in),optional :: d7
493  integer ,intent(in),optional :: d8
494  integer ,intent(in),optional :: d9
495  integer :: result
496 
497  !=== Variables for internal work
498  logical :: specified
499  character(*), parameter:: subname = 'present_select_Int'
500  continue
501 
502 !!$ call BeginSub(subname, &
503 !!$ & 'invalid=%d default=%d', &
504 !!$ & i=(/invalid, default/))
505  specified = .false.
506 
507  if ( present(d0) ) then
508  if ( d0 /= invalid ) then
509  result = d0
510  specified = .true.
511  endif
512  end if
513 
514  if ( present(d1) .and. .not. specified ) then
515  if ( d1 /= invalid ) then
516  result = d1
517  specified = .true.
518  endif
519  end if
520  if ( present(d2) .and. .not. specified ) then
521  if ( d2 /= invalid ) then
522  result = d2
523  specified = .true.
524  endif
525  end if
526  if ( present(d3) .and. .not. specified ) then
527  if ( d3 /= invalid ) then
528  result = d3
529  specified = .true.
530  endif
531  end if
532  if ( present(d4) .and. .not. specified ) then
533  if ( d4 /= invalid ) then
534  result = d4
535  specified = .true.
536  endif
537  end if
538  if ( present(d5) .and. .not. specified ) then
539  if ( d5 /= invalid ) then
540  result = d5
541  specified = .true.
542  endif
543  end if
544  if ( present(d6) .and. .not. specified ) then
545  if ( d6 /= invalid ) then
546  result = d6
547  specified = .true.
548  endif
549  end if
550  if ( present(d7) .and. .not. specified ) then
551  if ( d7 /= invalid ) then
552  result = d7
553  specified = .true.
554  endif
555  end if
556  if ( present(d8) .and. .not. specified ) then
557  if ( d8 /= invalid ) then
558  result = d8
559  specified = .true.
560  endif
561  end if
562  if ( present(d9) .and. .not. specified ) then
563  if ( d9 /= invalid ) then
564  result = d9
565  specified = .true.
566  endif
567  end if
568 
569  if (.not. specified) then
570  result = default
571  end if
572 
573 !!$ call EndSub(subname, "result=%d", &
574 !!$ & i=(/result/))
575 
type(gt_history), target, save, public default

◆ present_select_int_auto()

integer function dc_present::present_select_int_auto ( logical, intent(in)  invalid,
integer, intent(in)  default,
integer, intent(in), optional  d0,
integer, intent(in), optional  d1,
integer, intent(in), optional  d2,
integer, intent(in), optional  d3,
integer, intent(in), optional  d4,
integer, intent(in), optional  d5,
integer, intent(in), optional  d6,
integer, intent(in), optional  d7,
integer, intent(in), optional  d8,
integer, intent(in), optional  d9 
)
private

Definition at line 948 of file dc_present.f90.

948  !
949  ! invalid に <tt>.false.</tt> を与えた場合、省略可能な引数
950  ! d0 〜 d9 のうち、
951  ! 省略されておらず且つ優先順位が最も高いものを
952  ! 1 つ返します。優先順位が最も高いのは d0 で、
953  ! 最も低いのは d9 です。
954  !
955  ! invarlid が .true. の場合は、
956  ! 0 は省略されている
957  ! のと同様に扱われ、優先順位に関わらず無視されます。
958  ! 与えられた引数の全てが 0 の場合は default が返ります。
959  !
960  implicit none
961  logical ,intent(in) :: invalid
962  integer ,intent(in) :: default
963  integer ,intent(in),optional :: d0
964  integer ,intent(in),optional :: d1
965  integer ,intent(in),optional :: d2
966  integer ,intent(in),optional :: d3
967  integer ,intent(in),optional :: d4
968  integer ,intent(in),optional :: d5
969  integer ,intent(in),optional :: d6
970  integer ,intent(in),optional :: d7
971  integer ,intent(in),optional :: d8
972  integer ,intent(in),optional :: d9
973  integer :: result
974 
975  !=== Variables for internal work
976  logical :: specified
977  character(*), parameter:: subname = "present_select_Int_auto"
978  continue
979 
980 !!$ call BeginSub(subname, &
981 !!$ & 'invalid=%y default=%d', &
982 !!$ & l=(/invalid/), i=(/default/))
983  specified = .false.
984 
985  if ( present(d0) ) then
986  if ( .not. invalid ) then
987  result = d0
988  specified = .true.
989  elseif ( d0 /= 0 ) then
990  result = d0
991  specified = .true.
992  endif
993  end if
994 
995  if ( present(d1) .and. .not. specified ) then
996  if ( .not. invalid ) then
997  result = d1
998  specified = .true.
999  elseif ( d1 /= 0 ) then
1000  result = d1
1001  specified = .true.
1002  endif
1003  end if
1004  if ( present(d2) .and. .not. specified ) then
1005  if ( .not. invalid ) then
1006  result = d2
1007  specified = .true.
1008  elseif ( d2 /= 0 ) then
1009  result = d2
1010  specified = .true.
1011  endif
1012  end if
1013  if ( present(d3) .and. .not. specified ) then
1014  if ( .not. invalid ) then
1015  result = d3
1016  specified = .true.
1017  elseif ( d3 /= 0 ) then
1018  result = d3
1019  specified = .true.
1020  endif
1021  end if
1022  if ( present(d4) .and. .not. specified ) then
1023  if ( .not. invalid ) then
1024  result = d4
1025  specified = .true.
1026  elseif ( d4 /= 0 ) then
1027  result = d4
1028  specified = .true.
1029  endif
1030  end if
1031  if ( present(d5) .and. .not. specified ) then
1032  if ( .not. invalid ) then
1033  result = d5
1034  specified = .true.
1035  elseif ( d5 /= 0 ) then
1036  result = d5
1037  specified = .true.
1038  endif
1039  end if
1040  if ( present(d6) .and. .not. specified ) then
1041  if ( .not. invalid ) then
1042  result = d6
1043  specified = .true.
1044  elseif ( d6 /= 0 ) then
1045  result = d6
1046  specified = .true.
1047  endif
1048  end if
1049  if ( present(d7) .and. .not. specified ) then
1050  if ( .not. invalid ) then
1051  result = d7
1052  specified = .true.
1053  elseif ( d7 /= 0 ) then
1054  result = d7
1055  specified = .true.
1056  endif
1057  end if
1058  if ( present(d8) .and. .not. specified ) then
1059  if ( .not. invalid ) then
1060  result = d8
1061  specified = .true.
1062  elseif ( d8 /= 0 ) then
1063  result = d8
1064  specified = .true.
1065  endif
1066  end if
1067  if ( present(d9) .and. .not. specified ) then
1068  if ( .not. invalid ) then
1069  result = d9
1070  specified = .true.
1071  elseif ( d9 /= 0 ) then
1072  result = d9
1073  specified = .true.
1074  endif
1075  end if
1076 
1077  if (.not. specified) then
1078  result = default
1079  end if
1080 
1081 !!$ call EndSub(subname, "result=%d", &
1082 !!$ & i=(/result/))
1083 
type(gt_history), target, save, public default

◆ present_select_real()

real function dc_present::present_select_real ( real, intent(in)  invalid,
real, intent(in)  default,
real, intent(in), optional  r0,
real, intent(in), optional  r1,
real, intent(in), optional  r2,
real, intent(in), optional  r3,
real, intent(in), optional  r4,
real, intent(in), optional  r5,
real, intent(in), optional  r6,
real, intent(in), optional  r7,
real, intent(in), optional  r8,
real, intent(in), optional  r9 
)
private

Definition at line 592 of file dc_present.f90.

592  !
593  ! 省略可能な引数 r0 〜 r9 のうち、
594  ! 省略されておらず、且つ invalid と等しくないものを 1 つ返します。
595  ! 優先順位が最も高いものは r0 で、
596  ! 最も低いのは r9 です。
597  ! r0 〜 r9 の全てが省略されているか
598  ! もしくは invalid と同様な場合は default が返ります。
599  !
600  implicit none
601  real ,intent(in) :: invalid
602  real ,intent(in) :: default
603  real ,intent(in),optional :: r0
604  real ,intent(in),optional :: r1
605  real ,intent(in),optional :: r2
606  real ,intent(in),optional :: r3
607  real ,intent(in),optional :: r4
608  real ,intent(in),optional :: r5
609  real ,intent(in),optional :: r6
610  real ,intent(in),optional :: r7
611  real ,intent(in),optional :: r8
612  real ,intent(in),optional :: r9
613  real :: result
614 
615  !=== Variables for internal work
616  logical :: specified
617  character(*), parameter:: subname = 'present_select_Real'
618  continue
619 
620 !!$ call BeginSub(subname, &
621 !!$ & 'invalid=%r default=%r', &
622 !!$ & r=(/invalid, default/))
623  specified = .false.
624 
625  if ( present(r0) ) then
626  if ( r0 /= invalid ) then
627  result = r0
628  specified = .true.
629  endif
630  end if
631 
632  if ( present(r1) .and. .not. specified ) then
633  if ( r1 /= invalid ) then
634  result = r1
635  specified = .true.
636  endif
637  end if
638  if ( present(r2) .and. .not. specified ) then
639  if ( r2 /= invalid ) then
640  result = r2
641  specified = .true.
642  endif
643  end if
644  if ( present(r3) .and. .not. specified ) then
645  if ( r3 /= invalid ) then
646  result = r3
647  specified = .true.
648  endif
649  end if
650  if ( present(r4) .and. .not. specified ) then
651  if ( r4 /= invalid ) then
652  result = r4
653  specified = .true.
654  endif
655  end if
656  if ( present(r5) .and. .not. specified ) then
657  if ( r5 /= invalid ) then
658  result = r5
659  specified = .true.
660  endif
661  end if
662  if ( present(r6) .and. .not. specified ) then
663  if ( r6 /= invalid ) then
664  result = r6
665  specified = .true.
666  endif
667  end if
668  if ( present(r7) .and. .not. specified ) then
669  if ( r7 /= invalid ) then
670  result = r7
671  specified = .true.
672  endif
673  end if
674  if ( present(r8) .and. .not. specified ) then
675  if ( r8 /= invalid ) then
676  result = r8
677  specified = .true.
678  endif
679  end if
680  if ( present(r9) .and. .not. specified ) then
681  if ( r9 /= invalid ) then
682  result = r9
683  specified = .true.
684  endif
685  end if
686 
687  if (.not. specified) then
688  result = default
689  end if
690 
691 !!$ call EndSub(subname, "result=%r", &
692 !!$ & r=(/result/))
693 
type(gt_history), target, save, public default

◆ present_select_real_auto()

real function dc_present::present_select_real_auto ( logical, intent(in)  invalid,
real, intent(in)  default,
real, intent(in), optional  r0,
real, intent(in), optional  r1,
real, intent(in), optional  r2,
real, intent(in), optional  r3,
real, intent(in), optional  r4,
real, intent(in), optional  r5,
real, intent(in), optional  r6,
real, intent(in), optional  r7,
real, intent(in), optional  r8,
real, intent(in), optional  r9 
)
private

Definition at line 1100 of file dc_present.f90.

1100  !
1101  ! invalid に <tt>.false.</tt> を与えた場合、省略可能な引数
1102  ! r0 〜 r9 のうち、
1103  ! 省略されておらず且つ優先順位が最も高いものを
1104  ! 1 つ返します。優先順位が最も高いのは r0 で、
1105  ! 最も低いのは r9 です。
1106  !
1107  ! invarlid が .true. の場合は、
1108  ! 0 は省略されている
1109  ! のと同様に扱われ、優先順位に関わらず無視されます。
1110  ! 与えられた引数の全てが 0 の場合は default が返ります。
1111  !
1112  implicit none
1113  logical ,intent(in) :: invalid
1114  real ,intent(in) :: default
1115  real ,intent(in),optional :: r0
1116  real ,intent(in),optional :: r1
1117  real ,intent(in),optional :: r2
1118  real ,intent(in),optional :: r3
1119  real ,intent(in),optional :: r4
1120  real ,intent(in),optional :: r5
1121  real ,intent(in),optional :: r6
1122  real ,intent(in),optional :: r7
1123  real ,intent(in),optional :: r8
1124  real ,intent(in),optional :: r9
1125  real :: result
1126 
1127  !=== Variables for internal work
1128  logical :: specified
1129  character(*), parameter:: subname = "present_select_Real_auto"
1130  continue
1131 
1132 !!$ call BeginSub(subname, &
1133 !!$ & 'invalid=%y default=%r', &
1134 !!$ & l=(/invalid/), r=(/default/))
1135  specified = .false.
1136 
1137  if ( present(r0) ) then
1138  if ( .not. invalid ) then
1139  result = r0
1140  specified = .true.
1141  elseif ( r0 /= 0.0 ) then
1142  result = r0
1143  specified = .true.
1144  endif
1145  end if
1146 
1147  if ( present(r1) .and. .not. specified ) then
1148  if ( .not. invalid ) then
1149  result = r1
1150  specified = .true.
1151  elseif ( r1 /= 0.0 ) then
1152  result = r1
1153  specified = .true.
1154  endif
1155  end if
1156  if ( present(r2) .and. .not. specified ) then
1157  if ( .not. invalid ) then
1158  result = r2
1159  specified = .true.
1160  elseif ( r2 /= 0.0 ) then
1161  result = r2
1162  specified = .true.
1163  endif
1164  end if
1165  if ( present(r3) .and. .not. specified ) then
1166  if ( .not. invalid ) then
1167  result = r3
1168  specified = .true.
1169  elseif ( r3 /= 0.0 ) then
1170  result = r3
1171  specified = .true.
1172  endif
1173  end if
1174  if ( present(r4) .and. .not. specified ) then
1175  if ( .not. invalid ) then
1176  result = r4
1177  specified = .true.
1178  elseif ( r4 /= 0.0 ) then
1179  result = r4
1180  specified = .true.
1181  endif
1182  end if
1183  if ( present(r5) .and. .not. specified ) then
1184  if ( .not. invalid ) then
1185  result = r5
1186  specified = .true.
1187  elseif ( r5 /= 0.0 ) then
1188  result = r5
1189  specified = .true.
1190  endif
1191  end if
1192  if ( present(r6) .and. .not. specified ) then
1193  if ( .not. invalid ) then
1194  result = r6
1195  specified = .true.
1196  elseif ( r6 /= 0.0 ) then
1197  result = r6
1198  specified = .true.
1199  endif
1200  end if
1201  if ( present(r7) .and. .not. specified ) then
1202  if ( .not. invalid ) then
1203  result = r7
1204  specified = .true.
1205  elseif ( r7 /= 0.0 ) then
1206  result = r7
1207  specified = .true.
1208  endif
1209  end if
1210  if ( present(r8) .and. .not. specified ) then
1211  if ( .not. invalid ) then
1212  result = r8
1213  specified = .true.
1214  elseif ( r8 /= 0.0 ) then
1215  result = r8
1216  specified = .true.
1217  endif
1218  end if
1219  if ( present(r9) .and. .not. specified ) then
1220  if ( .not. invalid ) then
1221  result = r9
1222  specified = .true.
1223  elseif ( r9 /= 0.0 ) then
1224  result = r9
1225  specified = .true.
1226  endif
1227  end if
1228 
1229  if (.not. specified) then
1230  result = default
1231  end if
1232 
1233 !!$ call EndSub(subname, "result=%r", &
1234 !!$ & r=(/result/))
1235 
type(gt_history), target, save, public default