* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / widechar_4.f90
blob1166f8bfb77934923380ee2846b7465090bf784e
1 ! { dg-do run }
2 ! { dg-options "-fbackslash" }
4 character(kind=1,len=20) :: s1, t1
5 character(kind=4,len=20) :: s4, t4
7 call test (4_"ccc ", 4_"bbb", 4_"ccc", 4_"ddd")
8 call test (4_" \xACp ", 4_" \x900000 ", 4_" \xACp ", 4_"ddd")
9 call test (4_" \xACp ", 4_" \x900000 ", 4_" \xACp ", 4_"ddd")
11 call test2 (4_" \x900000 ", 4_" \xACp ", 4_"ddd")
13 contains
15 subroutine test(s4, t4, u4, v4)
16 character(kind=4,len=*) :: s4, t4, u4, v4
18 if (.not. (s4 >= t4)) call abort
19 if (.not. (s4 > t4)) call abort
20 if (.not. (s4 .ge. t4)) call abort
21 if (.not. (s4 .gt. t4)) call abort
22 if ( (s4 == t4)) call abort
23 if (.not. (s4 /= t4)) call abort
24 if ( (s4 .eq. t4)) call abort
25 if (.not. (s4 .ne. t4)) call abort
26 if ( (s4 <= t4)) call abort
27 if ( (s4 < t4)) call abort
28 if ( (s4 .le. t4)) call abort
29 if ( (s4 .lt. t4)) call abort
31 if (.not. (s4 >= u4)) call abort
32 if ( (s4 > u4)) call abort
33 if (.not. (s4 .ge. u4)) call abort
34 if ( (s4 .gt. u4)) call abort
35 if (.not. (s4 == u4)) call abort
36 if ( (s4 /= u4)) call abort
37 if (.not. (s4 .eq. u4)) call abort
38 if ( (s4 .ne. u4)) call abort
39 if (.not. (s4 <= u4)) call abort
40 if ( (s4 < u4)) call abort
41 if (.not. (s4 .le. u4)) call abort
42 if ( (s4 .lt. u4)) call abort
44 if ( (s4 >= v4)) call abort
45 if ( (s4 > v4)) call abort
46 if ( (s4 .ge. v4)) call abort
47 if ( (s4 .gt. v4)) call abort
48 if ( (s4 == v4)) call abort
49 if (.not. (s4 /= v4)) call abort
50 if ( (s4 .eq. v4)) call abort
51 if (.not. (s4 .ne. v4)) call abort
52 if (.not. (s4 <= v4)) call abort
53 if (.not. (s4 < v4)) call abort
54 if (.not. (s4 .le. v4)) call abort
55 if (.not. (s4 .lt. v4)) call abort
57 end subroutine test
59 subroutine test2(t4, u4, v4)
60 character(kind=4,len=*) :: t4, u4, v4
62 if (.not. (4_" \xACp " >= t4)) call abort
63 if (.not. (4_" \xACp " > t4)) call abort
64 if (.not. (4_" \xACp " .ge. t4)) call abort
65 if (.not. (4_" \xACp " .gt. t4)) call abort
66 if ( (4_" \xACp " == t4)) call abort
67 if (.not. (4_" \xACp " /= t4)) call abort
68 if ( (4_" \xACp " .eq. t4)) call abort
69 if (.not. (4_" \xACp " .ne. t4)) call abort
70 if ( (4_" \xACp " <= t4)) call abort
71 if ( (4_" \xACp " < t4)) call abort
72 if ( (4_" \xACp " .le. t4)) call abort
73 if ( (4_" \xACp " .lt. t4)) call abort
75 if (.not. (4_" \xACp " >= u4)) call abort
76 if ( (4_" \xACp " > u4)) call abort
77 if (.not. (4_" \xACp " .ge. u4)) call abort
78 if ( (4_" \xACp " .gt. u4)) call abort
79 if (.not. (4_" \xACp " == u4)) call abort
80 if ( (4_" \xACp " /= u4)) call abort
81 if (.not. (4_" \xACp " .eq. u4)) call abort
82 if ( (4_" \xACp " .ne. u4)) call abort
83 if (.not. (4_" \xACp " <= u4)) call abort
84 if ( (4_" \xACp " < u4)) call abort
85 if (.not. (4_" \xACp " .le. u4)) call abort
86 if ( (4_" \xACp " .lt. u4)) call abort
88 if ( (4_" \xACp " >= v4)) call abort
89 if ( (4_" \xACp " > v4)) call abort
90 if ( (4_" \xACp " .ge. v4)) call abort
91 if ( (4_" \xACp " .gt. v4)) call abort
92 if ( (4_" \xACp " == v4)) call abort
93 if (.not. (4_" \xACp " /= v4)) call abort
94 if ( (4_" \xACp " .eq. v4)) call abort
95 if (.not. (4_" \xACp " .ne. v4)) call abort
96 if (.not. (4_" \xACp " <= v4)) call abort
97 if (.not. (4_" \xACp " < v4)) call abort
98 if (.not. (4_" \xACp " .le. v4)) call abort
99 if (.not. (4_" \xACp " .lt. v4)) call abort
101 end subroutine test2
103 subroutine test3(t4, u4, v4)
104 character(kind=4,len=*) :: t4, u4, v4
106 if (.not. (4_" \xACp " >= 4_" \x900000 ")) call abort
107 if (.not. (4_" \xACp " > 4_" \x900000 ")) call abort
108 if (.not. (4_" \xACp " .ge. 4_" \x900000 ")) call abort
109 if (.not. (4_" \xACp " .gt. 4_" \x900000 ")) call abort
110 if ( (4_" \xACp " == 4_" \x900000 ")) call abort
111 if (.not. (4_" \xACp " /= 4_" \x900000 ")) call abort
112 if ( (4_" \xACp " .eq. 4_" \x900000 ")) call abort
113 if (.not. (4_" \xACp " .ne. 4_" \x900000 ")) call abort
114 if ( (4_" \xACp " <= 4_" \x900000 ")) call abort
115 if ( (4_" \xACp " < 4_" \x900000 ")) call abort
116 if ( (4_" \xACp " .le. 4_" \x900000 ")) call abort
117 if ( (4_" \xACp " .lt. 4_" \x900000 ")) call abort
119 if (.not. (4_" \xACp " >= 4_" \xACp ")) call abort
120 if ( (4_" \xACp " > 4_" \xACp ")) call abort
121 if (.not. (4_" \xACp " .ge. 4_" \xACp ")) call abort
122 if ( (4_" \xACp " .gt. 4_" \xACp ")) call abort
123 if (.not. (4_" \xACp " == 4_" \xACp ")) call abort
124 if ( (4_" \xACp " /= 4_" \xACp ")) call abort
125 if (.not. (4_" \xACp " .eq. 4_" \xACp ")) call abort
126 if ( (4_" \xACp " .ne. 4_" \xACp ")) call abort
127 if (.not. (4_" \xACp " <= 4_" \xACp ")) call abort
128 if ( (4_" \xACp " < 4_" \xACp ")) call abort
129 if (.not. (4_" \xACp " .le. 4_" \xACp ")) call abort
130 if ( (4_" \xACp " .lt. 4_" \xACp ")) call abort
132 if ( (4_" \xACp " >= 4_"ddd")) call abort
133 if ( (4_" \xACp " > 4_"ddd")) call abort
134 if ( (4_" \xACp " .ge. 4_"ddd")) call abort
135 if ( (4_" \xACp " .gt. 4_"ddd")) call abort
136 if ( (4_" \xACp " == 4_"ddd")) call abort
137 if (.not. (4_" \xACp " /= 4_"ddd")) call abort
138 if ( (4_" \xACp " .eq. 4_"ddd")) call abort
139 if (.not. (4_" \xACp " .ne. 4_"ddd")) call abort
140 if (.not. (4_" \xACp " <= 4_"ddd")) call abort
141 if (.not. (4_" \xACp " < 4_"ddd")) call abort
142 if (.not. (4_" \xACp " .le. 4_"ddd")) call abort
143 if (.not. (4_" \xACp " .lt. 4_"ddd")) call abort
145 end subroutine test3