public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
@ 2021-11-12 17:39 Harald Anlauf
  2021-11-12 20:18 ` Bernhard Reutner-Fischer
  0 siblings, 1 reply; 8+ messages in thread
From: Harald Anlauf @ 2021-11-12 17:39 UTC (permalink / raw)
  To: fortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 293 bytes --]

Dear Fortranners,

F2008:15.3.5 relaxed the condition on interoperable character variables
and now allows values different from one.  Similar text in F2018:18.3.4.
This required an adjustment in the interoperability check.

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

Thanks,
Harald


[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #2: 0001-Fortran-fix-interoperability-check-for-character-var.patch --]
[-- Type: text/x-patch, Size: 2666 bytes --]

From 1fc44a5bf0b294021490f3c0a1539982a09000f5 Mon Sep 17 00:00:00 2001
From: Harald Anlauf <anlauf@gmx.de>
Date: Fri, 12 Nov 2021 18:32:18 +0100
Subject: [PATCH] Fortran: fix interoperability check for character variables
 for F2008

gcc/fortran/ChangeLog:

	PR fortran/102368
	* check.c (is_c_interoperable): F2008:15.3.5 relaxed the condition
	on interoperable character variables and allows values different
	from one.

gcc/testsuite/ChangeLog:

	PR fortran/102368
	* gfortran.dg/c_sizeof_7.f90: New test.
---
 gcc/fortran/check.c                      | 20 ++++++++++++++------
 gcc/testsuite/gfortran.dg/c_sizeof_7.f90 | 13 +++++++++++++
 2 files changed, 27 insertions(+), 6 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/c_sizeof_7.f90

diff --git a/gcc/fortran/check.c b/gcc/fortran/check.c
index ffa07b510cd..69a2e35e81b 100644
--- a/gcc/fortran/check.c
+++ b/gcc/fortran/check.c
@@ -5272,13 +5272,21 @@ is_c_interoperable (gfc_expr *expr, const char **msg, bool c_loc, bool c_f_ptr)
 	&& !gfc_simplify_expr (expr->ts.u.cl->length, 0))
       gfc_internal_error ("is_c_interoperable(): gfc_simplify_expr failed");

-    if (!c_loc && expr->ts.u.cl
-	&& (!expr->ts.u.cl->length
-	    || expr->ts.u.cl->length->expr_type != EXPR_CONSTANT
-	    || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0))
+    if (!c_loc && expr->ts.u.cl)
       {
-	*msg = "Type shall have a character length of 1";
-	return false;
+	bool len_ok = (expr->ts.u.cl->length
+		       && expr->ts.u.cl->length->expr_type == EXPR_CONSTANT);
+
+	/* F2003:15.2.1 required the length of a character variable to be one.
+	   F2008:15.3.5 relaxed this to constant length. */
+	if (len_ok && !(gfc_option.allow_std & GFC_STD_F2008))
+	  len_ok = mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) == 0;
+
+	if (!len_ok)
+	  {
+	    *msg = "Type shall have a character length of 1";
+	    return false;
+	  }
       }
     }

diff --git a/gcc/testsuite/gfortran.dg/c_sizeof_7.f90 b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90
new file mode 100644
index 00000000000..3cfa3371f72
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90
@@ -0,0 +1,13 @@
+! { dg-do compile }
+! { dg-options "-std=f2008 -fdump-tree-original" }
+! { dg-final { scan-tree-dump-times "_gfortran_stop_numeric" 0 "original" } }
+! PR fortran/102368
+
+program main
+  use, intrinsic :: iso_c_binding
+  implicit none
+  character(kind=c_char, len=*), parameter :: a = 'abc'
+  character(kind=c_char, len=8)            :: b
+  if (c_sizeof (a) /= 3) stop 1
+  if (c_sizeof (b) /= 8) stop 2
+end program main
--
2.26.2


^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
  2021-11-12 17:39 [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING Harald Anlauf
@ 2021-11-12 20:18 ` Bernhard Reutner-Fischer
  2021-11-12 20:35   ` Harald Anlauf
  0 siblings, 1 reply; 8+ messages in thread
From: Bernhard Reutner-Fischer @ 2021-11-12 20:18 UTC (permalink / raw)
  To: Harald Anlauf via Fortran; +Cc: rep.dot.nop, Harald Anlauf, gcc-patches

On Fri, 12 Nov 2021 18:39:48 +0100
Harald Anlauf via Fortran <fortran@gcc.gnu.org> wrote:

Sounds plausible.
Nits:

> diff --git a/gcc/testsuite/gfortran.dg/c_sizeof_7.f90 b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90
> new file mode 100644
> index 00000000000..3cfa3371f72
> --- /dev/null
> +++ b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90

[I'd name this .f08, no?]

> @@ -0,0 +1,13 @@
> +! { dg-do compile }
> +! { dg-options "-std=f2008 -fdump-tree-original" }

[and drop the -std]

> +! { dg-final { scan-tree-dump-times "_gfortran_stop_numeric" 0 "original" } }

[ ...-times 0 == scan-tree-dump-not ]

> +! PR fortran/102368
> +
> +program main
> +  use, intrinsic :: iso_c_binding
> +  implicit none
> +  character(kind=c_char, len=*), parameter :: a = 'abc'
> +  character(kind=c_char, len=8)            :: b

character(kind=c_char, len=-42) :: c ! { dg-error "positive integer greater than 0" }
character(kind=c_char, len=-0) :: d ! { dg-error "positive integer greater than 0" }
character(kind=c_char, len=0) :: e ! { dg-error "positive integer greater than 0" }
character(kind=c_char, len=+0) :: f ! { dg-error "positive integer greater than 0" }
character(kind=c_char, len=0.0d) :: g ! { dg-error "positive integer greater than 0" }
character(kind=c_char, len=3.) :: h ! { dg-error "positive integer greater than 0" }
character(kind=c_char, len=.031415e2) :: i ! { dg-error "positive integer greater than 0" }
...
are caught elsewhere if one assumes that len should be a positive int > 0 (didn't look)
Also did not look if
character(kind=c_char, len=SELECTED_REAL_KIND(10)) :: j ! is that constant? Should it be?

> +  if (c_sizeof (a) /= 3) stop 1
> +  if (c_sizeof (b) /= 8) stop 2

indeed.
cheers,

> +end program main
> --
> 2.26.2
> 


^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
  2021-11-12 20:18 ` Bernhard Reutner-Fischer
