dc_string Module Reference

Detailed Description

Handling character types.

Author
Youhei SASAKI, Yasuhiro MORIKAWA, Eizi TOYODA

This module provides subrouteins handle character type variables.

Data Types

interface  concat
 
interface  cprintf
 
interface  get_array
 
interface  index_ofs
 
interface  lchar
 
interface  printf
 
interface  putline
 
interface  replace
 
interface  roundnum
 
interface  split
 
interface  stoa
 
interface  stod
 
interface  stoi
 
interface  str_to_logical
 
interface  strhead
 
interface  strieq
 
interface  strinclude
 
interface  tochar
 
interface  tolower
 
interface  toupper
 
interface  uchar
 

Functions/Subroutines

logical function strhead_cc (whole, head)
 
logical function strieq_cc (string_a, string_b)
 
logical function str_include_ac (carray, string, ignore_space, ignore_case)
 
logical function str2bool (string)
 
integer function atoi_scalar (string, default)
 
real(dp) function atod_scalar (string_in)
 
subroutine str2ip (int_ptr, string_in)
 
subroutine str2rp (real_ptr, string_in)
 
subroutine str2dp (real_ptr, string_in)
 
character(token) function itoa_scalar (i)
 
character(string) function itoa_array (ibuf)
 
character(token) function rtoa_scalar (x)
 
character(string) function rtoa_array (rbuf)
 
character(token) function dtoa_scalar (d)
 
character(string) function dtoa_array (dbuf)
 
character(token) function ltoa_scalar (l)
 
character(string) function ltoa_array (lbuf)
 
character(string) function, public joinchar (carray, expr)
 
subroutine concat_tail (carray, str, result)
 
character(string) function, dimension(1) str_to_array1 (c1)
 
character(string) function, dimension(2) str_to_array2 (c1, c2)
 
character(string) function, dimension(3) str_to_array3 (c1, c2, c3)
 
character(string) function, dimension(4) str_to_array4 (c1, c2, c3, c4)
 
character(string) function, dimension(5) str_to_array5 (c1, c2, c3, c4, c5)
 
character(string) function, dimension(6) str_to_array6 (c1, c2, c3, c4, c5, c6)
 
character(string) function, dimension(7) str_to_array7 (c1, c2, c3, c4, c5, c6, c7)
 
character(string) function, dimension(8) str_to_array8 (c1, c2, c3, c4, c5, c6, c7, c8)
 
character(string) function, dimension(9) str_to_array9 (c1, c2, c3, c4, c5, c6, c7, c8, c9)
 
character(string) function, dimension(10) str_to_array10 (c1, c2, c3, c4, c5, c6, c7, c8, c9, c10)
 
character(string) function, dimension(11) str_to_array11 (c1, c2, c3, c4, c5, c6, c7, c8, c9, c10, c11)
 
character(string) function, dimension(12) str_to_array12 (c1, c2, c3, c4, c5, c6, c7, c8, c9, c10, c11, c12)
 
subroutine split_cc (str, carray, sep, limit)
 
integer function, public index_ofs (string, start, substr)
 
recursive character(strlen) function, public replace (string, from, to, recursive, start_pos)
 
subroutine cupper (ch)
 
subroutine clower (ch)
 
character(string) function, public uchar (ch)
 
character(string) function, public lchar (ch)
 
character(string) function, public roundnum (num)
 

Function/Subroutine Documentation

◆ atod_scalar()

real(dp) function dc_string::atod_scalar ( character(len = *), intent(in)  string_in)
private

Definition at line 557 of file dc_string.f90.

References dc_types::string.

557  !
558  ! string で与えられる文字型変数を、倍精度実数型変数にして返します。
559  ! もしも string が数値に変換できない場合、0.0 が返ります。
560  !
561  use dc_types, only: string
562  character(len = *), intent(in):: string_in
563  integer:: ios
564  character(len = STRING):: buffer
565  integer:: ipoint, iexp
566  intrinsic scan
567 
568  continue
569 
570  buffer = string_in
571  ! もし整定数をいれてしまった場合は小数点を附加
572  if (index(buffer, '.') == 0) then
573  iexp = scan(buffer, "eEdD")
574  if (iexp /= 0) then
575  buffer(iexp+1: len(buffer)) = buffer(iexp: len(buffer)-1)
576  ipoint = iexp
577  else
578  ipoint = len_trim(buffer) + 1
579  endif
580  buffer(ipoint: ipoint) = '.'
581  endif
582  read(unit=buffer, fmt="(g80.10)", iostat=ios) result
583  if (ios /= 0) result = 0.0
Provides kind type parameter values.
Definition: dc_types.f90:49
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118

◆ atoi_scalar()

integer function dc_string::atoi_scalar ( character(len = *), intent(in)  string,
integer, intent(in), optional  default 
)
private

Definition at line 535 of file dc_string.f90.

535  !
536  ! string で与えられる文字型変数を、整数型変数にして返します。
537  ! もしも string が数値に変換できない場合、default が返ります。
538  ! default を指定しない場合は 0 が返ります。
539  !
540  character(len = *), intent(in):: string
541  integer, intent(in), optional:: default
542  integer:: ios
543 
544  continue
545 
546  read(unit=string, fmt="(i80)", iostat=ios) result
547  if (ios /= 0) then
548  if (present(default)) then
549  result = default
550  else
551  result = 0
552  endif
553  endif
type(gt_history), target, save, public default
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118

◆ clower()

subroutine dc_string::clower ( character(len = *), intent(inout)  ch)
private

Definition at line 1368 of file dc_string.f90.

1368  !
1369  ! 文字列 ch に英字が含まれる場合、その英字を小文字に変換して ch
1370  ! に返します。 英字でない文字や既に小文字になっている文字は
1371  ! そのまま返します。
1372  !
1373  character(len = *), intent(inout):: ch
1374  integer:: i, lch, idx
1375  continue
1376  lch = len(ch)
1377  do, i = 1, lch
1378  idx = ichar(ch(i:i))
1379  if (65 <= idx .and. idx <= 90) then
1380  ch(i:i)=char(idx + 32)
1381  end if
1382  end do

