forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

FTN95 demands type declaration for a subroutine name
Goto page 1, 2  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
mecej4



Joined: 31 Oct 2006
Posts: 1884

PostPosted: Sat Feb 24, 2018 12:57 am    Post subject: FTN95 demands type declaration for a subroutine name Reply with quote

In a program unit that contains a CALL <SNAME>(arglist) statement, SNAME is understood to be the name of a subroutine, typeless, and endowed with the EXTERNAL attribute. The F95 standard says:
Quote:
If the interface of the dummy procedure is implicit and a reference to the procedure appears as a subroutine reference, the actual argument shall be a subroutine or dummy procedure.

Given the following source code
Code:
subroutine sub(a,b)
integer a,b
b=a+2
return
end subroutine

subroutine eval(a,b,proc)
integer a,b
call proc(a,b)
return
end subroutine eval

program tst
external sub
integer p,q
p=2
call eval(p,q,sub)
print *,q
end program

FTN95 says
Code:
[FTN95/x64 Ver. 8.10.0 Copyright (c) Silverfrost Ltd 1993-2017]
    NO ERRORS  [<SUB> FTN95 v8.10.0]
    NO ERRORS  [<EVAL> FTN95 v8.10.0]
0017) call eval(p,q,sub)
WARNING - In a previous call to EVAL, the third argument was of type SUBROUTINE, it is now REAL(KIND=1) FUNCTION
    NO ERRORS, 1 WARNING  [<TST> FTN95 v8.10.0]

There is only one call to EVAL! If I compile with /IMP, I then get
Code:
    NO ERRORS  [<SUB> FTN95 v8.10.0]
0007) subroutine eval(a,b,proc)
*** PROC must appear in a type declaration because IMPLICIT NONE has been used
    1 ERROR  [<EVAL> FTN95 v8.10.0]
    NO ERRORS  [<TST> FTN95 v8.10.0]
*** Compilation failed
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Sat Feb 24, 2018 9:04 am    Post subject: Reply with quote

Many thanks for the feedback. This is probably the same issue as in a previous post. FTN95 sometimes remembers things earlier in the same file when it should forget them.
Back to top
View user's profile Send private message AIM Address
mecej4



Joined: 31 Oct 2006
Posts: 1884

PostPosted: Sat Feb 24, 2018 2:14 pm    Post subject: Reply with quote

Paul, the test case that you remembered is probably this: http://forums.silverfrost.com/viewtopic.php?t=3710 . There, you responded, "FTN95 remembers some things between separate program units when they occur in the same file and this is not always appropriate". That comment certainly applies to the example code of this post.

However, in addition to that problem, there is a separate issue that can be a "show-stopper". Consider the example code
Code:
subroutine eval(a,b,proc)
implicit none
integer a,b
call proc(a,b)
return
end subroutine eval

There is only one subprogram in the file, so there is nothing for the compiler to remember. Yet, the compiler refuses to compile this file:
Code:
[FTN95/Win32 Ver. 8.10.0 Copyright (c) Silverfrost Ltd 1993-2017]
0001) subroutine eval(a,b,proc)
*** PROC must appear in a type declaration because IMPLICIT NONE has been used
    1 ERROR  [<EVAL> FTN95 v8.10.0]
*** Compilation failed

The nature of PROC (that it is a procedure that has to be CALLed, and cannot have a return value or a type) is obvious from the context, and the F95 standard does not require a type declaration (nor does Fortran 95 and earlier provide a way of making such a declaration -- in contrast to the C language void).

A large number of numerical analysis packages apply an algorithm to a user-written subroutine, with the subroutine declared EXTERNAL in the caller and passed as an actual argument. A subroutine had to be used rather than a function in F77 because there was no way in F77 to write an array-valued function. For example, solving a set of nonlinear equations f(x) = 0, with x and f of dimension N, required writing a subroutine.

Any such F77 routine is impossible to compile with FTN95 unless one provides explicit interfaces to procedure arguments or is willing to give up the benefits of using IMPLICIT NONE.


Last edited by mecej4 on Sat Feb 24, 2018 11:47 pm; edited 1 time in total
Back to top
View user's profile Send private message
John-Silver



Joined: 30 Jul 2013
Posts: 1520
Location: Aerospace Valley

PostPosted: Sat Feb 24, 2018 10:35 pm    Post subject: Reply with quote

