dcstringsprintf.f90 File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine dcstringsprintf (unit, fmt, i, r, d, L, n, c1, c2, c3, ca)
 
subroutine append (unitx, ucur, val, stat)
 

Function/Subroutine Documentation

◆ append()

subroutine dcstringsprintf::append ( character(*), intent(inout)  unitx,
integer, intent(inout)  ucur,
character(*), intent(in)  val,
integer, intent(out)  stat 
)

Definition at line 368 of file dcstringsprintf.f90.

Referenced by dcstringsprintf().

368  !
369  ! unitx に val を付加。その際、unitx がその最大文字列長を越えた場合
370  ! には stat = 2 を返す。
371  !
372  character(*), intent(inout):: unitx ! 最終的に返される文字列
373  integer, intent(inout):: ucur ! unitx の文字数
374  character(*), intent(in) :: val ! unitx に付加される文字列
375  integer, intent(out) :: stat ! ステータス
376  integer :: wrsz ! val の文字列
377  continue
378  ! unitx の最大長を越えた場合には stat = 2 を返す。
379  if (ucur >= len(unitx)) then
380  stat = 2
381  ! 正常時の処理
382  else
383  ! unitx の長さを越えた場合も考慮して unitx に val を付加する。
384  wrsz = min(len(val), len(unitx) - ucur)
385  unitx(1+ucur: wrsz+ucur) = val(1: wrsz)
386  ucur = ucur + wrsz
387  stat = 0
388  if (wrsz < len(val)) stat = 1
389  endif
Here is the caller graph for this function:

◆ dcstringsprintf()

subroutine dcstringsprintf ( character(*), intent(out)  unit,
character(*), intent(in)  fmt,
integer, dimension(:), intent(in), optional  i,
real, dimension(:), intent(in), optional  r,
real(dp), dimension(:), intent(in), optional  d,
logical, dimension(:), intent(in), optional  L,
integer, dimension(:), intent(in), optional  n,
character(*), intent(in), optional  c1,
character(*), intent(in), optional  c2,
character(*), intent(in), optional  c3,
character(*), dimension(:), intent(in), optional  ca 
)

Definition at line 144 of file dcstringsprintf.f90.

References append(), and dc_types::dp.