@ 2021-11-12 20:35   ` Harald Anlauf
  2021-11-12 20:35     ` Harald Anlauf
  2021-11-12 21:58     ` Bernhard Reutner-Fischer
  0 siblings, 2 replies; 8+ messages in thread
From: Harald Anlauf @ 2021-11-12 20:35 UTC (permalink / raw)
  To: Bernhard Reutner-Fischer, Harald Anlauf via Fortran; +Cc: gcc-patches

Hi Bernhard,

Am 12.11.21 um 21:18 schrieb Bernhard Reutner-Fischer via Fortran:
> On Fri, 12 Nov 2021 18:39:48 +0100
> Harald Anlauf via Fortran <fortran@gcc.gnu.org> wrote:
>
> Sounds plausible.

this is what I thought, too.  And nvfortran and flang accept the
testcase, as well as crayftn (cce/12.0.2).

Intel accepts the first case (a), but rejects the second (b).
I asked in the Intel forum.  Steve Lionel doubts that the code is
valid.

There might be some confusion on my side, but having Cray on my
side feels good.  (Although the PR was entered into bugzilla by
a Cray employee).

> Nits:
>
>> diff --git a/gcc/testsuite/gfortran.dg/c_sizeof_7.f90 b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90
>> new file mode 100644
>> index 00000000000..3cfa3371f72
>> --- /dev/null
>> +++ b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90
>
> [I'd name this .f08, no?]
>
>> @@ -0,0 +1,13 @@
>> +! { dg-do compile }
>> +! { dg-options "-std=f2008 -fdump-tree-original" }
>
> [and drop the -std]
>
>> +! { dg-final { scan-tree-dump-times "_gfortran_stop_numeric" 0 "original" } }
>
> [ ...-times 0 == scan-tree-dump-not ]

Good point.

>> +! PR fortran/102368
>> +
>> +program main
>> +  use, intrinsic :: iso_c_binding
>> +  implicit none
>> +  character(kind=c_char, len=*), parameter :: a = 'abc'
>> +  character(kind=c_char, len=8)            :: b
>
> character(kind=c_char, len=-42) :: c ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=-0) :: d ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=0) :: e ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=+0) :: f ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=0.0d) :: g ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=3.) :: h ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=.031415e2) :: i ! { dg-error "positive integer greater than 0" }
> ...
> are caught elsewhere if one assumes that len should be a positive int > 0 (didn't look)
> Also did not look if
> character(kind=c_char, len=SELECTED_REAL_KIND(10)) :: j ! is that constant? Should it be?

These things should already be handled in general and
elsewhere, as they are not about interoperability.

>> +  if (c_sizeof (a) /= 3) stop 1
>> +  if (c_sizeof (b) /= 8) stop 2
>
> indeed.
> cheers,
>
>> +end program main
>> --
>> 2.26.2
>>
>

Thanks,
Harald




^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
  2021-11-12 20:35   ` Harald Anlauf
