1 !===-- module/iso_c_binding.f90 --------------------------------------------===!
3 ! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 ! See https://llvm.org/LICENSE.txt for license information.
5 ! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
7 !===------------------------------------------------------------------------===!
9 ! See Fortran 2018, clause 18.2
13 use __fortran_builtins
, only
: &
14 c_associated
=> __builtin_c_associated
, &
15 c_funloc
=> __builtin_c_funloc
, &
16 c_funptr
=> __builtin_c_funptr
, &
17 c_f_pointer
=> __builtin_c_f_pointer
, &
18 c_loc
=> __builtin_c_loc
, &
19 c_null_funptr
=> __builtin_c_null_funptr
, &
20 c_null_ptr
=> __builtin_c_null_ptr
, &
21 c_ptr
=> __builtin_c_ptr
, &
23 operator(==), operator(/=)
27 ! Set PRIVATE by default to explicitly only export what is meant
28 ! to be exported by this MODULE.
31 public
:: c_associated
, c_funloc
, c_funptr
, c_f_pointer
, c_loc
, &
32 c_null_funptr
, c_null_ptr
, c_ptr
, c_sizeof
, &
33 operator(==), operator(/=)
35 ! Table 18.2 (in clause 18.3.1)
36 ! TODO: Specialize (via macros?) for alternative targets
37 integer, parameter, public
:: &
42 c_int128_t
= 16 ! anticipating future addition
43 integer, parameter, public
:: &
45 c_short
= c_int16_t
, &
47 c_long_long
= c_int64_t
, &
48 c_signed_char
= c_int8_t
, &
49 c_size_t
= kind(c_sizeof(1)), &
51 c_intmax_t
= c_int64_t
, &
53 c_intmax_t
= c_int128_t
, &
55 c_intptr_t
= c_size_t
, &
56 c_ptrdiff_t
= c_size_t
57 integer, parameter, public
:: &
58 c_int_least8_t
= c_int8_t
, &
59 c_int_fast8_t
= c_int8_t
, &
60 c_int_least16_t
= c_int16_t
, &
61 #
if defined(__linux__
) && defined(__powerpc__
)
62 c_int_fast16_t
= c_long
, &
64 c_int_fast16_t
= c_int16_t
, &
66 c_int_least32_t
= c_int32_t
, &
67 #
if defined(__linux__
) && defined(__powerpc__
)
68 c_int_fast32_t
= c_long
, &
70 c_int_fast32_t
= c_int32_t
, &
72 c_int_least64_t
= c_int64_t
, &
73 c_int_fast64_t
= c_int64_t
, &
74 c_int_least128_t
= c_int128_t
, &
75 c_int_fast128_t
= c_int128_t
77 integer, parameter, public
:: &
86 integer, parameter, public
:: &
87 c_float_complex
= c_float
, &
88 c_double_complex
= c_double
, &
89 c_long_double_complex
= c_long_double
91 integer, parameter, public
:: c_bool
= 1
92 integer, parameter, public
:: c_char
= 1
94 ! C characters with special semantics
95 character(kind
=c_char
, len
=1), parameter, public
:: c_null_char
= achar(0)
96 character(kind
=c_char
, len
=1), parameter, public
:: c_alert
= achar(7)
97 character(kind
=c_char
, len
=1), parameter, public
:: c_backspace
= achar(8)
98 character(kind
=c_char
, len
=1), parameter, public
:: c_form_feed
= achar(12)
99 character(kind
=c_char
, len
=1), parameter, public
:: c_new_line
= achar(10)
100 character(kind
=c_char
, len
=1), parameter, public
:: c_carriage_return
= achar(13)
101 character(kind
=c_char
, len
=1), parameter, public
:: c_horizontal_tab
= achar(9)
102 character(kind
=c_char
, len
=1), parameter, public
:: c_vertical_tab
= achar(11)
104 interface c_f_procpointer
105 module procedure c_f_procpointer
107 public
:: c_f_procpointer
109 ! gfortran extensions
110 integer, parameter, public
:: &
112 c_float128_complex
= c_float128
116 subroutine c_f_procpointer(cptr
, fptr
)
117 type(c_funptr
), intent(in
) :: cptr
118 procedure(), pointer, intent(out
) :: fptr
120 end subroutine c_f_procpointer
122 end module iso_c_binding