144  !
145  ! フォーマット文字列 fmt に従って変換された文字列を unit に返します。
146  ! 第2引数 fmt には指示子を含む文字列を与えます。
147  ! 指示子には「<tt>%</tt>」を用います。
148  ! <tt>%</tt> を用いたい場合は 「<tt>%%</tt>」と記述します。
149  ! 指示子および用例に関しての詳細は dc_utils/dcstringsprintf.f90 を参照ください。
150  !
151  use dc_types, only: dp
152  implicit none
153  character(*), intent(out) :: unit
154  character(*), intent(in) :: fmt
155  integer, intent(in), optional:: i(:), n(:)
156  real, intent(in), optional:: r(:)
157  real(DP), intent(in), optional:: d(:)
158  logical, intent(in), optional:: l(:)
159  character(*), intent(in), optional:: c1, c2, c3
160  character(*), intent(in), optional:: ca(:)
161 
162  ! 上記配列引数のカウンタ
163  integer:: ni, nr, nd, nl, nc, na, nn
164  integer:: ucur ! unit に書かれた文字数
165  integer:: endp ! 既に処理された fmt の文字数
166  integer:: cur ! 現在着目中の文字は fmt(cur:cur) である
167  integer:: ptr ! fmt から検索をするときに使用
168  integer:: exp_ptr ! fmt から数値の指数部を検索をするときに使用
169  integer:: minus_ptr ! '-' を検索する時に使用
170  integer:: repeat ! %数字 または %* から決定された繰返し数
171  integer:: m ! 1:repeat の範囲で動くループ変数
172  integer:: stat ! エラー処理
173  character(80):: cbuf ! read/write 文のバッファ
174  character(80):: exp_buf ! real/write 文の指数部のバッファ (実数型用)
175  character(80):: ibuf ! real/write 文のバッファ (整数型用)
176  integer:: len_ibuf ! ibuf の長さ
177  integer:: figs_ibuf ! ibuf の有効な桁数
178  logical:: int_zero_fill ! 先頭を 0 で埋めるかどうかを判定するフラグ (整数型用)
179  integer:: int_figs ! 整数型を出力する際の桁数 (整数型用)
180 continue
181  ni = 0; nr = 0; nd = 0; nl = 0; nc = 0; na = 0; nn = 0
182  unit = ""
183  ucur = 0
184  endp = 0
185  int_figs = 0
186  int_zero_fill = .false.
187  mainloop: do
188  cur = endp + 1
189  if (cur > len(fmt)) exit mainloop
190  !
191  ! リテラルに転写できる文字列 fmt(cur:endp-1) を発見処理
192  !
193  endp = cur - 1 + scan(fmt(cur: ), '%')
194  if (endp > cur) then
195  call append(unit, ucur, fmt(cur:endp-1), stat)
196  if (stat /= 0) exit mainloop
197  else if (endp == cur - 1) then
198  call append(unit, ucur, fmt(cur: ), stat)
199  exit mainloop
200  endif
201  !
202  ! % から書式指定文字までを fmt(cur:endp) とする
203  !
204  cur = endp + 1
205  endp = cur - 1 + scan(fmt(cur: ), 'DdOoXxFfRrBbYySsCcAa%')
206  if (endp < cur) then
207  call append(unit, ucur, fmt(cur-1: ), stat)
208  exit mainloop
209  endif
210  cbuf = fmt(cur:endp-1)
211  !
212  ! %* がある場合、n(:) に渡された数から繰り返し回数を取得
213  !
214  if (cbuf(1:1) == '*') then
215  nn = nn + 1
216  if (nn > size(n)) then
217  repeat = 1
218  else
219  repeat = n(nn)
220  endif
221  ibuf = cbuf(2:)
222  else
223  repeat = 1
224  ibuf = cbuf
225 ! else if (cbuf == '') then
226 ! repeat = 1
227 ! else
228 ! ptr = verify(cbuf, " 0123456789")
229 ! if (ptr > 0) cbuf(ptr: ) = " "
230 ! read(cbuf, "(I80)", iostat=ptr) repeat
231  endif
232  !
233  ! %2d や %04d のように '%' の後ろに数字が指定され、
234  ! かつ d (整数型変数の表示) の場合には先頭に空白
235  ! または 0 を埋める.
236  !
237  if (scan(ibuf(1:1),'1234567890') > 0) then
238  if (ibuf(1:1) == '0') then
239  int_zero_fill = .true.
240  else
241  int_zero_fill = .false.
242  end if
243  read(unit=ibuf, fmt="(i80)") int_figs
244  else
245  int_figs = 0
246  int_zero_fill = .false.
247  endif
248  percentrepeat: do, m = 1, repeat
249  if (m > 1) then
250  call append(unit, ucur, ", ", stat)
251  if (stat /= 0) exit mainloop
252  endif
253  select case(fmt(endp:endp))
254  case('d', 'D')
255  if (.not. present(i)) cycle mainloop
256  ni = ni + 1; if (ni > size(i)) cycle mainloop
257  write(ibuf, "(i20)") i(ni)
258  len_ibuf = len(trim(adjustl(ibuf)))
259  figs_ibuf = verify(ibuf, ' ')
260  cbuf = ' '
261  if (int_figs > len_ibuf) then
262  minus_ptr = scan(ibuf, '-')
263  if (int_zero_fill) then
264  if (minus_ptr /= 0) then
265  len_ibuf = len_ibuf - 1
266  figs_ibuf = figs_ibuf + 1
267  cbuf(1:int_figs-len_ibuf) = '-0000000000000000000'
268  else
269  cbuf(1:int_figs-len_ibuf) = '00000000000000000000'
270  end if
271  end if
272  cbuf(int_figs-len_ibuf+1:) = ibuf(figs_ibuf:20)
273  else
274  cbuf = ibuf(figs_ibuf:20)
275  end if
276  call append(unit, ucur, trim(cbuf), stat)
277  if (stat /= 0) exit mainloop
278  case('o', 'O')
279  if (.not. present(i)) cycle mainloop
280  ni = ni + 1; if (ni > size(i)) cycle mainloop
281  write(cbuf, "(o20)") i(ni)
282  call append(unit, ucur, trim(adjustl(cbuf)), stat)
283  if (stat /= 0) exit mainloop
284  case('x', 'X')
285  if (.not. present(i)) cycle mainloop
286  ni = ni + 1; if (ni > size(i)) cycle mainloop
287  write(cbuf, "(z20)") i(ni)
288  call append(unit, ucur, trim(adjustl(cbuf)), stat)
289  if (stat /= 0) exit mainloop
290  case('f', 'F')
291  if (.not. present(d)) cycle mainloop
292  nd = nd + 1; if (nd > size(d)) cycle mainloop
293  write(cbuf, "(g80.40)") d(nd)
294  cbuf = adjustl(cbuf)
295  exp_ptr = verify(cbuf, ' 1234567890-+.', back=.true.)
296  exp_buf = ' '
297  if (exp_ptr > 0) then
298  exp_buf = cbuf(exp_ptr: )
299  cbuf(exp_ptr: ) = " "
300  end if
301  ptr = verify(cbuf, " 0", back=.true.)
302  if (ptr > 0) cbuf(ptr+1: ) = " "
303  cbuf = trim(cbuf) // trim(exp_buf)
304  call append(unit, ucur, trim(adjustl(cbuf)), stat)
305  if (stat /= 0) exit mainloop
306  case('r', 'R')
307  if (.not. present(r)) cycle mainloop
308  nr = nr + 1; if (nr > size(r)) cycle mainloop
309  write(cbuf, "(g80.40)") r(nr)
310  cbuf = adjustl(cbuf)
311  exp_ptr = verify(cbuf, ' 1234567890-+.', back=.true.)
312  exp_buf = ' '
313  if (exp_ptr > 0) then
314  exp_buf = cbuf(exp_ptr: )
315  cbuf(exp_ptr: ) = " "
316  end if
317  ptr = verify(cbuf, " 0", back=.true.)
318  if (ptr > 0) cbuf(ptr+1: ) = " "
319  cbuf = trim(cbuf) // trim(exp_buf)
320  call append(unit, ucur, trim(adjustl(cbuf)), stat)
321  if (stat /= 0) exit mainloop
322  case('b', 'B')
323  if (.not. present(l)) cycle mainloop
324  nl = nl + 1; if (nl > size(l)) cycle mainloop
325  write(cbuf, "(L1)") l(nl)
326  call append(unit, ucur, trim(adjustl(cbuf)), stat)
327  if (stat /= 0) exit mainloop
328  case('y', 'Y')
329  if (.not. present(l)) cycle mainloop
330  nl = nl + 1; if (nl > size(l)) cycle mainloop
331  if (l(nl)) then
332  call append(unit, ucur, "yes", stat)
333  if (stat /= 0) exit mainloop
334  else
335  call append(unit, ucur, "no", stat)
336  if (stat /= 0) exit mainloop
337  endif
338  case('c', 'C')
339  nc = nc + 1
340  if (nc == 1) then
341  if (.not. present(c1)) cycle percentrepeat
342  call append(unit, ucur, c1, stat)
343  if (stat /= 0) exit mainloop
344  else if (nc == 2) then
345  if (.not. present(c2)) cycle percentrepeat
346  call append(unit, ucur, c2, stat)
347  if (stat /= 0) exit mainloop
348  else if (nc == 3) then
349  if (.not. present(c3)) cycle percentrepeat
350  call append(unit, ucur, c3, stat)
351  if (stat /= 0) exit mainloop
352  endif
353  case('a', 'A')
354  if (.not. present(ca)) cycle mainloop
355  na = na + 1; if (na > size(ca)) cycle mainloop
356  call append(unit, ucur, trim(adjustl(ca(na))), stat)
357  if (stat /= 0) exit mainloop
358  case('%')
359  call append(unit, ucur, '%', stat)
360  if (stat /= 0) exit mainloop
361  end select
362  enddo percentrepeat
363  enddo mainloop
364  return
365 contains
366 
367  subroutine append(unitx, ucur, val, stat)
368  !
369  ! unitx に val を付加。その際、unitx がその最大文字列長を越えた場合
370  ! には stat = 2 を返す。
371  !
372  character(*), intent(inout):: unitx ! 最終的に返される文字列
373  integer, intent(inout):: ucur ! unitx の文字数
374  character(*), intent(in) :: val ! unitx に付加される文字列
375  integer, intent(out) :: stat ! ステータス
376  integer :: wrsz ! val の文字列
377  continue
378  ! unitx の最大長を越えた場合には stat = 2 を返す。
379  if (ucur >= len(unitx)) then
380  stat = 2
381  ! 正常時の処理
382  else
383  ! unitx の長さを越えた場合も考慮して unitx に val を付加する。
384  wrsz = min(len(val), len(unitx) - ucur)
385  unitx(1+ucur: wrsz+ucur) = val(1: wrsz)
386  ucur = ucur + wrsz
387  stat = 0
388  if (wrsz < len(val)) stat = 1
389  endif
390  end subroutine append
391 
integer, parameter, public dp
倍精度実数型変数
Definition: dc_types.f90:83
種別型パラメタを提供します。
Definition: dc_types.f90:49
subroutine append(unitx, ucur, val, stat)
Here is the call graph for this function: