Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Iain Sandoe



> On 8 Oct 2021, at 23:55, Thomas Koenig via Gcc  wrote:
> 
> 
> Hi Iain,
> 
>>> Things get interesting for user code, calling a routine compiled
>>> for double double with newer IEEE QP will result in breakage.
>> That would not happen with the proposal above, since the library would
>> have different entry points for the two formats.
> 
> I meant the case where the user writes, with an old, KIND=16 is double
> double compiler,
> 
>  subroutine foo(a)
>real(kind=16) :: a
>a = a + 1._16
>  end subroutine foo
> 
> and puts it in a library or an old object file, and in new code with an
> IEEE QP compiler calls that with
> 
>  real(kind=16) :: a
>  a = 2._16
>  call foo(a)
>  print *,a
> 
> this will result in silent generation of garbage values, since Fortran
> does not mangle the function name based on it types. For both cases, the
> subroutine will be called foo_  (or MOD..._foo).

hmm, well I thought about that case, but  … isn’t this “pilot error”?

if one compiles different parts of a project with incompatible command line 
options…

… or, say, compile with -mavx512 and then try to run code on hardware without
such a vector unit?

Getting wrong answers silently can likely be done with other command line
option mismatches.

Iain

> There is no choice - we need to make object code compiled by the user
> incompatible between the old and the new format on the systems where
> we make the switch.
> 
> This is starting to look like a can of worms from Pandora's box,
> if you pardon my mixed metaphors.

> 
> Best regards
> 
>   Thomas



Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Iain Sandoe
Hi Thomas,

recognising that this is complex - the intent here is to see if there are ways
to partition the problem (where the pain falls does depend on the choices
made).

perhaps:

 *A  library (interface, name)
 *B  compiler internals
 *C  user-facing changes

> On 8 Oct 2021, at 17:26, Thomas Koenig  wrote:
> 

>> If one wanted to prioritize library SO name stability - then, perhaps, the
>> approach Jonathan mentioned has been used for libstdc++ (add new
>> symbols for ieee128 with a different mangling to the existing r/c_16 ..)
>> would be preferable (the FE then has to choose the relevant symbol/
>> mangling depending on target).

(A) the points here ^^ are:

1/ the SO name could be left as it is
2/ a target that defaulted to QP routines would still (perhaps under
   some command line flag be able to use the older implementation).

I think both of those could be very helpful to end-users…

> That's not all that would have to be changed.