◆ concat_tail()

subroutine dc_string::concat_tail ( character(*), dimension(:), intent(in)  carray,
character(*), intent(in)  str,
character(string), dimension(:), pointer  result 
)
private

Definition at line 893 of file dc_string.f90.

893  !
894  ! 文字型配列 *carray* の各成分の末尾に *str* を追加して
895  ! *result* に返します。*carray* の各成分の末尾の空白は無視されます。
896  !
897  ! result(:) の配列サイズは carray のサイズに応じて自動的に決まります。
898  ! ただし、result(:) は必ず空状態または不定状態で与えてください。
899  ! 既に割り付けられている場合、メモリリークを起こします。
900  !
901  implicit none
902  character(*), intent(in) :: carray(:)
903  character(*), intent(in) :: str
904  character(STRING), pointer:: result(:) ! (out)
905  integer :: i, size_carray
906  continue
907  size_carray = size(carray)
908  allocate(result(size_carray))
909 
910  do i = 1, size_carray
911  result(i) = trim(carray(i)) // str
912  end do
913 

◆ cupper()

subroutine dc_string::cupper ( character(len = *), intent(inout)  ch)

Definition at line 1350 of file dc_string.f90.

1350  !
1351  ! 文字列 ch に英字が含まれる場合、その英字を大文字に変換して ch
1352  ! に返します。 英字でない文字や既に大文字になっている文字は
1353  ! そのまま返します。
1354  !
1355  character(len = *), intent(inout):: ch
1356  integer:: i, lch, idx
1357  continue
1358  lch = len(ch)
1359  do, i = 1, lch
1360  idx = ichar(ch(i:i))
1361  if (97 <= idx .and. idx <= 122) then
1362  ch(i:i)=char(idx - 32)
1363  end if
1364  end do

◆ dtoa_array()

character(string) function dc_string::dtoa_array ( real(dp), dimension(:), intent(in)  dbuf)
private

Definition at line 804 of file dc_string.f90.

804  !
805  ! 倍精度実数型配列 dbuf(:) で与えられる数値を文字型変数にして返します。
806  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
807  ! で区切って返します。
808  !
809  real(DP), intent(in):: dbuf(:)
810  integer:: i
811  continue
812  if (size(dbuf) <= 0) then
813  result = ""
814  return
815  endif
816  result = tochar(dbuf(1))
817  do, i = 2, size(dbuf)
818  result = trim(result) // ", " // trim(tochar(dbuf(i)))
819  enddo

◆ dtoa_scalar()

character(token) function dc_string::dtoa_scalar ( real(dp), intent(in)  d)
private

Definition at line 777 of file dc_string.f90.

777  !
778  ! 倍精度実数型変数 d で与えられる数値を文字型変数にして返します。
779  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
780  ! で区切って返します。
781  !
782  real(DP), intent(in):: d
783  character(len = 32):: buffer, expbuf
784  integer:: ptr, eptr
785  continue
786  write(unit=buffer, fmt="(g32.24)") d
787  eptr = scan(buffer, "eE", back=.true.)
788  expbuf = ''
789  if (eptr > 1) then
790  expbuf = buffer(eptr: )
791  buffer(eptr: ) = " "
792  end if
793 
794  ptr = verify(buffer, " 0", back=.true.)
795  if (ptr > 0) buffer(ptr+1: ) = " "
796 
797  if (eptr > 1) then
798  buffer = buffer(1:len_trim(buffer)) // expbuf
799  end if
800  result = adjustl(buffer)

◆ index_ofs()

integer function, public dc_string::index_ofs ( character(len = *), intent(in)  string,
integer, intent(in)  start,
character(len = *), intent(in)  substr 
)

Definition at line 1243 of file dc_string.f90.

1243  !
1244  ! 文字列 string の start 文字目以降の文字列の中に substr
1245  ! の文字列が含まれている時、その開始文字位置を返します。
1246  ! 含まれない場合は 0 を返します。
1247  ! 返される開始文字位置は文字列 string の先頭から数えます。
1248  !
1249  character(len = *), intent(in):: string
1250  integer, intent(in):: start
1251  character(len = *), intent(in):: substr
1252  intrinsic index
1253  if (start < 1) then
1254  result = 0
1255  return
1256  endif
1257  result = index(string(start: ), substr)
1258  if (result == 0) return
1259  result = start + result - 1
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118

◆ itoa_array()

character(string) function dc_string::itoa_array ( integer, dimension(:), intent(in)  ibuf)
private

Definition at line 712 of file dc_string.f90.

712  !
713  ! 整数型配列変数 ibuf(:) で与えられる数値を文字型変数にして返します。
714  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
715  ! で区切って返します。
716  !
717  integer, intent(in):: ibuf(:)
718  integer:: i
719  continue
720  if (size(ibuf) <= 0) then
721  result = ""
722  return
723  endif
724  result = tochar(ibuf(1))
725  do, i = 2, size(ibuf)
726  result = trim(result) // ", " // trim(tochar(ibuf(i)))
727  enddo

◆ itoa_scalar()

character(token) function dc_string::itoa_scalar ( integer, intent(in)  i)
private

Definition at line 699 of file dc_string.f90.

699  !
700  ! 整数型変数 i で与えられる数値を文字型変数にして返します。
701  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
702  ! で区切って返します。
703  !
704  integer, intent(in):: i
705  character(len = 32):: buffer
706  continue
707  write(unit=buffer, fmt="(i20)") i
708  result = adjustl(buffer)

◆ joinchar()

character(string) function, public dc_string::joinchar ( character(*), dimension(:), intent(in)  carray,
character(*), intent(in), optional  expr 
)

Definition at line 861 of file dc_string.f90.

