1 ! Copyright 2020-2022 Free Software Foundation, Inc.
3 ! This program is free software; you can redistribute it and/or modify
4 ! it under the terms of the GNU General Public License as published by
5 ! the Free Software Foundation; either version 3 of the License, or
6 ! (at your option) any later version.
8 ! This program is distributed in the hope that it will be useful,
9 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
10 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11 ! GNU General Public License for more details.
13 ! You should have received a copy of the GNU General Public License
14 ! along with this program. If not, see <http://www.gnu.org/licenses/>.
17 use, intrinsic :: iso_c_binding
, only
: c_int
, c_float
, c_double
18 type, bind(C
) :: MyType
22 end module type_module
24 program mixed_stack_main
29 ! Call a Fortran function.
33 end program mixed_stack_main
37 write(*,*) "Hello World" ! Break here.
38 end subroutine breakpt
40 subroutine mixed_func_1a()
52 call mixed_func_1b (1, 2.0, 3D0
, d
, "abcdef", obj
)
53 end subroutine mixed_func_1a
55 ! This subroutine is called from the Fortran code.
56 subroutine mixed_func_1b(a
, b
, c
, d
, e
, g
)
65 character(len
=:), allocatable
:: f
69 subroutine mixed_func_1c (a
, b
, c
, d
, f
, g
) bind(C
)
70 use, intrinsic :: iso_c_binding
, only
: c_int
, c_float
, c_double
71 use, intrinsic :: iso_c_binding
, only
: c_float_complex
, c_char
74 integer(c_int
), value
, intent(in
) :: a
75 real(c_float
), value
, intent(in
) :: b
76 real(c_double
), value
, intent(in
) :: c
77 complex(c_float_complex
), value
, intent(in
) :: d
78 character(c_char
), intent(in
) :: f(*)
80 end subroutine mixed_func_1c
83 ! Create a copy of the string with a NULL terminator on the end.
87 call mixed_func_1c (a
, b
, c
, d
, f
, g
)
88 end subroutine mixed_func_1b
90 ! This subroutine is called from the C code.
91 subroutine mixed_func_1d(a
, b
, c
, d
, str
)
92 use, intrinsic :: iso_c_binding
, only
: c_int
, c_float
, c_double
93 use, intrinsic :: iso_c_binding
, only
: c_float_complex
98 complex(c_float_complex
) :: d
99 character(len
=*) :: str
102 subroutine mixed_func_1e () bind(C
)
104 end subroutine mixed_func_1e
107 write(*,*) a
, b
, c
, d
, str
109 ! Call a C++ function (via an extern "C" wrapper).
111 end subroutine mixed_func_1d
113 ! This is called from C++ code.
114 subroutine mixed_func_1h ()
116 end subroutine mixed_func_1h