1! { dg-do run }
2
3!$omp declare reduction (foo : character(kind=1, len=*) &
4!$omp & : omp_out = trim(omp_out) // omp_in) initializer (omp_priv = '')
5!$omp declare reduction (bar : character(kind=1, len=:) &
6!$omp & : omp_out = trim(omp_in) // omp_out) initializer (omp_priv = '')
7!$omp declare reduction (baz : character(kind=1, len=1) &
8!$omp & : omp_out = char (ichar (omp_out) + ichar (omp_in) &
9!$omp & - ichar ('0'))) initializer (omp_priv = '0')
10!$omp declare reduction (baz : character(kind=1, len=2) &
11!$omp & : omp_out = char (ichar (omp_out(1:1)) + ichar (omp_in(1:1)) &
12!$omp & - ichar ('0')) // char (ichar (omp_out(2:2)) + &
13!$omp & ichar (omp_in(2:2)) - ichar ('0'))) initializer (omp_priv = '00')
14  character(kind=1, len=64) :: c, d
15  character(kind = 1, len=1) :: e
16  character(kind = 1, len=1+1) :: f
17  integer :: i
18  c = ''
19  d = ''
20  e = '0'
21  f = '00'
22!$omp parallel do reduction (foo : c) reduction (bar : d) &
23!$omp & reduction (baz : e, f)
24  do i = 1, 64
25    c = trim(c) // char (ichar ('0') + i)
26    d = char (ichar ('0') + i) // d
27    e = char (ichar (e) + mod (i, 3))
28    f = char (ichar (f(1:1)) + mod (i, 2)) &
29&	// char (ichar (f(2:2)) + mod (i, 3))
30  end do
31  do i = 1, 64
32    if (index (c, char (ichar ('0') + i)) .eq. 0) STOP 1
33    if (index (d, char (ichar ('0') + i)) .eq. 0) STOP 2
34  end do
35  if (e.ne.char (ichar ('0') + 64)) STOP 3
36  if (f(1:1).ne.char (ichar ('0') + 32)) STOP 4
37  if (f(2:2).ne.char (ichar ('0') + 64)) STOP 5
38end
39