Referenced by actual_iorange_dump(), dc_args::dcargsget0(), dc_args::dcargshelp0(), dc_args::dcargsputline0(), dc_hash::dchashputline0(), historyaddattrchar0(), historyaddattrdouble0(), historyaddattrdouble1(), historyaddattrint0(), historyaddattrint1(), historyaddattrlogical0(), historyaddattrreal0(), historyaddattrreal1(), historyaddvariable1(), historyaddvariable2(), historyautoaddvariable1(), historyautoallvarfix(), historyautoclose1(), historyautocreate1(), historyautocreate2(), historyautocreate3(), historyaxisaddattrchar0(), historyaxisaddattrdouble0(), historyaxisaddattrdouble1(), historyaxisaddattrint0(), historyaxisaddattrint1(), historyaxisaddattrlogical0(), historyaxisaddattrreal0(), historyaxisaddattrreal1(), 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(), historygettattrchar0(), historygettattrdouble0(), historygettattrdouble1(), historygettattrint0(), historygettattrint1(), historygettattrreal0(), historygettattrreal1(), historyputcharex(), historyputdoubleex(), historyputintex(), historyputline(), historyputrealex(), historyvarinfoaddattrchar0(), historyvarinfoaddattrdouble0(), historyvarinfoaddattrdouble1(), historyvarinfoaddattrint0(), historyvarinfoaddattrint1(), historyvarinfoaddattrlogical0(), historyvarinfoaddattrreal0(), historyvarinfoaddattrreal1(), historyvarinfocopy1(), gtool_historyauto_internal::hstfilecreate(), hstnmlinfoadd(), hstnmlinfoallnamevalid(), hstnmlinfoallvarinicheck(), hstnmlinfoassocgthist(), hstnmlinfoclose(), hstnmlinfocreate(), hstnmlinfodelete(), hstnmlinfoenddefine(), hstnmlinfogetnames(), hstnmlinfoinquire(), hstnmlinfonames(), hstnmlinfooutputstep(), hstnmlinfooutputstepdisable(), hstnmlinfooutputvalid(), hstnmlinfoputline(), hstnmlinforedefine(), hstnmlinforesetdefault(), and hstnmlinfosetvalidname().

861  !
862  ! 文字型配列 carray に与えた複数の文字列をカンマと空白
863  ! 「<tt>, </tt>」 で区切った1つの文字列にして返します。
864  ! expr に文字列を与えると、その文字列を区切り文字として用います。
865  !
866  implicit none
867  character(*) , intent(in) :: carray(:)
868  character(*) , intent(in), optional :: expr
869 
870  character(2) ,parameter :: default = ', '
871  character(STRING) :: delimiter
872  integer :: dellen, i
873  continue
874  if ( present(expr) ) then
875  delimiter = expr
876  dellen = len(expr)
877  else
878  delimiter = default
879  dellen = len(default)
880  endif
881  if (size(carray) <= 0) then
882  result = ""
883  return
884  endif
885  result = trim(carray(1))
886  do, i = 2, size(carray)
887  result = trim(result) // delimiter(1:dellen) // trim(carray(i))
888  enddo
type(gt_history), target, save, public default

◆ lchar()

character(string) function, public dc_string::lchar ( character(len = *), intent(in)  ch)

Definition at line 1397 of file dc_string.f90.

1397  !
1398  ! 文字列 ch に英字が含まれる場合、その英字を小文字に変換して返します。
1399  ! 英字でない文字や既に小文字になっている文字はそのまま返します。
1400  !
1401  character(len = *), intent(in):: ch
1402  continue
1403  result = ch
1404  call tolower(result)

◆ ltoa_array()

character(string) function dc_string::ltoa_array ( logical, dimension(:), intent(in)  lbuf)
private

Definition at line 838 of file dc_string.f90.

838  !
839  ! 論理型配列 lbuf(:) で与えられる数値を文字型変数にして返します。
840  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
841  ! で区切って返します。
842  !
843  logical, intent(in):: lbuf(:)
844  integer:: i
845  continue
846  if (size(lbuf) <= 0) then
847  result = ""
848  return
849  endif
850  result = tochar(lbuf(1))
851  do, i = 2, size(lbuf)
852  result = trim(result) // ", " // trim(tochar(lbuf(i)))
853  enddo

◆ ltoa_scalar()

character(token) function dc_string::ltoa_scalar ( logical, intent(in)  l)
private

Definition at line 823 of file dc_string.f90.

823  !
824  ! 論理型変数 l で与えられる数値を文字型変数にして返します。
825  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
826  ! で区切って返します。
827  !
828  logical, intent(in):: l
829  continue
830  if (l) then
831  result = ".true."
832  else
833  result = ".false."
834  end if

◆ replace()

recursive character(strlen) function, public dc_string::replace ( character(*), intent(in)  string,
character(*), intent(in)  from,
character(*), intent(in)  to,
logical, intent(in), optional  recursive,
integer, intent(in), optional  start_pos 
)

Definition at line 1264 of file dc_string.f90.

References dc_types::string.

1264  !
1265  ! 文字列 *string* に文字列 *from* が含まれる場合, その部分を文字列 *to*
1266  ! に置換して返します. 文字列 *from* が含まれない場合は *string*
1267  ! をそのまま返します. *from* が複数含まれる場合, 先頭の *from*
1268  ! のみが置換されます.
1269  !
1270  ! 全ての *from* を *to* へ変換したい場合には,
1271  ! オプショナル引数 *recursive* に .true. を与えてください.
1272  !
1273  ! デフォルトでは, 文字列の最初から検索を行います.
1274  ! オプショナル引数 *start_pos* を与える場合,
1275  ! *start_pos* 文字目から検索を行います.
1276  !
1277  ! If a string *from* is included in *string*, the string is
1278  ! replace to *to*, and the replaced string is returned.
1279  ! If a string *from* is not included, *string* is returned
1280  ! without change.
1281  ! When multiple *from* are included, only first *from* is replaced.
1282  !
1283  ! In order to replace all *from* to *to*, give ".true." to
1284  ! optional argument *recursive*.
1285  !
1286  ! By default, the string is searched from the top.
1287  ! If optional argument *start_pos* is given,
1288  ! the search is started from *start_pos*.
1289  !
1290  use dc_types, only: strlen => string
1291  implicit none
1292  character(STRLEN):: result
1293  character(*), intent(in):: string, from, to
1294  logical, intent(in), optional:: recursive
1295  integer, intent(in), optional:: start_pos
1296  integer:: sp
1297  integer:: i, isa, isb, iea, ieb
1298  integer:: ir
1299  continue
1300  if ( present(start_pos) ) then
1301  sp = start_pos
1302  else
1303  sp = 1
1304  end if
1305  if ( sp < 1 ) then
1306  sp = 1
1307  end if
1308 
1309  result = string
1310  i = index(result(sp:), from)
1311  if (i == 0) return
1312  i = i + sp - 1
1313  isa = i + len(from)
1314  isb = i + len(to)
1315  if (len(to) < len(from)) then
1316  iea = len(result)
1317  ieb = len(result) + len(to) - len(from)
1318  else
1319  iea = len(result) + len(from) - len(to)
1320  ieb = len(result)
1321  endif
1322  if (len(to) /= len(from)) result(isb:ieb) = result(isa:iea)
1323  result(i:i+len(to)-1) = to
1324 
1325  !-----------------------------------
1326  ! 再帰的処理
1327  ! Recursive process
1328  ir = index(result(i+len(to):), from)
1329  if ( len_trim(from) == 0 ) then
1330  ir = index(trim(result(i+len(to):)), from)
1331  end if
1332  if (ir /= 0) then
1333  if ( present(recursive) ) then
1334  if ( recursive ) then
1335  result = replace( string = result, &
1336  & from = from, to = to, &
1337  & recursive = recursive, &
1338  & start_pos = i+len(to) )
1339  end if
1340  end if
1341  end if
1342 
Provides kind type parameter values.
Definition: dc_types.f90:49
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118

◆ roundnum()

character(string) function, public dc_string::roundnum ( character(*), intent(in)  num)

Definition at line 1408 of file dc_string.f90.

1408  !
1409  ! '0.30000001' や '12.999998' などの丸め誤差によって端数が残って
1410  ! しまっている数値表記を '0.3' や '13.' などに整形して返します.
1411  !
1412  character(*), intent(in):: num
1413  character(STRING):: nrv, enrv
1414  integer:: i, moving_up, nrvi, dig, zero_stream
1415  continue
1416  !
1417  ! 実数でないものについてはそのまま返す.
1418  !
1419  if ( scan('.', trim(num) ) == 0 ) then
1420  result = num
1421  return
1422  end if
1423  nrv = num
1424 
1425  !
1426  ! 指数部を避けておく.
1427  !
1428  enrv = ''
1429  i = scan(nrv, "eE", back=.true.)
1430  if ( i > 1 ) then
1431  enrv = nrv(i:)
1432  nrv(i:) = " "
1433  elseif ( i == 1 ) then
1434  result = nrv
1435  return
1436  end if
1437 
1438  !
1439  ! 0.30000001 などの末尾の 1 のような, ゴミの桁の数値を掃除し,
1440  ! 0.3000000 などに整形.
1441  !
1442  if ( index( trim( nrv ), '.') - len_trim( nrv ) < -7 ) then
1443  do while ( index('567890.', nrv(len_trim(nrv):len_trim(nrv)) ) == 0 )
1444  if ( len_trim(nrv) < 2 ) exit
1445  nrv = nrv(1:len_trim(nrv)-1)
1446  end do
1447  end if
1448 
1449  !
1450  ! 0.30000001986 などの末尾の 1 以降のゴミの桁の数値を掃除し,
1451  ! 0.3000000 などに整形.
1452  !
1453  if ( index( trim( nrv ), '.') - len_trim( nrv ) < -7 ) then
1454  dig = index( trim( nrv ), '.') + 1
1455  zero_stream = 0
1456  do while ( dig < len_trim( nrv ) )
1457  if ( nrv(dig:dig) == "0" ) then
1458  zero_stream = zero_stream + 1
1459  else
1460  zero_stream = 0
1461  end if
1462  if ( zero_stream > 7 ) then
1463  nrv(dig:len_trim(nrv)) = '0'
1464  exit
1465  end if
1466  dig = dig + 1
1467  end do
1468  end if
1469 
1470  !
1471  ! 0.3000000 などの末尾の 0 を掃除し,
1472  ! 0.3 などに整形.
1473  !
1474  if ( index( trim( nrv ), '.') /= 0 ) then
1475  do while ( index('123456789.', nrv(len_trim(nrv):len_trim(nrv)) ) == 0 )
1476  if ( len_trim(nrv) < 2 ) exit
1477  nrv = nrv(1:len_trim(nrv)-1)
1478  end do
1479  end if
1480 
1481  !
1482  ! 0.89999998 などの末尾の 8 のような, ゴミの桁の数値を掃除し,
1483  ! 0.8999999 などに整形.
1484  !
1485  moving_up = 0
1486  if ( index( trim( nrv ), '.') - len_trim( nrv ) < -7 ) then
1487  do while ( index('12345690.', nrv(len_trim(nrv):len_trim(nrv)) ) == 0 )
1488  if ( len_trim(nrv) < 2 ) exit
1489  nrv = nrv(1:len_trim(nrv)-1)
1490  end do
1491  moving_up = 1
1492  end if
1493 
1494  !
1495  ! 0.8999999 などの末尾の 9 を掃除し, 繰り上げて
1496  ! 0.9 などに整形.
1497  !
1498  if ( moving_up > 0 ) then
1499  do while ( index('012345678.', nrv(len_trim(nrv):len_trim(nrv)) ) == 0 )
1500  if ( len_trim(nrv) < 2 ) exit
1501  nrv = nrv(1:len_trim(nrv)-1)
1502  end do
1503  end if
1504 
1505  i = len_trim(nrv)
1506  do while ( moving_up > 0 .and. i > 0 )
1507  if ( index('.', nrv(i:i)) /= 0 ) then
1508  i = i - 1
1509  cycle
1510  end if
1511  nrvi = stoi( nrv(i:i) ) + moving_up
1512 
1513  if ( nrvi < 10 ) then
1514  nrv(i:i) = trim( tochar( nrvi ) )
1515  exit
1516  else
1517  nrv(i:i) = '0'
1518  if ( i < 2 ) then
1519  nrv = '10'
1520  exit
1521  else
1522  i = i - 1
1523  cycle
1524  end if
1525  end if
1526  if ( len_trim(nrv) < 2 ) exit
1527  nrv = nrv(1:len_trim(nrv)-1)
1528  end do
1529 
1530  !
1531  ! 0.3000000 などの末尾の 0 を掃除し,
1532  ! 0.3 などに整形.
1533  !
1534  if ( index( trim( nrv ), '.') /= 0 ) then
1535  do while ( index('123456789.', nrv(len_trim(nrv):len_trim(nrv)) ) == 0 )
1536  if ( len_trim(nrv) < 2 ) exit
1537  nrv = nrv(1:len_trim(nrv)-1)
1538  end do
1539  end if
1540 
1541  !
1542  ! 指数部を復帰する
1543  !
1544  if ( len_trim(enrv) > 0 ) then
1545  nrv = trim(nrv) // enrv
1546  end if
1547 
1548  result = nrv