>  Consider
> 
>  write (*,*) 1.0_16
> end program
> 
> which is translated (using -fdump-tree-original) to
> 
> 
>_gfortran_st_write (_parm.0);
>{
>  static real(kind=16) C.3873 = 1.0e+0;
> 
>  _gfortran_transfer_real128_write (_parm.0, , 16);
>}
>_gfortran_st_write_done (_parm.0);
> 
> so we actually pass a separate kind number as well (why, I'm not sure).
> We would have to go through libgfortran with a fine comb to find all
> the occurrences.  Probably some m4 hackery in iparm.m4 and ifunction.m4.
> So, doable from the library side, if some work.

(B) This is the second area of interest, the fact that changes in the compiler 
internals
would be needed - and those take the time of the volunteers to implement 
(believe
me, I am painfully aware of how that pressure falls).

> Things get interesting for user code, calling a routine compiled
> for double double with newer IEEE QP will result in breakage.

That would not happen with the proposal above, since the library would
have different entry points for the two formats.

> We cannot use the KIND number to differentiate, because we must
> assume that people have used KIND=16 and selected_real_kind(30)
> interchangably, and we certainly do not want to nail people to
> the old double double precision on hardware for which IEEE QP
> is available.  

you don’t *have* to use the KIND number to differentiate to the library or the 
compiler
(although some alternate, more flexible, token would have to be invented).

(C) It’s the mapping between that internal token and the user’s view of the 
world that
needs to be defined in terms of what the combination of platform and command 
line
flags implies to the treatment of KIND=NN and selected_real_kind().

> So, KIND=15 for IEEE QP is out.

(C) I must confess this kind of change is where things seem very tricky to me.

changing how the language represents things seems to be something
that would benefit from agreement between compiler vendors

> It's not an easy problem, unfortunately.

no. it is not.
Iain




Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Thomas Koenig via Fortran



Hi Iain,


Things get interesting for user code, calling a routine compiled
for double double with newer IEEE QP will result in breakage.

That would not happen with the proposal above, since the library would
have different entry points for the two formats.


I meant the case where the user writes, with an old, KIND=16 is double
double compiler,

  subroutine foo(a)
real(kind=16) :: a
a = a + 1._16
  end subroutine foo

and puts it in a library or an old object file, and in new code with an
IEEE QP compiler calls that with

  real(kind=16) :: a
  a = 2._16
  call foo(a)
  print *,a

this will result in silent generation of garbage values, since Fortran
does not mangle the function name based on it types. For both cases, the
subroutine will be called foo_  (or MOD..._foo).

There is no choice - we need to make object code compiled by the user
incompatible between the old and the new format on the systems where
we make the switch.

This is starting to look like a can of worms from Pandora's box,
if you pardon my mixed metaphors.

Best regards

Thomas


Re: [PATCH] PR fortran/65454 - accept both old and new-style relational operators

2021-10-08 Thread Jerry D via Fortran




On 10/8/21 2:33 PM, Harald Anlauf via Fortran wrote:

Dear Fortranners,

F2018:10.1.5.5.1(2) requires the same interpretation of old and new-style
relational operators.  We internally distinguish between old and new style,
but try to map appropriately when used.

This mapping was missing when reading a module via
   USE module, ONLY: OPERATOR(op)
where op used a style different from the INTERFACE OPERATOR statement in
the declaring module.  The attached patch remedies this.

Note: we do neither change the module format nor actually remap an operator.
We simply improve the check whether the requested operator symbol exists in
the old-style or new-style version.

Regtested on x86_64-pc-linux-gnu.  OK for mainline?

Thanks,
Harald


Looks all good Harald, OK and thanks for the support!

Jerry


[PATCH] PR fortran/65454 - accept both old and new-style relational operators

2021-10-08 Thread Harald Anlauf via Fortran
Dear Fortranners,

F2018:10.1.5.5.1(2) requires the same interpretation of old and new-style
relational operators.  We internally distinguish between old and new style,
but try to map appropriately when used.

This mapping was missing when reading a module via
  USE module, ONLY: OPERATOR(op)
where op used a style different from the INTERFACE OPERATOR statement in
the declaring module.  The attached patch remedies this.

Note: we do neither change the module format nor actually remap an operator.
We simply improve the check whether the requested operator symbol exists in
the old-style or new-style version.

Regtested on x86_64-pc-linux-gnu.  OK for mainline?

Thanks,
Harald

Fortran: accept both old and new-style relational operators in USE, ONLY

F2018:10.1.5.5.1(2) requires the same interpretation of old and new-style
relational operators.  As gfortran internally distinguishes between
these versions, we must match equivalent notations in
	USE module, ONLY: OPERATOR(op)
statements when reading modules.

gcc/fortran/ChangeLog:

	PR fortran/65454
	* module.c (read_module): Handle old and new-style relational
	operators when used in USE module, ONLY: OPERATOR(op).

gcc/testsuite/ChangeLog:

	PR fortran/65454
	* gfortran.dg/interface_operator_3.f90: New test.

diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
index 1804066bc8c..7b98ba539d6 100644
--- a/gcc/fortran/module.c
+++ b/gcc/fortran/module.c
@@ -5592,6 +5592,9 @@ read_module (void)

   for (i = GFC_INTRINSIC_BEGIN; i != GFC_INTRINSIC_END; i++)
 {
+  gfc_use_rename *u = NULL, *v = NULL;
+  int j = i;
+
   if (i == INTRINSIC_USER)
 	continue;

@@ -5599,18 +5602,73 @@ read_module (void)
 	{
 	  u = find_use_operator ((gfc_intrinsic_op) i);

-	  if (u == NULL)
+	  /* F2018:10.1.5.5.1 requires same interpretation of old and new-style
+	 relational operators.  Special handling for USE, ONLY.  */
+	  switch (i)
+	{
+	case INTRINSIC_EQ:
+	  j = INTRINSIC_EQ_OS;
+	  break;
+	case INTRINSIC_EQ_OS:
+	  j = INTRINSIC_EQ;
+	  break;
+	case INTRINSIC_NE:
+	  j = INTRINSIC_NE_OS;
+	  break;
+	case INTRINSIC_NE_OS:
+	  j = INTRINSIC_NE;
+	  break;
+	case INTRINSIC_GT:
+	  j = INTRINSIC_GT_OS;
+	  break;
+	case INTRINSIC_GT_OS:
+	  j = INTRINSIC_GT;
+	  break;
+	case INTRINSIC_GE:
+	  j = INTRINSIC_GE_OS;
+	  break;
+	case INTRINSIC_GE_OS:
+	  j = INTRINSIC_GE;
+	  break;
+	case INTRINSIC_LT:
+	  j = INTRINSIC_LT_OS;
+	  break;
+	case INTRINSIC_LT_OS:
+	  j = INTRINSIC_LT;
+	  break;
+	case INTRINSIC_LE:
+	  j = INTRINSIC_LE_OS;
+	  break;
+	case INTRINSIC_LE_OS:
+	  j = INTRINSIC_LE;
+	  break;
+	default:
+	  break;
+	}
+
+	  if (j != i)
+	v = find_use_operator ((gfc_intrinsic_op) j);
+
+	  if (u == NULL && v == NULL)
 	{
 	  skip_list ();
 	  continue;
 	}

-	  u->found = 1;
+	  if (u)
+	u->found = 1;
+	  if (v)
+	v->found = 1;
 	}

   mio_interface (_current_ns->op[i]);
-  if (u && !gfc_current_ns->op[i])
-	u->found = 0;
+  if (!gfc_current_ns->op[i] && !gfc_current_ns->op[j])
+	{
+	  if (u)
+	u->found = 0;
+	  if (v)
+	v->found = 0;
+	}
 }

   mio_rparen ();
diff --git a/gcc/testsuite/gfortran.dg/interface_operator_3.f90 b/gcc/testsuite/gfortran.dg/interface_operator_3.f90
new file mode 100644
index 000..6a580b2f1cf
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/interface_operator_3.f90
@@ -0,0 +1,141 @@
+! { dg-do compile }
+! PR fortran/65454 - accept both old and new-style relational operators
+
+module m
+  implicit none
+  private :: t1
+  type t1
+ integer :: i
+  end type t1
+  interface operator (==)
+ module procedure :: my_cmp
+  end interface
+  interface operator (/=)
+ module procedure :: my_cmp
+  end interface
+  interface operator (<=)
+ module procedure :: my_cmp
+  end interface
+  interface operator (<)
+ module procedure :: my_cmp
+  end interface
+  interface operator (>=)
+ module procedure :: my_cmp
+  end interface
+  interface operator (>)
+ module procedure :: my_cmp
+  end interface
+contains
+  elemental function my_cmp (a, b) result (c)
+type(t1), intent(in) :: a, b
+logical  :: c
+c = a%i == b%i
+  end function my_cmp
+end module m
+
+module m_os
+  implicit none
+  private :: t2
+  type t2
+ integer :: i
+  end type t2
+  interface operator (.eq.)
+ module procedure :: my_cmp
+  end interface
+  interface operator (.ne.)
+ module procedure :: my_cmp
+  end interface
+  interface operator (.le.)
+ module procedure :: my_cmp
+  end interface
+  interface operator (.lt.)
+ module procedure :: my_cmp
+  end interface
+  interface operator (.ge.)
+ module procedure :: my_cmp
+  end interface
+  interface operator (.gt.)
+ module procedure :: my_cmp
+  end interface
+contains
+  elemental function my_cmp (a, b) result 

Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Segher Boessenkool
On Wed, Oct 06, 2021 at 11:42:11PM -0400, Michael Meissner wrote:
> On Wed, Oct 06, 2021 at 10:17:44AM -0500, Segher Boessenkool wrote:
> > On Wed, Oct 06, 2021 at 08:59:53AM +0200, Thomas Koenig wrote:
> > > On 05.10.21 23:54, Segher Boessenkool wrote:
> > > >>There is also the issue of binary data.  If some user has written
> > > >>out data in double double and wants to read it in as IEEE quad,
> > > >>the results are going to be garbage.  Another option for CONVERT
> > > >>might be the solution to that, or, as you wrote, having a
> > > >>REAL(KIND=15).  It should be inaccessible via SELECTED_REAL_KIND,
> > > >>though.
> > > >
> > > >That means flipping the default on all PowerPC to no longer be double-
> > > >double.  This means that you should have IEEE QP work everywhere, or the
> > > >people who do need more than double precision will have no recourse.
> > > 
> > > I think we can exclude big-endian POWER from this - they do not have
> > > IEEE QP support, correct?  So, exclude that from the SONAME change.
> > 
> > Not correct, no.  IEEE QP works fine in either endianness.
> > 
> > I don't know what the libraries do, but in GCC it works just fine.
> 
> It only has the support if you add the options to enable IEEE 128-bit support
> when compiling programs.  It is off by default.

You need -mvsx and -mfloat128, both on by default on power7 and later.

Without hardware QP support it will call __mulkf3 and friends.  But the
parameter passing is identical: in the high VSRs (i.e. the VRs).

There are no differences between BE and LE here.

> > Converting double-double to IEEE QP should not be hard or slow?
> 
> There are a lot of corner cases to get it right.  IIRC, there are a few values
> that double double can represent that are not expressable with exact precision
> in IEEE 128-bit.

Yes, but those are trivial to get right.  The value of a double-double
is the sum of both doubles.  The sign is the sign of the first component
though (which matters if adding -0. and +0.), that is all, all other
cases magically work out as wanted afaics.


Segher


Re: [PATCH v2, Fortran] Add diagnostic for F2018:C839 (TS29113:C535c)

2021-10-08 Thread Tobias Burnus

Hi Sandra

On 08.10.21 18:58, Sandra Loosemore wrote:

I concur that that should be in a separate PR.

It's PR102641 now.

Thanks.

OK to commit v2 of the patch (attached)?


OK – thanks for the patch!

Tobias

-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955


Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Segher Boessenkool
On Wed, Oct 06, 2021 at 10:03:59PM +, Joseph Myers wrote:
> On Wed, 6 Oct 2021, Segher Boessenkool wrote:
> > With "not in any" I mean: not for other architectures either!  All archs
> > that do not say anything about floating point in their machine
> > description get a working sofware floating point (for binary32 and
> > binary64 currently).
> 
> Any architecture that supports a software floating-point ABI (i.e. one 
> that does argument passing and return for floating-point in integer 
> registers) should specify it in its ABI documents.  For example, 
> https://github.com/riscv-non-isa/riscv-elf-psabi-doc/blob/master/riscv-cc.adoc
>  
> describes both "Integer Calling Convention" and "Hardware Floating-point 
> Calling Convention", with a series of named ABIs based on those such as 
> LP64, LP64F, etc. (like on (32-bit) Arm, but unlike Power or MIPS, RISC-V 
> GCC also supports building programs that use hardware floating-point 
> instructions but the software floating-point ABI).

But many CPUs do not have hardware floating point in any variant, and
their ABIs / calling conventions do not mention floating point at all.
Still, this works with GCC just fine: it passes floats and doubles the
same as 32-bit resp. 64-bit integers.

binary16 and bfloat16 would be easy to support the same way, but it is a
bit harder for binary128, because we do not have a 128-bit integer type
on all systems.  That should be fixed first probably.  It doesn't have
to be very good machine code, but having it supported everywhere would
simplify things a lot.

> That's how the (unified) 32-bit powerpc ABI documents things: both 
> hardware and software floating-point ABI variants.

Yes.  I am not saying this isn't good or desirable, but simply how
things are now.

> If the architecture doesn't support hardware floating point, or doesn't 
> have separate registers for it, the software floating-point ABI is just 
> "the ABI" and there's no separate hardware floating-point ABI, of course.

Right, and many architectures neglect to even mention anything to do
with floating point, although this is and always was a standard C
feature :-/


Segher


[PATCH v2, Fortran] Add diagnostic for F2018:C839 (TS29113:C535c)

2021-10-08 Thread Sandra Loosemore

On 10/7/21 9:25 AM, Tobias Burnus wrote:

Hi Sandra,

On 06.10.21 23:37, Sandra Loosemore wrote:
This patch is for PR fortran/54753, to add a diagnostic for violations 
of this constraint in the 2018 standard:


  C839 If an assumed-size or nonallocatable nonpointer assumed-rank
  array is an actual argument that corresponds to a dummy argument that
  is an INTENT (OUT) assumed-rank array, it shall not be polymorphic,
  finalizable, of a type with an allocatable ultimate component, or of a
  type for which default initialization is specified.

(It now uses an interface instead of an actual subroutine definition, 
since Tobias recently committed a patch to fix interfaces in order to 
unblock my work on this one.)  That bug is independent of enforcing 
this constraint so I'm planning to open a new issue for it with its 
own test case, if there isn't already one in Bugzilla.

I concur that that should be in a separate PR.


It's PR102641 now.


diff --git a/gcc/fortran/interface.c b/gcc/fortran/interface.c
...
+  gfc_array_spec *fas, *aas;
+  bool pointer_arg, allocatable_arg;;

Remove either ";" or ";".
@@ -3329,13 +3331,48 @@ gfc_compare_actual_formal (gfc_actual_arglist 
**ap, gfc_formal_arglist *formal,

+  if (a->expr->expr_type != EXPR_VARIABLE)
+    {
+  aas = NULL;
+  pointer_arg = false;
+  allocatable_arg = false;


This code is not generic but rather specific.
But it is fine as used in the code.

The question is how to prevent "?" or wrong code for future
code readers and writers.
 
Solution: I think the simplest would be to add a comment.


OK, done.


+  if (fas
+  && (fas->type == AS_ASSUMED_SHAPE
+  || fas->type == AS_DEFERRED
+  || (fas->type == AS_ASSUMED_RANK && f->sym->attr.pointer))
+  && aas
+  && aas->type == AS_ASSUMED_SIZE
    && (a->expr->ref == NULL
    || (a->expr->ref->type == REF_ARRAY
    && a->expr->ref->u.ar.type == AR_FULL)))

That's old code – but can you adapt it to handle BT_CLASS? I think
only 'f->sym->attr.pointer' causes the issue as it does not check for
CLASS_DATA()->attr.class_pointer – and the rest is fine, also because
of now using 'aas->type' which already encapsulates the classness.


Done.


Testcase:
--
type t
end type t
interface
   subroutine fc2 (x)
     import :: t
     class(t), pointer, intent(in) :: x(..)
   end
end interface
contains
   subroutine sub1(y)
     type(t), target :: y(*)
     call fc2 (y)  ! silently accepted
   end
end
--


OK, I incorporated that into the existing test case for that issue.


+  subroutine test_assumed_size_polymorphic (a1, a2)
+    class(t1) :: a1(*), a2(*)
+    call poly (a1, a2)  ! { dg-error "(A|a)ssumed.rank" }
+    call upoly (a1, a2)  ! { dg-error "(A|a)ssumed.rank" }
+  end subroutine

Can you also add a call like involving something like:
a1(5), a2(4:7), a1(:10) or a2(:-5) ? (Here, '(:-5)' is a
rank-1, size-zero array.)

Calls with those are valid as those pass the array size alongside.
 From the patch it looks as if they should just work, but it is
still good to test this.


+  subroutine test_assumed_size_unlimited_polymorphic (a1, a2)
+    class(*) :: a1(*), a2(*)
+    call upoly (a1, a2)  ! { dg-error "(A|a)ssumed.rank" }
+  end subroutine

Likewise.


This is done too.


Otherwise, it looks good to me.


OK to commit v2 of the patch (attached)?

-Sandra
commit 1beb8cc863225a5f2ba4a52fc3ff1d3320edbfef
Author: Sandra Loosemore 
Date:   Mon Sep 27 07:05:32 2021 -0700

Fortran: Add diagnostic for F2018:C839 (TS29113:C535c)

2021-10-08 Sandra Loosemore  

PR fortran/54753

gcc/fortran/
* interface.c (gfc_compare_actual_formal): Add diagnostic
for F2018:C839.  Refactor shared code and fix bugs with class
array info lookup, and extend similar diagnostic from PR94110
to also cover class types.

gcc/testsuite/
* gfortran.dg/c-interop/c535c-1.f90: Rewrite and expand.
* gfortran.dg/c-interop/c535c-2.f90: Remove xfails.
* gfortran.dg/c-interop/c535c-3.f90: Likewise.
* gfortran.dg/c-interop/c535c-4.f90: Likewise.
* gfortran.dg/PR94110.f90: Extend to cover class types.

diff --git a/gcc/fortran/interface.c b/gcc/fortran/interface.c
index a2fea0e97b8..2a71da75c72 100644
--- a/gcc/fortran/interface.c
+++ b/gcc/fortran/interface.c
@@ -3061,6 +3061,8 @@ gfc_compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal,
   unsigned long actual_size, formal_size;
   bool full_array = false;
   gfc_array_ref *actual_arr_ref;
+  gfc_array_spec *fas, *aas;
+  bool pointer_dummy, pointer_arg, allocatable_arg;
 
   actual = *ap;
 
@@ -3329,13 +3331,60 @@ gfc_compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal,
 	  return false;
 	}
 
-  if (f->sym->as
-	  && (f->sym->as->type == AS_ASSUMED_SHAPE
-	  || f->sym->as->type == 

Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Thomas Koenig via Fortran

Hi Iain,


If one wanted to prioritize library SO name stability - then, perhaps, the
approach Jonathan mentioned has been used for libstdc++ (add new
symbols for ieee128 with a different mangling to the existing r/c_16 ..)
would be preferable (the FE then has to choose the relevant symbol/
mangling depending on target).


That's not all that would have to be changed.  Consider

  write (*,*) 1.0_16
end program

which is translated (using -fdump-tree-original) to


_gfortran_st_write (_parm.0);
{
  static real(kind=16) C.3873 = 1.0e+0;

  _gfortran_transfer_real128_write (_parm.0, , 16);
}
_gfortran_st_write_done (_parm.0);

so we actually pass a separate kind number as well (why, I'm not sure).
We would have to go through libgfortran with a fine comb to find all
the occurrences.  Probably some m4 hackery in iparm.m4 and ifunction.m4.
So, doable from the library side, if some work.

Things get interesting for user code, calling a routine compiled
for double double with newer IEEE QP will result in breakage.
We cannot use the KIND number to differentiate, because we must
assume that people have used KIND=16 and selected_real_kind(30)
interchangably, and we certainly do not want to nail people to
the old double double precision on hardware for which IEEE QP
is available.  So, KIND=15 for IEEE QP is out.

It's not an easy problem, unfortunately.


Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Iain Sandoe



> On 8 Oct 2021, at 07:35, Thomas Koenig via Fortran  
> wrote:
> 
> 
> On 07.10.21 17:33, Jakub Jelinek wrote:
>>> It will also be a compatibility issue if users have code compiled on a LE
>>> system with GCC 11 and earlier with KIND=16, it will not link with GCC 12.
>> libgfortran ABI changed multiple times in the past already, e.g. the
>> so.1 -> so.2 transition in 4.2
>> so.2 -> so.3 transition in 4.3
>> so.3 -> so.4 transition in 7
>> so.4 -> so.5 transition in 8
>> and users have coped.
> 
> Yes, and it has always been a hassle for users, and we've been
> criticized for it.
> 
> This is currently a change which brings users on non-POWER-systems
> (the vast majority) all pain and no gain.  If this cannot be
> avoided, I would at least try to fit in as much of other improvements
> as there are possible.

If one wanted to prioritize library SO name stability - then, perhaps, the
approach Jonathan mentioned has been used for libstdc++ (add new
symbols for ieee128 with a different mangling to the existing r/c_16 ..)
would be preferable (the FE then has to choose the relevant symbol/
mangling depending on target).

.. perhaps I missed where that idea was already ruled out (in which case
sorry for the noise).
Iain
> 
> There's a PR for it somewhere, but I can think of three areas, none
> of the small, and all require an ABI change:
> 
> a) Get PDTs right (Paul?)
> b) Make file descriptors conform to the C interop version
> c) Remove the run-time parsing of I/O arguments and
>   replace them with a bit field.
> 
> What I mean by the last one is that
> 
>  WRITE (unit,'(A)',ADVANCE="NO")
> 
> we currently parse the "NO" at runtime, for every statement
> execution.  What we could be doing instead is to have
> 
> dt_parm.0.advance = __gfortran_evaluate_yesno ("NO")
> 
> where the latter function can be simplified at compile-time.
> 
> We should strive to break the ABI as few times as possible.
> 
> Best regards
> 
>   Thomas



Re: libgfortran.so SONAME and powerpc64le-linux ABI changes

2021-10-08 Thread Thomas Koenig via Fortran



On 07.10.21 17:33, Jakub Jelinek wrote:

It will also be a compatibility issue if users have code compiled on a LE
system with GCC 11 and earlier with KIND=16, it will not link with GCC 12.

libgfortran ABI changed multiple times in the past already, e.g. the
so.1 -> so.2 transition in 4.2
so.2 -> so.3 transition in 4.3
so.3 -> so.4 transition in 7
so.4 -> so.5 transition in 8
and users have coped.


Yes, and it has always been a hassle for users, and we've been
criticized for it.

This is currently a change which brings users on non-POWER-systems
(the vast majority) all pain and no gain.  If this cannot be
avoided, I would at least try to fit in as much of other improvements
as there are possible.

There's a PR for it somewhere, but I can think of three areas, none
of the small, and all require an ABI change:

a) Get PDTs right (Paul?)
b) Make file descriptors conform to the C interop version
c) Remove the run-time parsing of I/O arguments and
   replace them with a bit field.

What I mean by the last one is that

  WRITE (unit,'(A)',ADVANCE="NO")

we currently parse the "NO" at runtime, for every statement
execution.  What we could be doing instead is to have

dt_parm.0.advance = __gfortran_evaluate_yesno ("NO")

where the latter function can be simplified at compile-time.

We should strive to break the ABI as few times as possible.

Best regards

Thomas