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

Procedure Pointer (Components) with no explicit interface and with implicit typing

18 views
Skip to first unread message

Tobias Burnus

unread,
May 1, 2009, 5:02:06 AM5/1/09
to
Hello,

if I have

EXTERNAL proc

"proc" can be either a subroutine or a function. If I use

x = proc() ! (A)

I have an implicitly typed function. And using

call proc() ! (B)

I know that proc must be a subroutine. Mixing (A) and (B) in the same
program does not make sense and is invalid. ("proc" can either be a
subroutine or a function.)

The question is now: If I have a procedure pointer,

PROCEDURE(), POINTER :: procptr

in principle, I can assign to it either a function nor a subroutine, e.g.

procptr => sub
call procptr() ! (C)
procptr => func
x = procptr() ! (D)

Thus the function call (D) and the subroutine call (C) are both well
defined (whether they are valid standard Fortran is a different question).

Am I understanding the standard correctly, that (D) is invalid because
"procptr" has been used as subroutine before?

Analogously, one can have

type t
procedure(), pointer, nopass :: p
end type t
type(t) :: a, b
external :: func, sub

a%p => sub
b%p => func
call a%p
y = b%p()

Is is correct according to the standard that now "a%p" can not be used
as a function and b%p not used as subroutine since there was "call a%p"
and "y = b%p" before?

Additionally, is is correct that "b%p" gets implicitly typed as REAL in
this example? And thus, if there were an "IMPLICIT NONE", I could not
call it as function directly, but I had to use something like the following?

procedure(REAL), pointer :: ptr
ptr => b%p
y = ptr()

Or is this invalid as due to implicit none "b%p" needs to be a subroutine?

Thanks for enlightening me.

Tobias

Tobias Burnus

unread,
May 1, 2009, 1:33:14 PM5/1/09
to
Hello all,

I am *partially* answering myself below - but I am not completely sure
regarding some parts -- see especially at the bottom.

Tobias Burnus wrote:
> The question is now: If I have a procedure pointer,
> PROCEDURE(), POINTER :: procptr
> in principle, I can assign to it either a function nor a subroutine, e.g.
> procptr => sub
> call procptr() ! (C)
> procptr => func
> x = procptr() ! (D)
> Thus the function call (D) and the subroutine call (C) are both well
> defined (whether they are valid standard Fortran is a different question).
>
> Am I understanding the standard correctly, that (D) is invalid because
> "procptr" has been used as subroutine before?


I am reading the following such that the last two lines of the code
snippet above are invalid because of the following:

"7.4.2.2 Procedure pointer assignment"
"If proc-pointer-object has an implicit interface and is explicitly
typed or referenced as a function, proc-target shall be a function. If
proc-pointer-object has an implicit interface and is referenced as a
subroutine, proc-target shall be a subroutine."


> Analogously, one can have
>
> type t
> procedure(), pointer, nopass :: p
> end type t
> type(t) :: a, b
> external :: func, sub
>
> a%p => sub
> b%p => func
> call a%p
> y = b%p()

(I believe the program above is valid)

> Is it correct according to the standard that now "a%p" can not be used


> as a function and b%p not used as subroutine since there was "call a%p"
> and "y = b%p" before?

I think the same clause as above applies here, which makes any of the
following invalid if *added after* the code above:
"a%p=> func", "y = b%p()", "b%p => sub" and "call b%p".


> Additionally, is it correct that "b%p" gets implicitly typed as REAL in
> this example?

I believe it does get implicitly typed as in
b % p
"p" is the data entity / name which is referred to in "5.3 IMPLICIT
statement":

"Any data entity that is not explicitly declared by a type declaration
statement, is not an intrinsic function, and is not made accessible by
use association or host association is declared implicitly to be of the
type (and type parameters) mapped from the first letter of its name,
provided the mapping is not null."

Thus in "y = b % p()", "p" is implicitly typed as REAL (assuming no
IMPLICIT statement is present).


> And thus, if there were an "IMPLICIT NONE", I could not
> call it as function

This is still unclear to me.

F2003 has in 7.4.2.2:
"If proc-pointer-object has an implicit interface and is explicitly
typed or referenced as a function, proc-target shall be a function. If
proc-pointer-object has an implicit interface and is referenced as a
subroutine, proc-target shall be a subroutine."
"If proc-target and proc-pointer-object are functions, they shall have
the same type; corresponding type parameters shall either both be
deferred or both have the same value."

Assuming:
IMPLICIT NONE
real, external :: func
procedure(), pointer :: p
p => func
and furthermore assuming that p is not referenced as function (nor as
subroutine).

I don't see why it is invalid. But if it where valid, the following were
valid as well:

implicit none
external :: func
procedure(), pointer :: p1
procedure(REAL), pointer :: p2
real :: y
p1 => func ! (A)
p2 => p1 ! (B)
y = p2()

(A) is the questionable part from above. For (B) one has: p2 is
explicitly typed as function thus p2 needs to be associated with a
function with the same type. If it were associated if p1, it were
invalid as p1 does not have the right type (zero implicit mapping);
however, p2 is associated with the target of p1 (*) which is "func"
which is a real function.
(* = "if proc-target is associated with a procedure, proc-pointer-object
becomes associated with the same procedure.")

The three compilers I tried, accept (A) but reject (B).

Tobias

Richard Maine

unread,
May 1, 2009, 3:46:29 PM5/1/09
to
Tobias Burnus <bur...@net-b.de> wrote:
[questions about procedure pointers that could be either subroutines
or functions]

Afraid I don't have any answers for you... so perhaps I shouldn't post
at all. :-) I just wanted to let you know that I did see the question
and am not ignoring it. I just don't feel I can answer.

I think that kind of implicitness is an abomination that I wish hadn't
been allowed in the standard at all. It's a mess. I've seen some
discussion about some of the tricky points, but I'm afraid I just don't
recall the conclusions and some of the arguments seemed non-intuitive
enough to me that I don't think I can accurately reconstruct them. I'm
not even 100% sure that the questions were formally answered
definitively.

Some of the parts that I recall significant debate about related to
whether some restrictions were compile-time or run-time restrictions (of
course, not in those words in the standard, but with those ideas). For
example, off the top of my head, without trying to get the syntax and
other details right, is it valid to do something like

if (do_the_subroutine) then
proc_pointer => some_subroutine
call proc_pointer(x,y)
else
proc_pointer => some_function
y = proc_pointer(x)
end if

I suppose this is simillar to one of your examples.

I just don't recall the answer or even if there was formal agreement on
the answer. My personal answer is just yukk, but I realize that doesn't
hack it if you are trying to make compiler conform to the standard. :-)

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain

Dan Nagle

unread,
May 1, 2009, 4:24:25 PM5/1/09
to
Hello,

On 2009-05-01 15:46:29 -0400, nos...@see.signature (Richard Maine) said:

> Tobias Burnus <bur...@net-b.de> wrote:
> [questions about procedure pointers that could be either subroutines
> or functions]

> I've seen some


> discussion about some of the tricky points, but I'm afraid I just don't
> recall the conclusions and some of the arguments seemed non-intuitive
> enough to me that I don't think I can accurately reconstruct them. I'm
> not even 100% sure that the questions were formally answered
> definitively.

This is my recollection as well.

I think the issue has been discussed,
but I can't recall the result, nor whether
it was a formal interp or "just talk" :-(

If I had to guess, I'd guess "non-standard"
but I could be wrong.

I also agree with the "yukk" :-) <snipped>

--
Cheers!

Dan Nagle

0 new messages