◆ rtoa_array()

character(string) function dc_string::rtoa_array ( real, dimension(:), intent(in)  rbuf)
private

Definition at line 758 of file dc_string.f90.

758  !
759  ! 単精度実数型配列 rbuf(:)、で与えられる数値を文字型変数にして返します。
760  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
761  ! で区切って返します。
762  !
763  real, intent(in):: rbuf(:)
764  integer:: i
765  continue
766  if (size(rbuf) <= 0) then
767  result = ""
768  return
769  endif
770  result = tochar(rbuf(1))
771  do, i = 2, size(rbuf)
772  result = trim(result) // ", " // trim(tochar(rbuf(i)))
773  enddo

◆ rtoa_scalar()

character(token) function dc_string::rtoa_scalar ( real, intent(in)  x)
private

Definition at line 731 of file dc_string.f90.

731  !
732  ! 単精度実数型変数 x で与えられる数値を文字型変数にして返します。
733  ! 配列が与えられる場合、各要素をカンマと空白「<tt>, </tt>」
734  ! で区切って返します。
735  !
736  real, intent(in):: x
737  character(len = 16):: buffer, expbuf
738  integer:: ptr, eptr
739  continue
740  write(unit=buffer, fmt="(g16.8)") x
741  eptr = scan(buffer, "eE", back=.true.)
742  expbuf = ''
743  if (eptr > 1) then
744  expbuf = buffer(eptr: )
745  buffer(eptr: ) = " "
746  end if
747 
748  ptr = verify(buffer, " 0", back=.true.)
749  if (ptr > 0) buffer(ptr+1: ) = " "
750 
751  if (eptr > 1) then
752  buffer = buffer(1:len_trim(buffer)) // expbuf
753  end if
754  result = adjustl(buffer)

◆ split_cc()

subroutine dc_string::split_cc ( character(*), intent(in)  str,
character(*), dimension(:), pointer  carray,
character(*), intent(in)  sep,
integer, intent(in), optional  limit 
)
private

Definition at line 1143 of file dc_string.f90.

References dc_types::string.

1143  !
1144  ! *str* で与えられた文字列を 文字列 *sep* で分解し,
1145  ! ポインタ配列 *carray* に返します.
1146  ! *carray* は必ず空状態にして与えてください. 割り付け状態の
1147  ! 場合にはエラーを返します.
1148  !
1149  ! *limit* に正の数を与えた場合, 最大 *limit* 個のフィールドに分割
1150  ! します. 負の数や 0 の場合は省略した場合と同じになります. *str*
1151  ! の末尾の空白は除去されます. *sep* に空文字を代入する場合, 空白
1152  ! 文字で分割されます.
1153  !
1154  use dc_types, only: string
1155  implicit none
1156  character(*), intent(in):: str
1157  character(*), pointer:: carray(:) !(out)
1158  character(*), intent(in):: sep
1159  integer, intent(in), optional:: limit
1160  integer :: num, cur, i, limitnum
1161  character(STRING) :: substr
1162  logical :: end_flag
1163  continue
1164  if (present(limit)) then
1165  if (limit > 0) then
1166  limitnum = limit
1167  else
1168  limitnum = 0
1169  end if
1170  else
1171  limitnum = 0
1172  end if
1173 
1174  if (len(trim(sep)) == 0) then
1175  num = 1
1176  substr = str
1177  ! 重複して無駄だが carray を allocate するため, 何分割するか
1178  ! 調べ, num に格納する.
1179  do
1180  cur = index(trim(substr), ' ')
1181  if (cur == 0) exit
1182  num = num + 1
1183  substr = adjustl(substr(cur + len(sep) :len(substr)))
1184  end do
1185 
1186  if (limitnum /= 0 .and. num > limitnum) num = limitnum
1187  allocate(carray(num))
1188 
1189  substr = str
1190  end_flag = .false.
1191  do i = 1, num
1192  cur = index(trim(substr), ' ')
1193  if (cur == 0 .or. i == num) end_flag = .true.
1194  if (end_flag) then
1195  carray(i) = substr
1196  exit
1197  else
1198  carray(i) = substr(1:cur - 1)
1199  end if
1200  substr = adjustl(substr(cur + len(sep) :len(substr)))
1201  end do
1202 
1203  else
1204  num = 1
1205  substr = str
1206  ! 重複して無駄だが carray を allocate するため, 何分割するか
1207  ! 調べ, num に格納する.
1208  do
1209  cur = index(substr, trim(sep))
1210  if (cur == 0) exit
1211  num = num + 1
1212  substr = substr(cur + len(sep) :len(substr))
1213  end do
1214 
1215  if (limitnum /= 0 .and. num > limitnum) num = limitnum
1216  allocate(carray(num))
1217 
1218  substr = str
1219  end_flag = .false.
1220  do i = 1, num
1221  cur = index(substr, trim(sep))
1222  if (cur == 0 .or. i == num) end_flag = .true.
1223  if (end_flag) then
1224  carray(i) = substr
1225  exit
1226  else
1227  carray(i) = substr(1:cur - 1)
1228  end if
1229  substr = substr(cur + len(sep) :len(substr))
1230  end do
1231  end if
1232 
1233  return
1234 
Provides kind type parameter values.
Definition: dc_types.f90:49
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118

