OSDN Git Service

2011-01-29 Jerry DeLisle <jvdelisle@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / bind_c_usage_16.f03
1 ! { dg-do run }
2 ! { dg-additional-sources bind_c_usage_16_c.c }
3 !
4 ! PR fortran/34079
5 !
6 ! Ensure character-returning, bind(C) function work.
7 !
8 module mod
9   use iso_c_binding
10   implicit none
11 contains
12   function bar(x)  bind(c, name="returnA")
13     character(len=1,kind=c_char) :: bar, x
14     bar = x
15     bar = 'A'
16   end function bar
17   function foo()  bind(c, name="returnB")
18     character(len=1,kind=c_char) :: foo
19     foo = 'B'
20   end function foo
21 end module mod
22
23 subroutine test() bind(c)
24   use mod
25   implicit none
26   character(len=1,kind=c_char) :: a
27   character(len=3,kind=c_char) :: b
28   character(len=1,kind=c_char) :: c(3)
29   character(len=3,kind=c_char) :: d(3)
30   integer :: i
31
32   a = 'z'
33   b = 'fffff'
34   c = 'h'
35   d = 'uuuuu'
36
37   a = bar('x')
38   if (a /= 'A') call abort()
39   b = bar('y')
40   if (b /= 'A' .or. iachar(b(2:2))/=32 .or. iachar(b(3:3))/=32) call abort()
41   c = bar('x')
42   if (any(c /= 'A')) call abort()
43   d = bar('y')
44   if (any(d /= 'A')) call abort()
45
46   a = foo()
47   if (a /= 'B') call abort()
48   b = foo()
49   if (b /= 'B') call abort()
50   c = foo()
51   if (any(c /= 'B')) call abort()
52   d = foo()
53   if (any(d /= 'B')) call abort()
54   do i = 1,3
55     if(iachar(d(i)(2:2)) /=32 .or. iachar(d(i)(3:3)) /= 32) call abort()
56   end do
57 end subroutine