Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Variables that are function references

23 views
Skip to first unread message

Ian Harvey

unread,
Feb 26, 2012, 8:29:02 PM2/26/12
to
In F2008, a variable can be a function reference, if that function has a
data pointer result.

Does that function reference need to be of the classic
/function-reference/ form (something like "function_name(args)") or is
it also permitted to be a defined operation type of function reference?

My take is that they are permitted to be the latter, based on the
definition of function reference (not in italics) in 1.3.120.2. If that
is the case, does the following program read from the console or from an
unformatted file?

(My Fortran 2008 compiler is on the blink at the moment, so apologies
for any silly mistakes).


MODULE SomeOperators
IMPLICIT NONE
PRIVATE
PUBLIC :: OPERATOR(.op.)

INTERFACE OPERATOR(.op.)
PROCEDURE op_unary
PROCEDURE op_binary
END INTERFACE OPERATOR(.op.)

REAL, PUBLIC, TARGET :: thing
CONTAINS
FUNCTION op_unary(i) RESULT(ptr)
INTEGER, INTENT(IN) :: i
REAL, POINTER :: ptr ! Function result
!****
ptr => thing
END FUNCTION op_unary

FUNCTION op_binary(i,j) RESULT(fmt)
INTEGER, INTENT(IN) :: i
INTEGER, INTENT(IN) :: j
CHARACTER(7) :: fmt ! Function result
!****
fmt = '(G10.2)'
END FUNCTION op_binary
END MODULE SomeOperators

PROGRAM IAmConfused
USE SomeOperators
IMPLICIT NONE
INTEGER :: unit
REAL :: b
!************************************
unit = 10
thing = 1.0
b = 1.0

!------------------------------------
! Some prep work.

OPEN( unit,FILE='test.bin', FORM='UNFORMATTED', &
ACCESS='SEQUENTIAL', ACTION='WRITE', &
POSITION='REWIND', STATUS='REPLACE' )
WRITE (unit) 123.4, 567.8
CLOSE (unit)

OPEN( unit,FILE='test.bin', FORM='UNFORMATTED', &
ACCESS='SEQUENTIAL', ACTION='READ', &
POSITION='REWIND', STATUS='OLD' )

PRINT "('Enter a real number')"

!------------------------------------
! What does this do?

READ (unit) .op. 666, b

!------------------------------------
! Cleanup

CLOSE(unit, STATUS='DELETE')

PRINT *, thing, b

END PROGRAM IAmConfused


robert....@oracle.com

unread,
Feb 26, 2012, 9:48:57 PM2/26/12
to
On Feb 26, 5:29 pm, Ian Harvey <ian_har...@bigpond.com> wrote:
> In F2008, a variable can be a function reference, if that function has a
> data pointer result.

Right.

> Does that function reference need to be of the classic
> /function-reference/ form (something like "function_name(args)") or is
> it also permitted to be a defined operation type of function reference?

The latter.

> My take is that they are permitted to be the latter, based on the
> definition of function reference (not in italics) in 1.3.120.2.  If that
> is the case, does the following program read from the console or from an
> unformatted file?

A good question. Note that the syntax term /format/ (R915) does not
derive the term /variable/. Therefore, the operator .op. must be the
unary form of the operator. The READ statement will read from the
unit identified by 10.

Bob Corbett

robert....@oracle.com

unread,
Feb 26, 2012, 9:59:09 PM2/26/12
to
On Feb 26, 6:48 pm, robert.corb...@oracle.com wrote:
> On Feb 26, 5:29 pm, Ian Harvey <ian_har...@bigpond.com> wrote:
>
> > In F2008, a variable can be a function reference, if that function has a
> > data pointer result.
>
> Right.
>
> > Does that function reference need to be of the classic
> > /function-reference/ form (something like "function_name(args)") or is
> > it also permitted to be a defined operation type of function reference?
>
> The latter.
>
> > My take is that they are permitted to be the latter, based on the
> > definition of function reference (not in italics) in 1.3.120.2.  If that
> > is the case, does the following program read from the console or from an
> > unformatted file?
>
> A good question.  Note that the syntax term /format/ (R915) does not
> derive the term /variable/.  Therefore, the operator .op. must be the
> unary form of the operator.  The READ statement will read from the
> unit identified by 10.
>
> Bob Corbett

I take it back. I answered too quickly. There might well be an
ambiguity.

Bob Corbett

Ian Harvey

unread,
Feb 26, 2012, 10:23:49 PM2/26/12
to
On 2012-02-27 1:48 PM, robert....@oracle.com wrote:
> On Feb 26, 5:29 pm, Ian Harvey<ian_har...@bigpond.com> wrote:
>> In F2008, a variable can be a function reference, if that function has a
>> data pointer result.
>
> Right.
>
>> Does that function reference need to be of the classic
>> /function-reference/ form (something like "function_name(args)") or is
>> it also permitted to be a defined operation type of function reference?
>
> The latter.
>
>> My take is that they are permitted to be the latter, based on the
>> definition of function reference (not in italics) in 1.3.120.2. If that
>> is the case, does the following program read from the console or from an
>> unformatted file?
>
> A good question. Note that the syntax term /format/ (R915) does not
> derive the term /variable/. Therefore, the operator .op. must be the
> unary form of the operator. The READ statement will read from the
> unit identified by 10.