◆ str2bool()

logical function dc_string::str2bool ( character(len = *), intent(in)  string)
private

Definition at line 515 of file dc_string.f90.

515  !
516  ! string で与えられる文字型変数を論理型にして返します。 string
517  ! が空、 または 0、 0.0、 0.0D0、 0.0d0、 .false.、 .FALSE.、 f、
518  ! F、 false、 FALSE の場合には <tt>.false.</tt> が返ります。
519  ! それ以外の場合には <tt>.true.</tt> が返ります。
520  !
521  character(len = *), intent(in):: string
522 
523  continue
524 
525  select case(string)
526  case ("", "0", "0.0", "0.0D0", "0.0d0", ".false.", ".FALSE.", &
527  & "f", "F", "false", "FALSE")
528  result = .false.
529  case default
530  result = .true.
531  end select
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118

◆ str2dp()

subroutine dc_string::str2dp ( real(dp), dimension(:), pointer  real_ptr,
character(len = *), intent(in)  string_in 
)
private

Definition at line 659 of file dc_string.f90.

659  !
660  ! string で与えられる文字型変数をカンマ「,」で区切り、
661  ! 倍精度実数型配列ポインタ real_ptr(:) にして返します。
662  ! real_ptr(:) の配列サイズは string の内容に応じて自動的に決まります。
663  !
664  ! ただし、real_ptr(:) は必ず空状態または不定状態で与えてください。
665  ! 既に割り付けられている場合、メモリリークを起こします。
666  !
667  real(DP), pointer:: real_ptr(:) !(out)
668  character(len = *), intent(in):: string_in
669  integer:: i, j, idx, nvalues
670  continue
671  nvalues = 1
672  i = 1
673  do
674  idx = index(string_in(i: ), ',')
675  if (idx == 0) exit
676  i = i + idx - 1 + 1
677  nvalues = nvalues + 1
678  enddo
679  allocate(real_ptr(nvalues))
680  i = 1
681  j = 1
682  do
683  idx = index(string_in(i: ), ',')
684  if (idx == 0) then
685  real_ptr(j) = stod(string_in(i: ))
686  exit
687  endif
688  real_ptr(j) = stod(string_in(i: i+idx-2))
689  i = i + idx - 1 + 1
690  j = j + 1
691  enddo

◆ str2ip()

subroutine dc_string::str2ip ( integer, dimension(:), pointer  int_ptr,
character(len = *), intent(in)  string_in 
)

Definition at line 587 of file dc_string.f90.

587  !
588  ! string で与えられる文字型変数をカンマ「,」で区切り、
589  ! 整数型配列ポインタ int_ptr(:) にして返します。 int_ptr(:)
590  ! の配列サイズは string の内容に応じて自動的に決まります。
591  !
592  ! ただし、int_ptr(:) は必ず空状態または不定状態で与えてください。
593  ! 既に割り付けられている場合、メモリリークを起こします。
594  !
595  integer, pointer:: int_ptr(:) !(out)
596  character(len = *), intent(in):: string_in
597  integer:: i, j, idx, nvalues
598  continue
599  nvalues = 1
600  i = 1
601  do
602  idx = index(string_in(i: ), ',')
603  if (idx == 0) exit
604  i = i + idx - 1 + 1
605  nvalues = nvalues + 1
606  enddo
607  allocate(int_ptr(nvalues))
608  i = 1
609  j = 1
610  do
611  idx = index(string_in(i: ), ',')
612  if (idx == 0) then
613  int_ptr(j) = stoi(string_in(i: ))
614  exit
615  endif
616  int_ptr(j) = stod(string_in(i: i+idx-2))
617  i = i + idx - 1 + 1
618  j = j + 1
619  enddo

◆ str2rp()

subroutine dc_string::str2rp ( real, dimension(:), pointer  real_ptr,
character(len = *), intent(in)  string_in 
)
private

Definition at line 623 of file dc_string.f90.

623  !
624  ! string で与えられる文字型変数をカンマ「,」で区切り、
625  ! 単精度実数型配列ポインタ real_ptr(:) にして返します。
626  ! real_ptr(:) の配列サイズは string の内容に応じて自動的に決まります。
627  !
628  ! ただし、real_ptr(:) は必ず空状態または不定状態で与えてください。
629  ! 既に割り付けられている場合、メモリリークを起こします。
630  !
631  real, pointer:: real_ptr(:) !(out)
632  character(len = *), intent(in):: string_in
633  integer:: i, j, idx, nvalues
634  continue
635  nvalues = 1
636  i = 1
637  do
638  idx = index(string_in(i: ), ',')
639  if (idx == 0) exit
640  i = i + idx - 1 + 1
641  nvalues = nvalues + 1
642  enddo
643  allocate(real_ptr(nvalues))
644  i = 1
645  j = 1
646  do
647  idx = index(string_in(i: ), ',')
648  if (idx == 0) then
649  real_ptr(j) = stod(string_in(i: ))
650  exit
651  endif
652  real_ptr(j) = stod(string_in(i: i+idx-2))
653  i = i + idx - 1 + 1
654  j = j + 1
655  enddo

◆ str_include_ac()

logical function dc_string::str_include_ac ( character(*), dimension(:), intent(in)  carray,
character(*), intent(in)  string,
logical, intent(in), optional  ignore_space,
logical, intent(in), optional  ignore_case 
)
private

Definition at line 446 of file dc_string.f90.

References strieq_cc().

