diff --git a/gcc/fortran/intrinsic.texi b/gcc/fortran/intrinsic.texi index 1aacd336bf8b412a051e56f376a5421246a596e6..1b9a89dcd9a3d9c00a8462a0b6417b8a494ef800 100644 --- a/gcc/fortran/intrinsic.texi +++ b/gcc/fortran/intrinsic.texi @@ -15193,8 +15193,8 @@ In addition to the integer named constants required by the Fortran 2003 standard and @code{C_PTRDIFF_T} of TS 29113, GNU Fortran provides as an extension named constants for the 128-bit integer types supported by the C compiler: @code{C_INT128_T, C_INT_LEAST128_T, C_INT_FAST128_T}. -Furthermore, if @code{__float128} is supported in C, the named constants -@code{C_FLOAT128, C_FLOAT128_COMPLEX} are defined. +Furthermore, if @code{_Float128} is supported in C, the named constants +@code{C_FLOAT128} and @code{C_FLOAT128_COMPLEX} are defined. @multitable @columnfractions .15 .35 .35 .35 @headitem Fortran Type @tab Named constant @tab C type @tab Extension @@ -15225,11 +15225,11 @@ Furthermore, if @code{__float128} is supported in C, the named constants @item @code{REAL} @tab @code{C_FLOAT} @tab @code{float} @item @code{REAL} @tab @code{C_DOUBLE} @tab @code{double} @item @code{REAL} @tab @code{C_LONG_DOUBLE} @tab @code{long double} -@item @code{REAL} @tab @code{C_FLOAT128} @tab @code{__float128} @tab Ext. +@item @code{REAL} @tab @code{C_FLOAT128} @tab @code{_Float128} @tab Ext. @item @code{COMPLEX}@tab @code{C_FLOAT_COMPLEX} @tab @code{float _Complex} @item @code{COMPLEX}@tab @code{C_DOUBLE_COMPLEX}@tab @code{double _Complex} @item @code{COMPLEX}@tab @code{C_LONG_DOUBLE_COMPLEX}@tab @code{long double _Complex} -@item @code{REAL} @tab @code{C_FLOAT128_COMPLEX} @tab @code{__float128 _Complex} @tab Ext. +@item @code{COMPLEX}@tab @code{C_FLOAT128_COMPLEX} @tab @code{_Float128 _Complex} @tab Ext. @item @code{LOGICAL}@tab @code{C_BOOL} @tab @code{_Bool} @item @code{CHARACTER}@tab @code{C_CHAR} @tab @code{char} @end multitable diff --git a/gcc/fortran/iso-c-binding.def b/gcc/fortran/iso-c-binding.def index e65c750faca7f29be728acf598ed2fb091aa0eb4..50256fe862098f81869e982c9fd02d193edeac15 100644 --- a/gcc/fortran/iso-c-binding.def +++ b/gcc/fortran/iso-c-binding.def @@ -116,7 +116,7 @@ NAMED_REALCST (ISOCBINDING_LONG_DOUBLE, "c_long_double", \ get_real_kind_from_node (long_double_type_node), GFC_STD_F2003) /* GNU Extension. Note that the equivalence here is specifically to - the IEEE 128-bit type __float128; if that does not map onto a type + the IEEE 128-bit type _Float128; if that does not map onto a type otherwise supported by the Fortran front end, get_real_kind_from_node will reject it as unsupported. */ NAMED_REALCST (ISOCBINDING_FLOAT128, "c_float128", \ diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c index 46670baae558d564c26b0c391a65d4fb05de9bb0..42a995be3483bd019f6cff7b2b047a62df3b7256 100644 --- a/gcc/fortran/trans-intrinsic.c +++ b/gcc/fortran/trans-intrinsic.c @@ -175,7 +175,7 @@ gfc_builtin_decl_for_float_kind (enum built_in_function double_built_in, if (gfc_real_kinds[i].c_float128) { - /* For __float128, the story is a bit different, because we return + /* For _Float128, the story is a bit different, because we return a decl to a library function rather than a built-in. */ gfc_intrinsic_map_t *m; for (m = gfc_intrinsic_map; m->double_built_in != double_built_in ; m++) @@ -387,7 +387,7 @@ build_round_expr (tree arg, tree restype) resprec = TYPE_PRECISION (restype); /* Depending on the type of the result, choose the int intrinsic (iround, - available only as a builtin, therefore cannot use it for __float128), long + available only as a builtin, therefore cannot use it for _Float128), long int intrinsic (lround family) or long long intrinsic (llround). If we don't have an appropriate function that converts directly to the integer type (such as kind == 16), just use ROUND, and then convert the result to @@ -689,7 +689,7 @@ gfc_build_intrinsic_lib_fndecls (void) if (gfc_real16_is_float128) { /* If we have soft-float types, we create the decls for their - C99-like library functions. For now, we only handle __float128 + C99-like library functions. For now, we only handle _Float128 q-suffixed functions. */ tree type, complex_type, func_1, func_2, func_cabs, func_frexp; diff --git a/gcc/fortran/trans-types.h b/gcc/fortran/trans-types.h index 3b45ce25666e82302e8f8d674b0c4198451edd25..6804bfe9edb11dcbc91acae6460dc570557bd83d 100644 --- a/gcc/fortran/trans-types.h +++ b/gcc/fortran/trans-types.h @@ -55,7 +55,7 @@ extern GTY(()) tree gfc_charlen_type_node; /* The following flags give us information on the correspondence of real (and complex) kinds with C floating-point types long double - and __float128. */ + and _Float128. */ extern bool gfc_real16_is_float128; enum gfc_packed { diff --git a/gcc/testsuite/gfortran.dg/PR100914.c b/gcc/testsuite/gfortran.dg/PR100914.c index c6bd9733e0b70ae945f7a59b953fbec38799f23e..ea339e724b754d64d0002da0b37a12ba5f9bbb2d 100644 --- a/gcc/testsuite/gfortran.dg/PR100914.c +++ b/gcc/testsuite/gfortran.dg/PR100914.c @@ -5,7 +5,6 @@ #include <stdbool.h> #include <stdio.h> #include <math.h> -#include <quadmath.h> #include <ISO_Fortran_binding.h> @@ -29,7 +28,7 @@ #define CMPLXL(x, y) ((long double complex)((long double)(x) + (long double complex)I * (long double)(y))) #undef CMPLX -#define CMPLX(x, y) ((__complex128 )((double)(x) + (double complex)I * (double)(y))) +#define CMPLX(x, y) ((_Float128 _Complex )((double)(x) + (double complex)I * (double)(y))) #define N 11 #define M 7 @@ -37,7 +36,7 @@ typedef float _Complex c_float_complex; typedef double _Complex c_double_complex; typedef long double _Complex c_long_double_complex; -typedef __complex128 c_float128_complex; +typedef _Float128 _Complex c_float128_complex; bool c_vrfy_c_float_complex (const CFI_cdesc_t *restrict); diff --git a/gcc/testsuite/gfortran.dg/PR100914.f90 b/gcc/testsuite/gfortran.dg/PR100914.f90 index 64b333506e3989bd63fafda482814e38cb57a513..d8057fd617cc7843a06b31a7a542a4f4b8d1ee05 100644 --- a/gcc/testsuite/gfortran.dg/PR100914.f90 +++ b/gcc/testsuite/gfortran.dg/PR100914.f90 @@ -2,6 +2,7 @@ ! { dg-do run { xfail { { x86_64*-*-* i?86*-*-* } && longdouble128 } } } ! { dg-additional-sources PR100914.c } ! { dg-require-effective-target fortran_real_c_float128 } +! { dg-additional-options "-Wno-pedantic" } ! ! Test the fix for PR100914 ! diff --git a/gcc/testsuite/gfortran.dg/c-interop/typecodes-array-float128-c.c b/gcc/testsuite/gfortran.dg/c-interop/typecodes-array-float128-c.c index d081febaaf44fe3fdfa35daf67f1d91ddc840001..4fcb6e2dbbd0ee4cd7d1405f39991638da725d0f 100644 --- a/gcc/testsuite/gfortran.dg/c-interop/typecodes-array-float128-c.c +++ b/gcc/testsuite/gfortran.dg/c-interop/typecodes-array-float128-c.c @@ -32,7 +32,7 @@ void ctest (CFI_cdesc_t *arg_float128, CFI_cdesc_t *arg_complex128) { - check (arg_float128, sizeof (__float128), CFI_type_float128); - check (arg_complex128, sizeof (__float128) * 2, + check (arg_float128, sizeof (_Float128), CFI_type_float128); + check (arg_complex128, sizeof (_Float128) * 2, CFI_type_float128_Complex); } diff --git a/gcc/testsuite/gfortran.dg/c-interop/typecodes-sanity-c.c b/gcc/testsuite/gfortran.dg/c-interop/typecodes-sanity-c.c index a1d044b8040f5fb1e0301e3cebbf828ad07ed8b4..90f0b20fa457efe3009ffd88afd4e3d201a817f0 100644 --- a/gcc/testsuite/gfortran.dg/c-interop/typecodes-sanity-c.c +++ b/gcc/testsuite/gfortran.dg/c-interop/typecodes-sanity-c.c @@ -23,8 +23,7 @@ static struct tc_info tc_table[] = { /* Extension types. Note there is no portable C equivalent type for CFI_type_ucs4_char type - (4-byte Unicode characters), and GCC rejects "__float128 _Complex", - so this is kind of hacky... */ + (4-byte Unicode characters), so this is kind of hacky... */ #if CFI_type_int128_t > 0 { CFI_type_int128_t, "CFI_type_int128_t", sizeof (__int128), 1 }, @@ -38,9 +37,9 @@ static struct tc_info tc_table[] = #endif #if CFI_type_float128 > 0 { CFI_type_float128, "CFI_type_float128", - sizeof (__float128), 1 }, + sizeof (_Float128), 1 }, { CFI_type_float128_Complex, "CFI_type_float128_Complex", - sizeof (__float128) * 2, 1 }, + sizeof (_Float128 _Complex), 1 }, #endif #if CFI_type_cfunptr > 0 { CFI_type_cfunptr, "CFI_type_cfunptr", diff --git a/gcc/testsuite/gfortran.dg/c-interop/typecodes-scalar-float128-c.c b/gcc/testsuite/gfortran.dg/c-interop/typecodes-scalar-float128-c.c index f1833aab9fb36b4df01baa4a737dac9ab0116b8b..7eafa93d82582cdbb07b194ccd67473e63c9065b 100644 --- a/gcc/testsuite/gfortran.dg/c-interop/typecodes-scalar-float128-c.c +++ b/gcc/testsuite/gfortran.dg/c-interop/typecodes-scalar-float128-c.c @@ -31,8 +31,8 @@ void ctest (CFI_cdesc_t *arg_float128, CFI_cdesc_t *arg_complex128) { - check (arg_float128, sizeof (__float128), CFI_type_float128); - check (arg_complex128, sizeof (__float128) * 2, + check (arg_float128, sizeof (_Float128), CFI_type_float128); + check (arg_complex128, sizeof (_Float128) * 2, CFI_type_float128_Complex); } diff --git a/gcc/testsuite/lib/target-supports.exp b/gcc/testsuite/lib/target-supports.exp index 8697ceb53c9c889b256ea053e2d6ed342c22bdea..f11c4e60a6e028618223ff55c7081995159eb4e1 100644 --- a/gcc/testsuite/lib/target-supports.exp +++ b/gcc/testsuite/lib/target-supports.exp @@ -1578,8 +1578,8 @@ proc check_effective_target_fortran_real_10 { } { # Return 1 if the target supports Fortran real kind C_FLOAT128, # 0 otherwise. This differs from check_effective_target_fortran_real_16 -# because __float128 has the additional requirement that it be the -# 128-bit IEEE encoding; even if __float128 is available in C, it may not +# because _Float128 has the additional requirement that it be the +# 128-bit IEEE encoding; even if _Float128 is available in C, it may not # have a corresponding Fortran kind on targets (PowerPC) that use some # other encoding for long double/TFmode/real(16). proc check_effective_target_fortran_real_c_float128 { } { diff --git a/libgfortran/ISO_Fortran_binding.h b/libgfortran/ISO_Fortran_binding.h index 50b02d27c9c21b77ba766ec04a2dcd5ffc39b919..d431d09e61ba9f297b812df7d359d6bca35668cd 100644 --- a/libgfortran/ISO_Fortran_binding.h +++ b/libgfortran/ISO_Fortran_binding.h @@ -281,7 +281,7 @@ extern int CFI_setpointer (CFI_cdesc_t *, CFI_cdesc_t *, const CFI_index_t []); #define CFI_type_long_double (CFI_type_Real + (10 << CFI_type_kind_shift)) #define CFI_type_long_double_Complex (CFI_type_Complex + (10 << CFI_type_kind_shift)) -/* This is the IEEE 128-bit encoding, same as float128. */ +/* This is the IEEE 128-bit encoding, same as _Float128. */ #elif (__CFI_LDBL_MANT_DIG__ == 113 \ && __CFI_LDBL_MIN_EXP__ == -16381 \ && __CFI_LDBL_MAX_EXP__ == 16384) @@ -303,7 +303,7 @@ extern int CFI_setpointer (CFI_cdesc_t *, CFI_cdesc_t *, const CFI_index_t []); #error "Can't determine kind of long double" #endif -/* Similarly for __float128. This always refers to the IEEE encoding +/* Similarly for _Float128. This always refers to the IEEE encoding and not some other 128-bit representation, so if we already used kind 16 for a non-IEEE representation, this one must be unsupported in Fortran even if it's available in C. */ diff --git a/libgfortran/runtime/ISO_Fortran_binding.c b/libgfortran/runtime/ISO_Fortran_binding.c index 0e1a419460a962abf2d99e2cf0f26cfaf87ba46b..e01cc650e90eea779a15dd81bc9ee2c34f8ee0d9 100644 --- a/libgfortran/runtime/ISO_Fortran_binding.c +++ b/libgfortran/runtime/ISO_Fortran_binding.c @@ -222,7 +222,7 @@ gfc_desc_to_cfi_desc (CFI_cdesc_t **d_ptr, const gfc_array_void *s) elem_len and not the kind, we get into trouble with long double kinds that do not correspond directly to the elem_len, specifically the kind 10 80-bit long double on x86 targets. On x86_64, this has size - 16 and cannot be differentiated from true __float128. Prefer the + 16 and cannot be differentiated from true _Float128. Prefer the standard long double type over the GNU extension in that case. */ if (d->type == CFI_type_Real && kind == sizeof (long double)) d->type = CFI_type_long_double;