aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / character_mismatch.f90
blobe1619467ccce37f37fa44a532f2de9bcbf9cbe05
1 ! { dg-do compile }
3 ! Test case contributed by Mark Eggleston <mark.eggleston@codethink.com>
5 program test
6 use iso_fortran_env
7 implicit none
8 integer, parameter :: ucs4 = selected_char_kind('ISO_10646')
9 integer :: x
10 character(len=7) :: s = "abcd123"
11 character(4, ucs4) :: s4 = char(int(z'20ac'), ucs4) // ucs4_"100"
13 x = s
14 x = "string"
15 x = "A longer string" // " plus a bit"
16 x = s // s
17 x = s // "a bit more"
18 x = "prefix:" // s
19 x = s4
20 x = ucs4_"string"
21 x = ucs4_"A longer string" // ucs4_" plus a bit"
22 x = s4 // s4
23 x = s4 // ucs4_"a bit more"
24 x = ucs4_"prefix:" // s4
26 call f(s)
27 call f("string")
28 call f("A longer string" // " plus a bit")
29 call f(s // s)
30 call f(s // "a bit more")
31 call f("a string:" // s)
33 call f(s4)
34 call f(ucs4_"string")
35 call f(ucs4_"A longer string" // ucs4_" plus a bit")
36 call f(s4 // s4)
37 call f(s4 // ucs4_"a bit more")
38 call f(ucs4_"a string:" // s4)
40 write(*,*) "" // ucs4_""
42 contains
43 subroutine f(y)
44 integer, intent(in) :: y
46 write(*,*) y
47 end subroutine f
49 end program
51 ! { dg-error "CHARACTER\\(7\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 13 }
52 ! { dg-error "CHARACTER\\(6\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 14 }
53 ! { dg-error "CHARACTER\\(26\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 15 }
54 ! { dg-error "CHARACTER\\(14\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 16 }
55 ! { dg-error "CHARACTER\\(17\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 17 }
56 ! { dg-error "CHARACTER\\(14\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 18 }
57 ! { dg-error "CHARACTER\\(4,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 19 }
58 ! { dg-error "CHARACTER\\(6,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 20 }
59 ! { dg-error "CHARACTER\\(26,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 21 }
60 ! { dg-error "CHARACTER\\(8,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 22 }
61 ! { dg-error "CHARACTER\\(14,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 23 }
62 ! { dg-error "CHARACTER\\(11,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 24 }
63 ! { dg-error "CHARACTER\\(7\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 26 }
64 ! { dg-error "CHARACTER\\(6\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 27 }
65 ! { dg-error "CHARACTER\\(26\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 28 }
66 ! { dg-error "CHARACTER\\(14\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 29 }
67 ! { dg-error "CHARACTER\\(17\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 30 }
68 ! { dg-error "CHARACTER\\(16\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 31 }
69 ! { dg-error "CHARACTER\\(4,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 33 }
70 ! { dg-error "CHARACTER\\(6,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 34 }
71 ! { dg-error "CHARACTER\\(26,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 35 }
72 ! { dg-error "CHARACTER\\(8,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 36 }
73 ! { dg-error "CHARACTER\\(14,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 37 }
74 ! { dg-error "CHARACTER\\(13,4\\) to INTEGER\\(4\\)" "type mismatch" { target \*-\*-\* } 38 }
75 ! { dg-error "CHARACTER\\(0\\)/CHARACTER\\(0,4\\)" "operand type mismatch" { target \*-\*-\* } 40 }