446  !
447  ! 文字型配列引数 *carray* が文字型引数 *string* と等しい要素を持つ場合に
448  ! .true. を返します.
449  !
450  ! 文字列の前後の空白は無視されます.
451  ! オプショナル引数 *ignore_space* に .false. を
452  ! 与えた場合には文字列先頭の空白を無視しません.
453  !
454  ! オプショナル引数 *ignore_case* に .true. を与えた場合には
455  ! 大文字, 小文字の違いを無視して比較します.
456  !
457  ! If an character array argument *carray* has the same
458  ! as character argument *string*, ".true." is returned.
459  !
460  ! And beginning and trailing spaces are ignored.
461  ! If ".false." is given to an optional argument *ignore_space*,
462  ! beginning spaces are not ignored.
463  !
464  ! If ".true." is given to an optional argument *ignore_case*,
465  ! this function ignores case.
466  !
467  character(*), intent(in):: carray(:)
468  character(*), intent(in):: string
469  logical, intent(in), optional:: ignore_space
470  logical, intent(in), optional:: ignore_case
471  integer:: array_size, i
472  logical:: ignore_space_work, ignore_case_work
473 
474  continue
475 
476  ignore_space_work = .true.
477  if ( present(ignore_space) ) then
478  if ( .not. ignore_space ) then
479  ignore_space_work = .false.
480  end if
481  end if
482 
483  ignore_case_work = .false.
484  if ( present(ignore_case) ) then
485  if ( ignore_case ) then
486  ignore_case_work = .true.
487  end if
488  end if
489 
490  array_size = size(carray)
491  do i = 1, array_size
492  if ( ignore_space_work ) then
493  if ( ignore_case_work ) then
494  result = &
495  & strieq_cc( trim( adjustl( carray(i) ) ), &
496  & trim( adjustl( string ) ) )
497  else
498  result = &
499  & ( trim( adjustl( carray(i) ) ) == trim( adjustl( string ) ) )
500  end if
501 
502  else
503  if ( ignore_case_work ) then
504  result = &
505  & strieq_cc( trim( carray(i) ), trim( string ) )
506  else
507  result = ( trim(carray(i)) == trim(string) )
508  end if
509  end if
510  if (result) return
511  end do
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118
Here is the call graph for this function:

◆ str_to_array1()

character(string) function, dimension(1) dc_string::str_to_array1 ( character(*), intent(in)  c1)
private

Definition at line 917 of file dc_string.f90.

917  !
918  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
919  !
920  ! 1 から 1 個までの引数を与えることが可能です。
921  !
922  character(*), intent(in) :: c1
923  character(STRING) :: result(1)
924 
925  continue
926  result(1) = c1

◆ str_to_array10()

character(string) function, dimension(10) dc_string::str_to_array10 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5,
character(*), intent(in)  c6,
character(*), intent(in)  c7,
character(*), intent(in)  c8,
character(*), intent(in)  c9,
character(*), intent(in)  c10 
)
private

Definition at line 1070 of file dc_string.f90.

1070  !
1071  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
1072  !
1073  ! 1 から 10 個までの引数を与えることが可能です。
1074  !
1075  character(*), intent(in) :: c1,c2,c3,c4,c5,c6,c7,c8,c9,c10
1076  character(STRING) :: result(10)
1077 
1078  continue
1079  result(1) = c1
1080  result(2) = c2
1081  result(3) = c3
1082  result(4) = c4
1083  result(5) = c5
1084  result(6) = c6
1085  result(7) = c7
1086  result(8) = c8
1087  result(9) = c9
1088  result(10) = c10

◆ str_to_array11()

character(string) function, dimension(11) dc_string::str_to_array11 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5,
character(*), intent(in)  c6,
character(*), intent(in)  c7,
character(*), intent(in)  c8,
character(*), intent(in)  c9,
character(*), intent(in)  c10,
character(*), intent(in)  c11 
)
private

Definition at line 1092 of file dc_string.f90.

1092  !
1093  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
1094  !
1095  ! 1 から 11 個までの引数を与えることが可能です。
1096  !
1097  character(*), intent(in) :: c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11
1098  character(STRING) :: result(11)
1099 
1100  continue
1101  result(1) = c1
1102  result(2) = c2
1103  result(3) = c3
1104  result(4) = c4
1105  result(5) = c5
1106  result(6) = c6
1107  result(7) = c7
1108  result(8) = c8
1109  result(9) = c9
1110  result(10) = c10
1111  result(11) = c11

◆ str_to_array12()

character(string) function, dimension(12) dc_string::str_to_array12 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5,
character(*), intent(in)  c6,
character(*), intent(in)  c7,
character(*), intent(in)  c8,
character(*), intent(in)  c9,
character(*), intent(in)  c10,
character(*), intent(in)  c11,
character(*), intent(in)  c12 
)
private

Definition at line 1115 of file dc_string.f90.

1115  !
1116  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
1117  !
1118  ! 1 から 12 個までの引数を与えることが可能です。
1119  !
1120  character(*), intent(in) :: c1,c2,c3,c4,c5,c6,c7,c8,c9,c10,c11,c12
1121  character(STRING) :: result(12)
1122 
1123  continue
1124  result(1) = c1
1125  result(2) = c2
1126  result(3) = c3
1127  result(4) = c4
1128  result(5) = c5
1129  result(6) = c6
1130  result(7) = c7
1131  result(8) = c8
1132  result(9) = c9
1133  result(10) = c10
1134  result(11) = c11
1135  result(12) = c12

◆ str_to_array2()

character(string) function, dimension(2) dc_string::str_to_array2 ( character(*), intent(in)  c1,
character(*), intent(in)  c2 
)
private

Definition at line 930 of file dc_string.f90.

930  !
931  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
932  !
933  ! 1 から 2 個までの引数を与えることが可能です。
934  !
935  character(*), intent(in) :: c1,c2
936  character(STRING) :: result(2)
937 
938  continue
939  result(1) = c1
940  result(2) = c2

◆ str_to_array3()

character(string) function, dimension(3) dc_string::str_to_array3 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3 
)
private

Definition at line 944 of file dc_string.f90.

944  !
945  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
946  !
947  ! 1 から 3 個までの引数を与えることが可能です。
948  !
949  character(*), intent(in) :: c1,c2,c3
950  character(STRING) :: result(3)
951 
952  continue
953  result(1) = c1
954  result(2) = c2
955  result(3) = c3

◆ str_to_array4()

character(string) function, dimension(4) dc_string::str_to_array4 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4 
)
private

Definition at line 959 of file dc_string.f90.

