view gcc/testsuite/gfortran.dg/bind_c_usage_18.f90 @ 144:8f4e72ab4e11

fix segmentation fault caused by nothing next cur_op to end
author Takahiro SHIMIZU <anatofuz@cr.ie.u-ryukyu.ac.jp>
date Sun, 23 Dec 2018 21:23:56 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! { dg-options "-Wc-binding-type" }
!
! PR fortran/38160
!

subroutine foo(x,y,z,a) bind(c) ! { dg-warning "but may not be C interoperable" }
  use iso_c_binding
  implicit none
  integer(4) :: x
  integer(c_float) :: y ! { dg-warning "C kind type parameter is for type REAL" }
  complex(c_float) :: z ! OK, c_float == c_float_complex
  real(c_float_complex) :: a ! OK, c_float == c_float_complex
end subroutine foo

use iso_c_binding
implicit none
integer, parameter :: it = c_int
integer, parameter :: dt = c_double
complex(c_int), target    :: z1  ! { dg-warning "C kind type parameter is for type INTEGER" }
complex(it), target       :: z2  ! { dg-warning "C kind type parameter is for type INTEGER" }
complex(c_double), target :: z3  ! OK
complex(dt), target       :: z4  ! OK
type(c_ptr) :: ptr

ptr = c_loc(z1)
ptr = c_loc(z2)
ptr = c_loc(z3)
ptr = c_loc(z4)
end