blob: 71e81709374d5dbc0e41d29742acd2d775ec25a9 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
|
! { dg-do compile }
! Verify that initialization of c_ptr components works. This is based on
! code from fgsl:
! http://www.lrz-muenchen.de/services/software/mathematik/gsl/fortran/
! and tests PR 33395.
module fgsl
use, intrinsic :: iso_c_binding
implicit none
!
!
! Kind and length parameters are default integer
!
integer, parameter, public :: fgsl_double = c_double
!
! Types : Array support
!
type, public :: fgsl_vector
private
type(c_ptr) :: gsl_vector = c_null_ptr
end type fgsl_vector
contains
function fgsl_vector_align(p_x, f_x)
real(fgsl_double), pointer :: p_x(:)
type(fgsl_vector) :: f_x
integer :: fgsl_vector_align
fgsl_vector_align = 4
end function fgsl_vector_align
end module fgsl
module tmod
use fgsl
implicit none
contains
subroutine expb_df() bind(c)
type(fgsl_vector) :: f_x
real(fgsl_double), pointer :: p_x(:)
integer :: status
status = fgsl_vector_align(p_x, f_x)
end subroutine expb_df
end module tmod
! { dg-final { cleanup-modules "fgsl tmod" } }
|