OSDN Git Service

PR debug/43329
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / repeat_2.f90
1 ! REPEAT intrinsic
2 !
3 ! { dg-do run }
4 subroutine foo(i, j, s, t)
5   implicit none
6   integer, intent(in) :: i, j
7   character(len=i), intent(in) :: s
8   character(len=i*j), intent(in) :: t
9
10   if (repeat(s,j) /= t) call abort
11   call bar(j,s,t)
12 end subroutine foo
13
14 subroutine bar(j, s, t)
15   implicit none
16   integer, intent(in) :: j
17   character(len=*), intent(in) :: s
18   character(len=len(s)*j), intent(in) :: t
19
20   if (repeat(s,j) /= t) call abort
21 end subroutine bar
22
23 program test
24   implicit none
25   character(len=0), parameter :: s0 = "" 
26   character(len=1), parameter :: s1 = "a"
27   character(len=2), parameter :: s2 = "ab"
28   character(len=0) :: t0 
29   character(len=1) :: t1
30   character(len=2) :: t2
31   integer :: i
32
33   t0 = ""
34   t1 = "a"
35   t2 = "ab"
36
37   if (repeat(t0, 0) /= "") call abort
38   if (repeat(t1, 0) /= "") call abort
39   if (repeat(t2, 0) /= "") call abort
40   if (repeat(t0, 1) /= "") call abort
41   if (repeat(t1, 1) /= "a") call abort
42   if (repeat(t2, 1) /= "ab") call abort
43   if (repeat(t0, 2) /= "") call abort
44   if (repeat(t1, 2) /= "aa") call abort
45   if (repeat(t2, 2) /= "abab") call abort
46
47   if (repeat(s0, 0) /= "") call abort
48   if (repeat(s1, 0) /= "") call abort
49   if (repeat(s2, 0) /= "") call abort
50   if (repeat(s0, 1) /= "") call abort
51   if (repeat(s1, 1) /= "a") call abort
52   if (repeat(s2, 1) /= "ab") call abort
53   if (repeat(s0, 2) /= "") call abort
54   if (repeat(s1, 2) /= "aa") call abort
55   if (repeat(s2, 2) /= "abab") call abort
56
57   i = 0
58   if (repeat(t0, i) /= "") call abort
59   if (repeat(t1, i) /= "") call abort
60   if (repeat(t2, i) /= "") call abort
61   i = 1
62   if (repeat(t0, i) /= "") call abort
63   if (repeat(t1, i) /= "a") call abort
64   if (repeat(t2, i) /= "ab") call abort
65   i = 2
66   if (repeat(t0, i) /= "") call abort
67   if (repeat(t1, i) /= "aa") call abort
68   if (repeat(t2, i) /= "abab") call abort
69
70   i = 0
71   if (repeat(s0, i) /= "") call abort
72   if (repeat(s1, i) /= "") call abort
73   if (repeat(s2, i) /= "") call abort
74   i = 1
75   if (repeat(s0, i) /= "") call abort
76   if (repeat(s1, i) /= "a") call abort
77   if (repeat(s2, i) /= "ab") call abort
78   i = 2
79   if (repeat(s0, i) /= "") call abort
80   if (repeat(s1, i) /= "aa") call abort
81   if (repeat(s2, i) /= "abab") call abort
82
83   call foo(0,0,"","")
84   call foo(0,1,"","")
85   call foo(0,2,"","")
86   call foo(1,0,"a","")
87   call foo(1,1,"a","a")
88   call foo(1,2,"a","aa")
89   call foo(2,0,"ab","")
90   call foo(2,1,"ab","ab")
91   call foo(2,2,"ab","abab")
92 end program test