modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / bind_c_coms.f90
blob2f9714947c7f43cb1b11051d43e35808dc9b8932
1 ! { dg-do run }
2 ! { dg-additional-sources bind_c_coms_driver.c }
3 ! { dg-options "-w" }
4 ! the -w option is to prevent the warning about long long ints
5 module bind_c_coms
6 ! { dg-additional-options "-fcommon" { target hppa*-*-hpux* } }
7 use, intrinsic :: iso_c_binding
8 implicit none
10 common /COM/ R, S
11 real(c_double) :: r
12 real(c_double) :: t
13 real(c_double) :: s
14 bind(c) :: /COM/, /SINGLE/, /MYCOM/
15 common /SINGLE/ T
16 common /MYCOM/ LONG_INTS
17 integer(c_long) :: LONG_INTS
18 common /MYCOM2/ LONG_LONG_INTS
19 integer(c_long_long) :: long_long_ints
20 bind(c) :: /mycom2/
22 common /com2/ i, j
23 integer(c_int) :: i, j
24 bind(c, name="f03_com2") /com2/
26 common /com3/ m, n
27 integer(c_int) :: m, n
28 bind(c, name="") /com3/
30 contains
31 subroutine test_coms() bind(c)
32 r = r + .1d0;
33 s = s + .1d0;
34 t = t + .1d0;
35 long_ints = long_ints + 1
36 long_long_ints = long_long_ints + 1
37 i = i + 1
38 j = j + 1
40 m = 1
41 n = 1
42 end subroutine test_coms
43 end module bind_c_coms
45 module bind_c_coms_2
46 use, intrinsic :: iso_c_binding, only: c_int
47 common /com3/ m, n
48 integer(c_int) :: m, n
49 bind(c, name="") /com3/
50 end module bind_c_coms_2