2018-09-30 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / widechar_intrinsics_9.f90
blobc73dce4f81f31ad283243dc2346506942f279cdb
1 ! { dg-do run }
2 ! { dg-options "-fbackslash" }
4 implicit none
5 character(kind=1,len=3) :: s1, t1
6 character(kind=4,len=3) :: s4, t4
8 s1 = "foo" ; t1 = "bar"
9 call check_minmax_1 ("foo", "bar", min("foo","bar"), max("foo","bar"))
10 call check_minmax_1 ("bar", "foo", min("foo","bar"), max("foo","bar"))
11 call check_minmax_1 (s1, t1, min(s1,t1), max(s1,t1))
12 call check_minmax_1 (t1, s1, min(s1,t1), max(s1,t1))
14 s1 = " " ; t1 = "bar"
15 call check_minmax_1 (" ", "bar", min(" ","bar"), max(" ","bar"))
16 call check_minmax_1 ("bar", " ", min(" ","bar"), max(" ","bar"))
17 call check_minmax_1 (s1, t1, min(s1,t1), max(s1,t1))
18 call check_minmax_1 (t1, s1, min(s1,t1), max(s1,t1))
20 s1 = " " ; t1 = " "
21 call check_minmax_1 (" ", " ", min(" "," "), max(" "," "))
22 call check_minmax_1 (" ", " ", min(" "," "), max(" "," "))
23 call check_minmax_1 (s1, t1, min(s1,t1), max(s1,t1))
24 call check_minmax_1 (t1, s1, min(s1,t1), max(s1,t1))
26 s1 = "d\xFF " ; t1 = "d "
27 call check_minmax_1 ("d\xFF ", "d ", min("d\xFF ","d "), max("d\xFF ","d "))
28 call check_minmax_1 ("d ", "d\xFF ", min("d\xFF ","d "), max("d\xFF ","d "))
29 call check_minmax_1 (s1, t1, min(s1,t1), max(s1,t1))
30 call check_minmax_1 (t1, s1, min(s1,t1), max(s1,t1))
32 s4 = 4_" " ; t4 = 4_"xxx"
33 call check_minmax_2 (4_" ", 4_"xxx", min(4_" ", 4_"xxx"), &
34 max(4_" ", 4_"xxx"))
35 call check_minmax_2 (4_"xxx", 4_" ", min(4_" ", 4_"xxx"), &
36 max(4_" ", 4_"xxx"))
37 call check_minmax_2 (s4, t4, min(s4,t4), max(s4,t4))
38 call check_minmax_2 (t4, s4, min(s4,t4), max(s4,t4))
40 s4 = 4_" \u1be3m" ; t4 = 4_"xxx"
41 call check_minmax_2 (4_" \u1be3m", 4_"xxx", min(4_" \u1be3m", 4_"xxx"), &
42 max(4_" \u1be3m", 4_"xxx"))
43 call check_minmax_2 (4_"xxx", 4_" \u1be3m", min(4_" \u1be3m", 4_"xxx"), &
44 max(4_" \u1be3m", 4_"xxx"))
45 call check_minmax_2 (s4, t4, min(s4,t4), max(s4,t4))
46 call check_minmax_2 (t4, s4, min(s4,t4), max(s4,t4))
48 contains
50 subroutine check_minmax_1 (s1, s2, smin, smax)
51 implicit none
52 character(kind=1,len=*), intent(in) :: s1, s2, smin, smax
53 character(kind=4,len=len(s1)) :: w1, w2, wmin, wmax
55 w1 = s1 ; w2 = s2 ; wmin = smin ; wmax = smax
56 if (min (w1, w2) /= wmin) STOP 1
57 if (max (w1, w2) /= wmax) STOP 2
58 if (min (s1, s2) /= smin) STOP 3
59 if (max (s1, s2) /= smax) STOP 4
60 end subroutine check_minmax_1
62 subroutine check_minmax_2 (s1, s2, smin, smax)
63 implicit none
64 character(kind=4,len=*), intent(in) :: s1, s2, smin, smax
66 if (min (s1, s2) /= smin) STOP 5
67 if (max (s1, s2) /= smax) STOP 6
68 end subroutine check_minmax_2
70 end