@ 2021-11-12 20:35     ` Harald Anlauf
  2021-11-12 21:58     ` Bernhard Reutner-Fischer
  1 sibling, 0 replies; 8+ messages in thread
From: Harald Anlauf @ 2021-11-12 20:35 UTC (permalink / raw)
  To: fortran; +Cc: gcc-patches

Hi Bernhard,

Am 12.11.21 um 21:18 schrieb Bernhard Reutner-Fischer via Fortran:
> On Fri, 12 Nov 2021 18:39:48 +0100
> Harald Anlauf via Fortran <fortran@gcc.gnu.org> wrote:
> 
> Sounds plausible.

this is what I thought, too.  And nvfortran and flang accept the
testcase, as well as crayftn (cce/12.0.2).

Intel accepts the first case (a), but rejects the second (b).
I asked in the Intel forum.  Steve Lionel doubts that the code is
valid.

There might be some confusion on my side, but having Cray on my
side feels good.  (Although the PR was entered into bugzilla by
a Cray employee).

> Nits:
> 
>> diff --git a/gcc/testsuite/gfortran.dg/c_sizeof_7.f90 b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90
>> new file mode 100644
>> index 00000000000..3cfa3371f72
>> --- /dev/null
>> +++ b/gcc/testsuite/gfortran.dg/c_sizeof_7.f90
> 
> [I'd name this .f08, no?]
> 
>> @@ -0,0 +1,13 @@
>> +! { dg-do compile }
>> +! { dg-options "-std=f2008 -fdump-tree-original" }
> 
> [and drop the -std]
> 
>> +! { dg-final { scan-tree-dump-times "_gfortran_stop_numeric" 0 "original" } }
> 
> [ ...-times 0 == scan-tree-dump-not ]

Good point.

>> +! PR fortran/102368
>> +
>> +program main
>> +  use, intrinsic :: iso_c_binding
>> +  implicit none
>> +  character(kind=c_char, len=*), parameter :: a = 'abc'
>> +  character(kind=c_char, len=8)            :: b
> 
> character(kind=c_char, len=-42) :: c ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=-0) :: d ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=0) :: e ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=+0) :: f ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=0.0d) :: g ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=3.) :: h ! { dg-error "positive integer greater than 0" }
> character(kind=c_char, len=.031415e2) :: i ! { dg-error "positive integer greater than 0" }
> ...
> are caught elsewhere if one assumes that len should be a positive int > 0 (didn't look)
> Also did not look if
> character(kind=c_char, len=SELECTED_REAL_KIND(10)) :: j ! is that constant? Should it be?

These things should already be handled in general and
elsewhere, as they are not about interoperability.

>> +  if (c_sizeof (a) /= 3) stop 1
>> +  if (c_sizeof (b) /= 8) stop 2
> 
> indeed.
> cheers,
> 
>> +end program main
>> --
>> 2.26.2
>>
> 

Thanks,
Harald





^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
  2021-11-12 20:35   ` Harald Anlauf
  2021-11-12 20:35     ` Harald Anlauf
@ 2021-11-12 21:58     ` Bernhard Reutner-Fischer
  2021-11-12 22:23       ` Harald Anlauf
  1 sibling, 1 reply; 8+ messages in thread
From: Bernhard Reutner-Fischer @ 2021-11-12 21:58 UTC (permalink / raw)
  To: Harald Anlauf; +Cc: rep.dot.nop, Harald Anlauf via Fortran

On Fri, 12 Nov 2021 21:35:42 +0100
Harald Anlauf <anlauf@gmx.de> wrote:

> Hi Bernhard,
> 
> Am 12.11.21 um 21:18 schrieb Bernhard Reutner-Fischer via Fortran:
> > On Fri, 12 Nov 2021 18:39:48 +0100
> > Harald Anlauf via Fortran <fortran@gcc.gnu.org> wrote:
> >
> > Sounds plausible.  
> 
> this is what I thought, too.  And nvfortran and flang accept the
> testcase, as well as crayftn (cce/12.0.2).

Don't know about the former 2, but cray is really the MIPS compiler
(open64 / pathscale etc), no?
I always liked the SGI compiler (it was marvellous in mem addressing
really, at least in my cases in former times) but i'm not familiar with
the other two so cannot deduct anything from their opinion TBH.
> 
> Intel accepts the first case (a), but rejects the second (b).
> I asked in the Intel forum.  Steve Lionel doubts that the code is
> valid.
On what grounds does Steve L. think it's invalid? Missing initializer
to rectify the len=8? If so, what's the reasoning to doubt that?

> 
> There might be some confusion on my side, but having Cray on my
> side feels good.  (Although the PR was entered into bugzilla by
> a Cray employee).

Vendors. Well. It would certainly be the first time a vendor was not
entirely correct.
IME vendors tended to favour compatibility over correctness more often
than not. This certainly may have, erm, has changed.

> > are caught elsewhere if one assumes that len should be a positive int > 0 (didn't look)
> > Also did not look if
> > character(kind=c_char, len=SELECTED_REAL_KIND(10)) :: j ! is that constant? Should it be?  
> 
> These things should already be handled in general and
> elsewhere, as they are not about interoperability.

Excellent. I'd ACK your patch then but i cannot approve it.
Thanks for the patch and cheers,

^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
  2021-11-12 21:58     ` Bernhard Reutner-Fischer
@ 2021-11-12 22:23       ` Harald Anlauf
  2021-11-12 22:23         ` Harald Anlauf
  2021-11-13  8:48         ` Bernhard Reutner-Fischer
  0 siblings, 2 replies; 8+ messages in thread
From: Harald Anlauf @ 2021-11-12 22:23 UTC (permalink / raw)
  To: fortran; +Cc: Harald Anlauf via Fortran

Hi Bernhard,

Am 12.11.21 um 22:58 schrieb Bernhard Reutner-Fischer via Fortran:
> On Fri, 12 Nov 2021 21:35:42 +0100
> Harald Anlauf <anlauf@gmx.de> wrote:
> 
>> Hi Bernhard,
>>
>> Am 12.11.21 um 21:18 schrieb Bernhard Reutner-Fischer via Fortran:
>>> On Fri, 12 Nov 2021 18:39:48 +0100
>>> Harald Anlauf via Fortran <fortran@gcc.gnu.org> wrote:
>>>
>>> Sounds plausible.
>>
>> this is what I thought, too.  And nvfortran and flang accept the
>> testcase, as well as crayftn (cce/12.0.2).
> 
> Don't know about the former 2, but cray is really the MIPS compiler
> (open64 / pathscale etc), no?

I thought that most of Cray's compilers was their own development
targeting their vector hardware.  My own experience is limited to
their compilers on x86-type systems (+ GPUs).  They seemed to be
rather progressive in developing the Fortran standard as well as
implementing it in their own compilers, besides supporting open
standards.  (That seemed to slow down w.r.t. OpenACC).

> I always liked the SGI compiler (it was marvellous in mem addressing
> really, at least in my cases in former times) but i'm not familiar with
> the other two so cannot deduct anything from their opinion TBH.
>>
>> Intel accepts the first case (a), but rejects the second (b).
>> I asked in the Intel forum.  Steve Lionel doubts that the code is
>> valid.
> On what grounds does Steve L. think it's invalid? Missing initializer
> to rectify the len=8? If so, what's the reasoning to doubt that?

See:

https://community.intel.com/t5/Intel-Fortran-Compiler/Interoperability-of-character-variables/td-p/1329554

>>
>> There might be some confusion on my side, but having Cray on my
>> side feels good.  (Although the PR was entered into bugzilla by
>> a Cray employee).
> 
> Vendors. Well. It would certainly be the first time a vendor was not
> entirely correct.
> IME vendors tended to favour compatibility over correctness more often
> than not. This certainly may have, erm, has changed.

Well, Cray not only sells hardware, but systems with support.
You get multiple programming environments on their systems,
one of which is likely cce (Cray Compilation Environment),
and very often the GNU compilers.  Depending on the contract
you get in addition Intel, Nvidia, ...

Users may report issues with these components through their
support contract.  With GNU, I guess they just add a PR to
bugzilla; with commercial software vendors their might be
different ways.

>>> are caught elsewhere if assumes that len should be a positive int > 0 (didn't look)
>>> Also did not look if
>>> character(kind=c_char, len=SELECTED_REAL_KIND(10)) :: j ! is that constant? Should it be?
>>
>> These things should already be handled in general and
>> elsewhere, as they are not about interoperability.
> 
> Excellent. I'd ACK your patch then but i cannot approve it.
> Thanks for the patch and cheers,
> 

There'll be a way to resolve this PR.  Maybe Tobias or Thomas have
an opinion.  There are strange ways in the standard anyway to pass
Fortran character strings to BIND(C) procedures.  Look e.g. at
"5.5.2.11 Sequence association" which sort of hacks this situation
for some applications relevant to me.

Cheers,
Harald





^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
  2021-11-12 22:23       ` Harald Anlauf
@ 2021-11-12 22:23         ` Harald Anlauf
  2021-11-13  8:48         ` Bernhard Reutner-Fischer
  1 sibling, 0 replies; 8+ messages in thread
From: Harald Anlauf @ 2021-11-12 22:23 UTC (permalink / raw)
  To: Bernhard Reutner-Fischer; +Cc: Harald Anlauf via Fortran

Hi Bernhard,

Am 12.11.21 um 22:58 schrieb Bernhard Reutner-Fischer via Fortran:
> On Fri, 12 Nov 2021 21:35:42 +0100
> Harald Anlauf <anlauf@gmx.de> wrote:
>
>> Hi Bernhard,
>>
>> Am 12.11.21 um 21:18 schrieb Bernhard Reutner-Fischer via Fortran:
>>> On Fri, 12 Nov 2021 18:39:48 +0100
>>> Harald Anlauf via Fortran <fortran@gcc.gnu.org> wrote:
>>>
>>> Sounds plausible.
>>
>> this is what I thought, too.  And nvfortran and flang accept the
>> testcase, as well as crayftn (cce/12.0.2).
>
> Don't know about the former 2, but cray is really the MIPS compiler
> (open64 / pathscale etc), no?

I thought that most of Cray's compilers was their own development
targeting their vector hardware.  My own experience is limited to
their compilers on x86-type systems (+ GPUs).  They seemed to be
rather progressive in developing the Fortran standard as well as
implementing it in their own compilers, besides supporting open
standards.  (That seemed to slow down w.r.t. OpenACC).

> I always liked the SGI compiler (it was marvellous in mem addressing
> really, at least in my cases in former times) but i'm not familiar with
> the other two so cannot deduct anything from their opinion TBH.
>>
>> Intel accepts the first case (a), but rejects the second (b).
>> I asked in the Intel forum.  Steve Lionel doubts that the code is
>> valid.
> On what grounds does Steve L. think it's invalid? Missing initializer
> to rectify the len=8? If so, what's the reasoning to doubt that?

See:

https://community.intel.com/t5/Intel-Fortran-Compiler/Interoperability-of-character-variables/td-p/1329554

>>
>> There might be some confusion on my side, but having Cray on my
>> side feels good.  (Although the PR was entered into bugzilla by
>> a Cray employee).
>
> Vendors. Well. It would certainly be the first time a vendor was not
> entirely correct.
> IME vendors tended to favour compatibility over correctness more often
> than not. This certainly may have, erm, has changed.

Well, Cray not only sells hardware, but systems with support.
You get multiple programming environments on their systems,
one of which is likely cce (Cray Compilation Environment),
and very often the GNU compilers.  Depending on the contract
you get in addition Intel, Nvidia, ...

Users may report issues with these components through their
support contract.  With GNU, I guess they just add a PR to
bugzilla; with commercial software vendors their might be
different ways.

>>> are caught elsewhere if assumes that len should be a positive int > 0 (didn't look)
>>> Also did not look if
>>> character(kind=c_char, len=SELECTED_REAL_KIND(10)) :: j ! is that constant? Should it be?
>>
>> These things should already be handled in general and
>> elsewhere, as they are not about interoperability.
>
> Excellent. I'd ACK your patch then but i cannot approve it.
> Thanks for the patch and cheers,
>

There'll be a way to resolve this PR.  Maybe Tobias or Thomas have
an opinion.  There are strange ways in the standard anyway to pass
Fortran character strings to BIND(C) procedures.  Look e.g. at
"5.5.2.11 Sequence association" which sort of hacks this situation
for some applications relevant to me.

Cheers,
Harald




^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING
  2021-11-12 22:23       ` Harald Anlauf
  2021-11-12 22:23         ` Harald Anlauf
@ 2021-11-13  8:48         ` Bernhard Reutner-Fischer
  1 sibling, 0 replies; 8+ messages in thread
From: Bernhard Reutner-Fischer @ 2021-11-13  8:48 UTC (permalink / raw)
  To: Harald Anlauf; +Cc: rep.dot.nop, Harald Anlauf via Fortran

On Fri, 12 Nov 2021 23:23:24 +0100
Harald Anlauf <anlauf@gmx.de> wrote:

> F2008:15.3.5 relaxed the condition on interoperable character variables
> and now allows values different from one.  Similar text in F2018:18.3.4.
> This required an adjustment in the interoperability check.

In N2146 i see though

F2018:18.3.2 Interoperability of intrinsic types
p1: ... If the type is character, the length type parameter is
interoperable if and only if its value is one.

So it seems the 'one' constraint just was moved ?

> There'll be a way to resolve this PR.  Maybe Tobias or Thomas have
> an opinion.  There are strange ways in the standard anyway to pass
> Fortran character strings to BIND(C) procedures.  Look e.g. at
> "5.5.2.11 Sequence association" which sort of hacks this situation
> for some applications relevant to me.

Yes. I think you refer to 15.5.2.11 (15, not 5)
NOTE 18.21 contains a sample 

CHARACTER(LEN=10, KIND=C_CHAR) :: &
& DIGIT_STRING = C_CHAR_’123456789’ // C_NULL_CHAR

where, if i read this correctly, the interoperability is laundered by
"These correspond to character array dummy
arguments in the procedure interface body as allowed
by Fortran’s rules of sequence association (15.5.2.11)"

The reasoning seems to be that the LEN=10 in this context is a mere
array initializer for an array(10) and hence a "10 times LEN=1", thus
fine?

^ permalink raw reply	[flat|nested] 8+ messages in thread

end of thread, other threads:[~2021-11-13  8:48 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2021-11-12 17:39 [PATCH] PR fortran/102368 - Failure to compile program using the C_SIZEOF function in ISO_C_BINDING Harald Anlauf
2021-11-12 20:18 ` Bernhard Reutner-Fischer
2021-11-12 20:35   ` Harald Anlauf
2021-11-12 20:35     ` Harald Anlauf
2021-11-12 21:58     ` Bernhard Reutner-Fischer
2021-11-12 22:23       ` Harald Anlauf
2021-11-12 22:23         ` Harald Anlauf
2021-11-13  8:48         ` Bernhard Reutner-Fischer

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).