959  !
960  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
961  !
962  ! 1 から 4 個までの引数を与えることが可能です。
963  !
964  character(*), intent(in) :: c1,c2,c3,c4
965  character(STRING) :: result(4)
966 
967  continue
968  result(1) = c1
969  result(2) = c2
970  result(3) = c3
971  result(4) = c4

◆ str_to_array5()

character(string) function, dimension(5) dc_string::str_to_array5 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5 
)
private

Definition at line 975 of file dc_string.f90.

975  !
976  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
977  !
978  ! 1 から 5 個までの引数を与えることが可能です。
979  !
980  character(*), intent(in) :: c1,c2,c3,c4,c5
981  character(STRING) :: result(5)
982 
983  continue
984  result(1) = c1
985  result(2) = c2
986  result(3) = c3
987  result(4) = c4
988  result(5) = c5

◆ str_to_array6()

character(string) function, dimension(6) dc_string::str_to_array6 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5,
character(*), intent(in)  c6 
)
private

Definition at line 992 of file dc_string.f90.

992  !
993  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
994  !
995  ! 1 から 6 個までの引数を与えることが可能です。
996  !
997  character(*), intent(in) :: c1,c2,c3,c4,c5,c6
998  character(STRING) :: result(6)
999 
1000  continue
1001  result(1) = c1
1002  result(2) = c2
1003  result(3) = c3
1004  result(4) = c4
1005  result(5) = c5
1006  result(6) = c6

◆ str_to_array7()

character(string) function, dimension(7) dc_string::str_to_array7 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5,
character(*), intent(in)  c6,
character(*), intent(in)  c7 
)
private

Definition at line 1010 of file dc_string.f90.

1010  !
1011  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
1012  !
1013  ! 1 から 7 個までの引数を与えることが可能です。
1014  !
1015  character(*), intent(in) :: c1,c2,c3,c4,c5,c6,c7
1016  character(STRING) :: result(7)
1017 
1018  continue
1019  result(1) = c1
1020  result(2) = c2
1021  result(3) = c3
1022  result(4) = c4
1023  result(5) = c5
1024  result(6) = c6
1025  result(7) = c7

◆ str_to_array8()

character(string) function, dimension(8) dc_string::str_to_array8 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5,
character(*), intent(in)  c6,
character(*), intent(in)  c7,
character(*), intent(in)  c8 
)
private

Definition at line 1029 of file dc_string.f90.

1029  !
1030  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
1031  !
1032  ! 1 から 8 個までの引数を与えることが可能です。
1033  !
1034  character(*), intent(in) :: c1,c2,c3,c4,c5,c6,c7,c8
1035  character(STRING) :: result(8)
1036 
1037  continue
1038  result(1) = c1
1039  result(2) = c2
1040  result(3) = c3
1041  result(4) = c4
1042  result(5) = c5
1043  result(6) = c6
1044  result(7) = c7
1045  result(8) = c8

◆ str_to_array9()

character(string) function, dimension(9) dc_string::str_to_array9 ( character(*), intent(in)  c1,
character(*), intent(in)  c2,
character(*), intent(in)  c3,
character(*), intent(in)  c4,
character(*), intent(in)  c5,
character(*), intent(in)  c6,
character(*), intent(in)  c7,
character(*), intent(in)  c8,
character(*), intent(in)  c9 
)
private

Definition at line 1049 of file dc_string.f90.

1049  !
1050  ! 異なる長さの複数の文字型変数を 1 つの文字型配列に変換します。
1051  !
1052  ! 1 から 9 個までの引数を与えることが可能です。
1053  !
1054  character(*), intent(in) :: c1,c2,c3,c4,c5,c6,c7,c8,c9
1055  character(STRING) :: result(9)
1056 
1057  continue
1058  result(1) = c1
1059  result(2) = c2
1060  result(3) = c3
1061  result(4) = c4
1062  result(5) = c5
1063  result(6) = c6
1064  result(7) = c7
1065  result(8) = c8
1066  result(9) = c9

◆ strhead_cc()

logical function dc_string::strhead_cc ( character(len = *), intent(in)  whole,
character(len = *), intent(in)  head 
)

Definition at line 402 of file dc_string.f90.

402  !
403  ! 文字列 head と文字列 whole の先頭部分 (head と同じ文字列長)
404  ! とを比較し、同じものならば .true. を、異なる場合には .false.
405  ! を返します。 whole の文字列長が head の文字列長よりも短い場合には
406  ! .false. を返します。
407  !
408  character(len = *), intent(in):: whole
409  character(len = *), intent(in):: head
410 
411  continue
412 
413  result = (len(whole) >= len(head))
414  if (.not. result) return
415  result = (whole(1:len(head)) == head)
416 

◆ strieq_cc()

logical function dc_string::strieq_cc ( character(len = *), intent(in)  string_a,
character(len = *), intent(in)  string_b 
)
private

Definition at line 420 of file dc_string.f90.

Referenced by str_include_ac().

420  !
421  ! 大文字・小文字を無視して文字列の比較を行います。
422  ! 文字列 string_a と文字列 string_b を比較し、同じものならば
423  ! .true. を、異なる場合には .false. を返します。
424  !
425  !--
426  ! ※ 注意書き ※
427  !
428  ! コンパイラによっては character(len = len(string_a)):: abuf
429  ! が通らないため, 文字数を dc_types で提供される種別型
430  ! パラメタ STRING で制限
431  !++
432  !
433  character(len = *), intent(in):: string_a
434  character(len = *), intent(in):: string_b
435  character(len = STRING):: abuf
436  character(len = STRING):: bbuf
437  abuf = string_a
438  bbuf = string_b
439  call toupper(abuf)
440  call toupper(bbuf)
441  result = (abuf == bbuf)
Here is the caller graph for this function:

◆ uchar()

character(string) function, public dc_string::uchar ( character(len = *), intent(in)  ch)

Definition at line 1386 of file dc_string.f90.

1386  !
1387  ! 文字列 ch に英字が含まれる場合、その英字を大文字に変換して返します。
1388  ! 英字でない文字や既に大文字になっている文字はそのまま返します。
1389  !
1390  character(len = *), intent(in):: ch
1391  continue
1392  result = ch
1393  call toupper(result)