/format/ does include the term /default-char-expr/, and

(unit) .op. 666

is (maybe "could be", or "would be in any other context") such an
expression - the (unit) thing just being a (pointlessly) parenthesised
expression and .op. resolving to the op_binary specific procedure that
has a default character result.

I think under F90 that's how it is interpreted anyway, though it gives
all five compilers I tried grief.

What am I missing that stops this from being a syntax ambiguity?

robert....@oracle.com

unread,
Feb 26, 2012, 11:36:31 PM2/26/12
to
On Feb 26, 7:23 pm, Ian Harvey <ian_har...@bigpond.com> wrote:
> On 2012-02-27 1:48 PM, robert.corb...@oracle.com wrote:
>
> >> My take is that they are permitted to be the latter, based on the
> >> definition of function reference (not in italics) in 1.3.120.2.  If that
> >> is the case, does the following program read from the console or from an
> >> unformatted file?
>
> > A good question.  Note that the syntax term /format/ (R915) does not
> > derive the term /variable/.  Therefore, the operator .op. must be the
> > unary form of the operator.  The READ statement will read from the
> > unit identified by 10.
>
> /format/ does include the term /default-char-expr/, and
>
>   (unit) .op. 666
>
> is (maybe "could be", or "would be in any other context") such an
> expression - the (unit) thing just being a (pointlessly) parenthesised
> expression and .op. resolving to the op_binary specific procedure that
> has a default character result.
>
> I think under F90 that's how it is interpreted anyway, though it gives
> all five compilers I tried grief.
>
> What am I missing that stops this from being a syntax ambiguity?

I realized soon after posting my first response that your example
did not show the case I thought it did. There does appear to be
an ambiguity.

Bob Corbett

Ian Harvey

unread,
Mar 1, 2012, 10:19:34 PM3/1/12
to
On 2012-02-27 3:36 PM, robert....@oracle.com wrote:
...
> I realized soon after posting my first response that your example
> did not show the case I thought it did. There does appear to be
> an ambiguity.

Apologies for that - we crossed posts. The example was rather obscure too.

Here's another case:

MODULE AUnaryAndBinaryOp
IMPLICIT NONE
PRIVATE
PUBLIC :: OPERATOR(.op.)

INTERFACE OPERATOR(.op.)
PROCEDURE unary_op
PROCEDURE binary_op
END INTERFACE OPERATOR(.op.)

REAL, TARGET, PUBLIC :: blue
REAL, TARGET, PUBLIC :: green
CONTAINS
FUNCTION unary_op(arg) RESULT(ptr)
INTEGER, INTENT(IN) :: arg
REAL, POINTER :: ptr
ptr => blue
END FUNCTION unary_op

FUNCTION binary_op(lhs, rhs) RESULT(ptr)
INTEGER, INTENT(IN) :: lhs
INTEGER, INTENT(IN) :: rhs
REAL, POINTER :: ptr
ptr => green
END FUNCTION binary_op
END MODULE MODULE AUnaryAndBinaryOp


PROGRAM AmbiguousAssignment
USE AUnaryAndBinaryOp
IMPLICIT NONE
!*************************************
blue = 1.0
green = 2.0

! What does this do? Is 10 a label
! or an operand?
10 .op. 20 = 5.0

PRINT *, blue, green
END PROGRAM AmbiguousAssignment


The previous example was (I think) valid F2003, with F2008 adding a
possible alternative interpretation. I presume in those circumstances
the existing F90+ interpretation would have precedence?

In this case both possibilities require F2008. Is this one of those
cases where the standard "fails to establish an interpretation" and so
program and processor behaviour is formally undefined?

robert....@oracle.com

unread,
Mar 2, 2012, 12:07:14 AM3/2/12
to
On Mar 1, 7:19 pm, Ian Harvey <ian_har...@bigpond.com> wrote:
> On 2012-02-27 3:36 PM, robert.corb...@oracle.com wrote:
> ...
>
> > I realized soon after posting my first response that your example
> > did not show the case I thought it did.  There does appear to be
> > an ambiguity.
>
> Apologies for that - we crossed posts.  The example was rather obscure too.

Happens all the time. I frequently write responses to posts
only to find that by the time I hit "send," there have been
other responses covering everything I had to say.

I did report the problem to the J3 e-mail list. There is
agreement that the ambiguity is real.

Bob Corbett
I do not think so, but other members of the committee disagree.
I think the standard establishes more than one interpretation,
which is not the same as failing to establish an interpretation.

