nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / c_char_tests_5.f90
blobc7a1c6e8c2bc4935104aa1288bbf671fb2dfb128
1 ! { dg-do run }
2 ! { dg-options "-fbackslash" }
4 ! PR fortran/103828
5 ! Check that we can C char with non-ASCII values, which are interoperable
6 ! with both INTEGER(C_SIGNED_CHAR) and CHARACTER(C_CHAR).
8 program test
9 use, intrinsic :: iso_c_binding, only : c_signed_char, c_char
10 implicit none
12 interface
13 ! In order to perform this test, we cheat and pretend to give each function
14 ! the other one's prototype. It should still work, because all arguments
15 ! are interoperable with C char.
17 subroutine test1 (a) bind(c, name='test_int')
18 import c_char
19 character(kind=c_char, len=1), value :: a
20 end subroutine test1
22 subroutine test2 (a) bind(c, name='test_char')
23 import c_signed_char
24 integer(kind=c_signed_char), value :: a
25 end subroutine test2
27 end interface
29 call test1('\xA3')
30 call test2(-93_c_signed_char)
32 end program test
34 subroutine test_int (a) bind(c)
35 use, intrinsic :: iso_c_binding, only : c_signed_char
36 implicit none
37 integer(c_signed_char), value :: a
39 if (a /= iachar('\xA3', kind=c_signed_char)) stop 1
40 end subroutine
42 subroutine test_char (a) bind(c)
43 use, intrinsic :: iso_c_binding, only : c_char
44 implicit none
45 character(kind=c_char, len=1), value :: a
47 if (a /= '\xA3') stop 101
48 end subroutine