I didn't know you could pass the name of a subroutine as an argument of a subroutine !
The compiler is obviously seeing it as a variable (even though the 'CALL' statement is there.
Can you have a defined variable with the same name as the name of a subroutine ? It aphe compiler also picks up that the subroutine 'proC' isn't defined anywhere ?pears so.
Presumeably t
_________________
''Computers (HAL and MARVIN excepted) are incredibly rigid. They question nothing. Especially input data.Human beings are incredibly trusting of computers and don't check input data. Together cocking up even the simplest calculation ... Smile "
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1884

PostPosted: Sat Feb 24, 2018 11:47 pm    Post subject: Re: Reply with quote

John-Silver wrote:
I didn't know you could pass the name of a subroutine as an argument of a subroutine !

A programming language without that feature would be very limited in applicability. Such arguments have been allowed at least since Fortran IV. See the last bullet list item on page 64, column 2, of http://bitsavers.org/pdf/ibm/system3/SC28-6874-3_IBM_System3_FortranIV_ReferenceManual_sep76.pdf .

Actually, it is the address of the subroutine entry point that is passed as an argument. The name may not exist in the EXE at all, once the compiler and linker have finished, unless you requested debug symbols to be planted in the EXE.

Fortran 2003 and later allows us to use variables of type "procedure" and pointers to procedures.
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Sun Feb 25, 2018 12:11 am    Post subject: Reply with quote

I'm with you on this, John-Silver. I'd never even used an external function until Clearwin+. Never saw the point, as there are other ways to skin this particular cat. In sensu stricto, and I'm sure that Paul will agree with this, if it is in the standard, and FTN95 is expected to be fully standard-conforming, then sooner or later it needs to be implemented or corrected. The fact that no-one else ever noticed it probably means that the majority of users could well support the fix being a low priority !
.
So Mecej4, did FTN77 handle this? Did FTN95 ever do so (and therefore it could be a regression)? In fact, the problem goes away when the code is compiled without IMPLICIT NONE - so in the interim, you could do without it. What happens if you declare PROC to have a specific type? Or even, can it be declared EXTERNAL (that removes the error, but I don't know if that works in a complete program). I'm assuming that EXTERNAL tells FTN95 &/or SLINK that the name 'proc' is a global symbol. Perhaps Paul would tell us if that is a fix of sorts.

I know that some people declared named BLOCK DATA subprograms EXTERNAL just so that the linker would complain if a separately compiled file wasn't linked, so EXTERNAL is probably rather benign if abused.

Eddie
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Sun Feb 25, 2018 12:41 am    Post subject: Reply with quote

Quote:
A programming language without that feature would be very limited in applicability.


I'm not sure if I agree with that opinion!

Eddie
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Sun Feb 25, 2018 1:01 am    Post subject: Reply with quote

It seems like EXTERNAL is the fix:

Code:
program eddie
implicit none
external proc
integer a,b
a=1;b=2
call eval(a,b,proc)
end
subroutine eval(a,b,proc)
implicit none
external proc
integer a,b
call proc(a,b)
return
end subroutine eval
subroutine proc(a,b)
implicit none
integer a,b
write(*,*) a,b,a+b
return
end


It seems like "procedure" is spelled "external" up in Salford ! (sometimes).

Eddie
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1884

PostPosted: Sun Feb 25, 2018 3:47 am    Post subject: Re: Reply with quote

LitusSaxonicum wrote:
It seems like EXTERNAL is the fix

That would be redundant. In fact, the F95 standard covers this issue:
Quote:
12.1.1 Procedure classification by reference: ... A reference to a subroutine is a CALL statement or...

followed by
Quote:
12.2.1 Characteristics of dummy arguments: Each dummy argument is either a dummy data object, a dummy procedure...

and
Quote:
12.1.2.3 Dummy procedures: A dummy argument that is specified as a procedure or appears in a procedure reference is a dummy procedure.

The second alternative in the last quote establishes that the CALL statement with the dummy argument PROC makes the dummy identifiable as a dummy procedure (rather than a dummy data object). Therefore, adding an EXTERNAL declaration, which is the first alternative, would be redundant and the compiler is wrong to require such redundancy.

Secondly, once PROC is identified as a dummy procedure, it is clearly not a data object, and the CALL PROC establishes that the procedure is a subroutine and not a function. Therefore, there is no basis for requiring a type declaration, with or without IMPLICIT NONE.
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Sun Feb 25, 2018 11:32 am    Post subject: Reply with quote

The IBM system 3 was introduced in 1969, and so would not have had IMPLICIT NONE in its Fortran compiler, so the problem is introduced in Fortran 77: in my view for this problem the redundancy is in IMPLICIT NONE, in the sense of “not (or no longer) needed or useful; superfluous.” The Fortran of the time also had no INTENT, so it cared not whether an argument was used.
Indeed, the passing of a subroutine name to another subprogram is itself superfluous, as the programmer must know at the time of writing the program the full range of possible names (as they don’t appear to be passed as a character variable), so the problem can quite easily be addressed through an integer variable N, as in:
Code:
IF (N .EQ. 1) THEN
CALL PROC (A, B)
ELSE IF (N .EQ. 2) THEN
CALL SOLV (A, B)
Etc

If there are only two choices, a LOGICAL variable would suffice. So the whole edifice is superfluous anyway.
I bow to your command of the Fortran standards, but if there is no problem with this bizarre, virtually unknown and entirely superfluous case, then why is the declaration of PROCEDURE required in later standards? Presumably Silverfrost could snooker this argument by creating a PROCEDURE alias for EXTERNAL, and claiming this as a Fortran 2003 feature.
Indeed, if you insist on the declaration of types for all symbols through IMPLICIT NONE, then how is a compiler to recognise at an early stage that a particular symbol is an external subprogram? (In accordance with the lines you cite). At least a FUNCTION has a type, which is apparent to the compiler, either implicitly or explicitly. If the compiler assumes (as it might quite properly do), that any symbol name in an argument list that does not have a specific declaration of type is a procedure name, then much of the point of IMPLICIT NONE is defeated, and the early reporting of undefined variables would not be possible, as the check would be deferred until the whole Fortran code had been examined for a CALL statement, in which case the check would be reported at the final END of a subprogram. Instead, it appears to me that FTN95 finalises its list of declared variable types at the first executable statement. On the balance of probability it is far more likely that an undeclared argument type is simply an error rather than an external procedure name.
The use of EXTERNAL is a way of telling the compiler that the argument is a procedure that cuts the Gordian knot.
You will have seen my stated view on standards-compliance, but there are other criteria such as usefulness, and this is far from being the show-stopper you claim. There are at least 3 solutions, and obstinate insistence on conformance to a rather ridiculous, bizarre and virtually unknown facility is itself rather bizarre, and potentially a huge time-waster for someone.
Eddie
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1884

PostPosted: Sun Feb 25, 2018 2:04 pm    Post subject: Re: Reply with quote

LitusSaxonicum wrote:
Indeed, the passing of a subroutine name to another subprogram is itself superfluous, as the programmer must know at the time of writing the program the full range of possible names (as they don’t appear to be passed as a character variable),

Anyone who has used subroutine libraries knows that this claim is not valid. Here is an example: the NAG library routine E04ABF (documented at https://nag.co.uk/numeric/fl/nagdoc_fl26/html/e04/e04abf.html) finds the minimum of F(x) in the interval (a,b). What is the very first argument passed to E04ABF? It is the function pointer to F. When the library was written, the authors could not have known the name of a function subprogram for F(x) that a user would write years later, nor could they have relied on the linker's placing the function code at a pre-specified address. In Fortran 77, the number of possible names of functions is 26 X 37^30, so a sequence of IF - THEN - ELSE-s to cover all names would be rather formidable.

In Fortran, there are three widely used methods for calling an arbitrary user-defined function: (i) subprogram arguments, which we are discussing here, (ii) reverse communication, which is useful and has its place, but lots of drawbacks to usage, and (iii) alternate returns, which are obsolete.

If you sit back and think about how a compiler works, you may realise that when you use a compiler (from the command line or a GUI front end) you are doing something similar to passing a function: you pass the source file name to a compiler. What happens may well be paraphrased as CALL COMPILER(arg1, arg2, ...), with arg1 = <source_file_name>, arg2 = '/OPT', arg3 = '/64', etc. The number of possible values for arg2, etc., may be few enough to be handled by SELECT CASE or IF-THEN sequences, but the number of possible values for arg1 is, essentially, infinite.

Eddie, I find (through Search) that we have gone through this debate before, in 2014, with DavidB, John Campbell and others contributing their takes: http://forums.silverfrost.com/viewtopic.php?t=2847&highlight=simpson .

F.W.I.W., IMPLICIT NONE is described in detail on p. 51 of the IBM Fortran IV manual that I cited. Most of my exposure to mainframes was to CDC 6000 series machines. Those did not have IMPLICIT NONE, and "byte" was an alien concept.
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2551
Location: Sydney

PostPosted: Sun Feb 25, 2018 11:32 pm    Post subject: Reply with quote

This must be a compiler bug for IMPLICIT NONE
Based on mecej4's quote of the F95 standard, there is a bug in the use of implicit none.I did the following tests:
Code:

!  this works
 subroutine eval(a,b,proc)
! implicit none
! external proc
  integer a,b
  call proc(a,b)
  return
 end subroutine eval

!  this works
 subroutine eval(a,b,proc)
  implicit none
  external proc
  integer a,b
  call proc(a,b)
  return
 end subroutine eval

!  this fails
 subroutine eval(a,b,proc)
 implicit none
! external proc
  integer a,b
  call proc(a,b)
  return
 end subroutine eval


I have seen other examples where FTN95 assumes a function when an array is not correctly defined, so there are rules in the compiler to identify external routines. It appears that an externally supplied subroutine is not handled correctly.
It has been a bit vague to me on when EXTERNAL must be provided. I typically use EXTERNAL for documentation to list the routines that are called from this routine.

Eddie, there is the classic coding of Simpson's rule, by supplying an external function, but it is an infrequent coding approach.

John
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1884

PostPosted: Mon Feb 26, 2018 2:05 am    Post subject: Reply with quote

The third version of EVAL provided by John is compiled without error messages by Lahey, NAG, Gfortran and Intel.

Quote:
It has been a bit vague to me on when EXTERNAL must be provided.
There are some heuristics that I use, and a compiler might use similar rules to resolve apparent ambiguities, but it often has to digest the full body of a subprogram before this becomes possible.

EXTERNAL comes into relevance only if leaving it out would cause the named variable to be treated as a data object instead of a procedure object, and we do not want that to occur. The question arises most often in the caller, because the compiler has to insert information in the OBJ file to tell the linker to look for that external symbol in the same or other OBJ files or libraries.

In a procedure that receives a procedure argument and passes it to another procedure, it is unnecessary to establish whether the pass-through variable is a procedure object or a data object. No EXTERNAL needed.

In a procedure that receives a procedure argument and references that procedure, the compiler has to know whether that is a subroutine or a function, and the type of the return value, if a function. From the context of the procedure reference it should be clear whether the procedure is a subroutine or a function. For a function, a type declaration may be provided or implicit typing accepted.

There are probably circumstances that are not covered by these heuristics. If the same name is used for two different procedure,s scoping rules may have to be applied to decide which specific procedure is to be invoked.
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1884

PostPosted: Mon Feb 26, 2018 1:26 pm    Post subject: Re: Reply with quote

JohnCampbell wrote:
... there is the classic coding of Simpson's rule, by supplying an external function, but it is an infrequent coding approach.

That infrequency is probably experienced by people working with linear problems (such as FEA stress analyses of elastic structures). For such problems, the assembly phase leaves one with the mathematical problem of solving a sparse system of linear equations. For representing the full details of the problem and the resulting solution, the native structures of Fortran -- 1-, 2- and 3-dimensional arrays -- suffice.

When the problems being solved are nonlinear, and because of the large (essentially, infinite) types of nonlinearity possible, if one wishes to write modular code there has to be a way for the solver code to return control to the caller, requesting a function, gradient or Hessian to be evaluated.

Even for linear but large-scale problems, such call-backs are used when Arnoldi techniques are used. There are iterative sparse linear equation solvers that solve A x = b without knowing A; all that they require is that the user provide a call-back procedure that computes A x or A x - b when requested.
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Mon Feb 26, 2018 4:34 pm    Post subject: Reply with quote

The two issues raised by mecej4 at the beginning of this thread have now been fixed for the next release of FTN95.
Back to top
View user's profile Send private message AIM Address
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Goto page 1, 2  Next
Page 1 of 2

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group