Bob Corbett

robert....@oracle.com

unread,
Mar 5, 2012, 3:53:13 AM3/5/12
to
I found an ambiguity that is similar to your last one.

DO 10 .OP. P = 1, N

The "10" is either the label of the DO loop's terminal
statement or the left operand of a binary operation.

Bob Corbett

Ian Harvey

unread,
Mar 5, 2012, 7:44:44 AM3/5/12
to
I think there are additional restrictions around the /do-variable/ that
save the day here (the same aspect that prevents you from using a
general array element as the index) - see R819.

Thanks for forwarding this to the J3 list. I think that this function
reference as a variable feature could be useful, its just a shame that
the syntax has these quirks. If the function reference was limited to
being a classic /function-reference/ then a lot of the issues disappear,
and I doubt the loss of some syntax niceness (or nastiness, depending on
your point of view) would offend too many.

IanH

robert....@oracle.com

unread,
Mar 5, 2012, 3:01:13 PM3/5/12
to
On Mar 5, 4:44 am, Ian Harvey <ian_har...@bigpond.com> wrote:
> On 2012-03-05 7:53 PM, robert.corb...@oracle.com wrote:
>
> > I found an ambiguity that is similar to your last one.
>
> >        DO 10 .OP. P = 1, N
>
> > The "10" is either the label of the DO loop's terminal
> > statement or the left operand of a binary operation.
>
> > Bob Corbett
>
> I think there are additional restrictions around the /do-variable/ that
> save the day here (the same aspect that prevents you from using a
> general array element as the index) - see R819.

You are correct. I oeverlooked that a /do-variable/ is a /name/,
not a /variable/.

> Thanks for forwarding this to the J3 list.  I think that this function
> reference as a variable feature could be useful, its just a shame that
> the syntax has these quirks.  If the function reference was limited to
> being a classic /function-reference/ then a lot of the issues disappear,
> and I doubt the loss of some syntax niceness (or nastiness, depending on
> your point of view) would offend too many.

The ambiguities are a hot topic on the e-mail list. I agree with your
proposed solution, but other people suggested other solutions. The
issue
is not yet settled.

Bob Corbett

glen herrmannsfeldt

unread,
Mar 5, 2012, 3:27:48 PM3/5/12
to
robert....@oracle.com wrote:
> On Mar 5, 4:44 am, Ian Harvey <ian_har...@bigpond.com> wrote:
>> On 2012-03-05 7:53 PM, robert.corb...@oracle.com wrote:

(snip)
>> > DO 10 .OP. P = 1, N
(snip)
>> I think there are additional restrictions around the /do-variable/
>> that save the day here (the same aspect that prevents you
>> from using a general array element as the index) - see R819.

> You are correct. I oeverlooked that a /do-variable/ is a /name/,
> not a /variable/.

I do remember many years ago in PL/I doing something like:

DCL I FIXED BINARY(31,0) COMPLEX;
I=0;
DO IMAG(I)=1 TO 100;
PUT SKIP LIST(I,SQRT(I));
END;

Using a pseudo-variable, which looks like a function but can
be used in the context of an L-value. (Last I knew, built-in
only, there are no user-defined pseudo-variables.)

The one restriction that I remember is that you can't nest them.

Substring assignment is also done with a pseudo-variable:

substr(s,3,2)='xy';

like the Fortran s(3:4)='xy'

>> Thanks for forwarding this to the J3 list. I think that this function
>> reference as a variable feature could be useful, its just a shame that
>> the syntax has these quirks.

-- glen

John Harper

unread,
Mar 5, 2012, 4:18:59 PM3/5/12
to
robert....@oracle.com wrote:

> You are correct. I oeverlooked that a /do-variable/ is a /name/,
> not a /variable/.
>
At first I thought that was wrong when I found this in F2008 8.1.6.2:

C812 (R819) The do-variable shall be a variable of type integer.

But then I got confused by the previous line saying

R819 do-variable is scalar-int-variable-name

Should C812 have said "The do-variable shall be the name of a variable of
type integer"?

What would have happened if Lewis Carroll, a mathematical logician who wrote
the following, had been a member of J3?

[The White Knight said]'The name of the song is called "HADDOCKS' EYES."'
'Oh, that's the name of the song, is it?' Alice said, trying to feel
interested.
'No, you don't understand,' the Knight said, looking a little vexed.
'That's what the name is CALLED. The name really IS "THE AGED AGED MAN."'
'Then I ought to have said "That's what the SONG is called"?' Alice
corrected herself.
'No, you oughtn't: that's quite another thing! The SONG is called "WAYS
AND MEANS": but that's only what it's CALLED, you know!'
'Well, what IS the song, then?' said Alice, who was by this time
completely bewildered.
'I was coming to that,' the Knight said. 'The song really IS "A-SITTING ON
A GATE": and the tune's my own invention.'

--
John Harper

0 new messages